aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers/Txt2Tags.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Readers/Txt2Tags.hs')
-rw-r--r--src/Text/Pandoc/Readers/Txt2Tags.hs55
1 files changed, 43 insertions, 12 deletions
diff --git a/src/Text/Pandoc/Readers/Txt2Tags.hs b/src/Text/Pandoc/Readers/Txt2Tags.hs
index 3a51b9d84..6f8c19ac7 100644
--- a/src/Text/Pandoc/Readers/Txt2Tags.hs
+++ b/src/Text/Pandoc/Readers/Txt2Tags.hs
@@ -73,11 +73,13 @@ instance Default T2TMeta where
getT2TMeta :: [FilePath] -> FilePath -> IO T2TMeta
getT2TMeta inps out = do
curDate <- formatTime defaultTimeLocale "%F" <$> getZonedTime
- let getModTime = fmap (formatTime defaultTimeLocale "%F") .
+ let getModTime = fmap (formatTime defaultTimeLocale "%T") .
getModificationTime
- curMtime <- catchIOError
- (maximum <$> mapM getModTime inps)
- (const (return ""))
+ curMtime <- case inps of
+ [] -> formatTime defaultTimeLocale "%T" <$> getZonedTime
+ _ -> catchIOError
+ (maximum <$> mapM getModTime inps)
+ (const (return ""))
return $ T2TMeta curDate curMtime (intercalate ", " inps) out
-- | Read Txt2Tags from an input string returning a Pandoc document
@@ -91,13 +93,42 @@ readTxt2TagsNoMacros = readTxt2Tags def
parseT2T :: T2T Pandoc
parseT2T = do
- _ <- (Nothing <$ try blankline) <|> (Just <$> (count 3 anyLine))
+ -- Parse header if standalone flag is set
+ standalone <- getOption readerStandalone
+ when standalone parseHeader
+ body <- mconcat <$> manyTill block eof
+ meta' <- stateMeta <$> getState
+ return $ Pandoc meta' (B.toList body)
+
+parseHeader :: T2T ()
+parseHeader = do
+ () <$ try blankline <|> header
+ meta <- stateMeta <$> getState
+ optional blanklines
config <- manyTill setting (notFollowedBy setting)
-- TODO: Handle settings better
- let settings = foldr (\(k,v) -> B.setMeta k (MetaString v)) nullMeta config
- updateState (\s -> s {stateMeta = settings})
- body <- mconcat <$> manyTill block eof
- return $ Pandoc mempty (B.toList body)
+ let settings = foldr (\(k,v) -> B.setMeta k (MetaString v)) meta config
+ updateState (\s -> s {stateMeta = settings}) <* optional blanklines
+
+header :: T2T ()
+header = titleline >> authorline >> dateline
+
+headerline :: B.ToMetaValue a => String -> T2T a -> T2T ()
+headerline field p = (() <$ try blankline)
+ <|> (p >>= updateState . B.setMeta field)
+
+titleline :: T2T ()
+titleline =
+ headerline "title" (trimInlines . mconcat <$> manyTill inline newline)
+
+authorline :: T2T ()
+authorline =
+ headerline "author" (sepBy author (char ';') <* newline)
+ where
+ author = trimInlines . mconcat <$> many (notFollowedBy (char ';' <|> newline) >> inline)
+
+dateline :: T2T ()
+dateline = headerline "date" (trimInlines . mconcat <$> manyTill inline newline)
type Keyword = String
type Value = String
@@ -242,7 +273,7 @@ indentWith n = count n space
table :: T2T Blocks
table = try $ do
- header <- fmap snd <$> option mempty (try headerRow)
+ tableHeader <- fmap snd <$> option mempty (try headerRow)
rows <- many1 (many commentLine *> tableRow)
let columns = transpose rows
let ncolumns = length columns
@@ -250,7 +281,7 @@ table = try $ do
let rows' = map (map snd) rows
let size = maximum (map length rows')
let rowsPadded = map (pad size) rows'
- let headerPadded = if (not (null header)) then pad size header else mempty
+ let headerPadded = if (not (null tableHeader)) then pad size tableHeader else mempty
return $ B.table mempty
(zip aligns (replicate ncolumns 0.0))
headerPadded rowsPadded
@@ -497,7 +528,7 @@ image = try $ do
-- Characters used in markup
specialChars :: String
-specialChars = "%*-_/|:+"
+specialChars = "%*-_/|:+;"
tab :: T2T Char
tab = char '\t'