aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2014-08-21 16:42:28 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2014-08-21 16:42:28 -0700
commit17f71002ae099fe1bbd4ffda4a979bb6c5bab9e1 (patch)
treee69b70e81e7556ac78ae15352eabda1cb0de7b42
parent604e1da878982fb14827b0ef5087c4646a85ff00 (diff)
parentaa808055f04951e4d6f580764ca755c4391c96b1 (diff)
downloadpandoc-17f71002ae099fe1bbd4ffda4a979bb6c5bab9e1.tar.gz
Merge pull request #1553 from mpickering/master
Txt2Tags reader: Header is now parsed only if standalone flag is set
-rw-r--r--src/Text/Pandoc/Readers/Txt2Tags.hs55
-rw-r--r--tests/Tests/Old.hs2
-rw-r--r--tests/Tests/Readers/Txt2Tags.hs2
-rw-r--r--tests/txt2tags.native1
-rw-r--r--tests/txt2tags.t2t4
5 files changed, 48 insertions, 16 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'
diff --git a/tests/Tests/Old.hs b/tests/Tests/Old.hs
index 300430e79..256855a1d 100644
--- a/tests/Tests/Old.hs
+++ b/tests/Tests/Old.hs
@@ -141,7 +141,7 @@ tests = [ testGroup "markdown"
"haddock-reader.haddock" "haddock-reader.native"
]
, testGroup "txt2tags"
- [ test "reader" ["-r", "t2t", "-w", "native"]
+ [ test "reader" ["-r", "t2t", "-w", "native", "-s"]
"txt2tags.t2t" "txt2tags.native" ]
, testGroup "epub" [
test "features" ["-r", "epub", "-w", "native"]
diff --git a/tests/Tests/Readers/Txt2Tags.hs b/tests/Tests/Readers/Txt2Tags.hs
index 4748cdc07..fd7c767e0 100644
--- a/tests/Tests/Readers/Txt2Tags.hs
+++ b/tests/Tests/Readers/Txt2Tags.hs
@@ -12,7 +12,7 @@ import Data.Monoid (mempty, mconcat)
import Text.Pandoc.Readers.Txt2Tags
t2t :: String -> Pandoc
-t2t s = readTxt2Tags (T2TMeta "date" "mtime" "in" "out") def ('\n' : s)
+t2t s = readTxt2Tags (T2TMeta "date" "mtime" "in" "out") def s
infix 4 =:
(=:) :: ToString c
diff --git a/tests/txt2tags.native b/tests/txt2tags.native
index 9f80d6d2c..189c099e2 100644
--- a/tests/txt2tags.native
+++ b/tests/txt2tags.native
@@ -1,3 +1,4 @@
+Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "author"]]),("date",MetaInlines [Str "date"]),("includeconf",MetaString "rules.conf"),("title",MetaInlines [Str "Txt2tags",Space,Str "Markup",Space,Str "Rules"])]})
[Para [Str "This",Space,Str "document",Space,Str "describes",Space,Str "all",Space,Str "the",Space,Str "details",Space,Str "about",Space,Str "each",Space,Str "txt2tags",Space,Str "mark.",Space,Str "The",Space,Str "target",Space,Str "audience",Space,Str "are",Space,Strong [Str "experienced"],Space,Str "users.",Space,Str "You",Space,Str "may",Space,Str "find",Space,Str "it",Space,Str "useful",Space,Str "if",Space,Str "you",Space,Str "want",Space,Str "to",Space,Str "master",Space,Str "the",Space,Str "marks",Space,Str "or",Space,Str "solve",Space,Str "a",Space,Str "specific",Space,Str "problem",Space,Str "about",Space,Str "a",Space,Str "mark."]
,Para [Str "If",Space,Str "you",Space,Str "are",Space,Str "new",Space,Str "to",Space,Str "txt2tags",Space,Str "or",Space,Str "just",Space,Str "want",Space,Str "to",Space,Str "know",Space,Str "which",Space,Str "are",Space,Str "the",Space,Str "available",Space,Str "marks,",Space,Str "please",Space,Str "read",Space,Str "the",Space,Link [Str "Markup",Space,Str "Demo"] ("MARKUPDEMO",""),Str "."]
,Para [Str "Note",Space,Str "1:",Space,Str "This",Space,Str "document",Space,Str "is",Space,Str "generated",Space,Str "directly",Space,Str "from",Space,Str "the",Space,Str "txt2tags",Space,Str "test-suite.",Space,Str "All",Space,Str "the",Space,Str "rules",Space,Str "mentioned",Space,Str "here",Space,Str "are",Space,Str "100%",Space,Str "in",Space,Str "sync",Space,Str "with",Space,Str "the",Space,Str "current",Space,Str "program",Space,Str "code."]
diff --git a/tests/txt2tags.t2t b/tests/txt2tags.t2t
index e282498d0..d374b7a85 100644
--- a/tests/txt2tags.t2t
+++ b/tests/txt2tags.t2t
@@ -1,6 +1,6 @@
Txt2tags Markup Rules
-
-
+author
+date
%!includeconf: rules.conf
This document describes all the details about each txt2tags mark.