aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Text/Pandoc/Readers/Org/Meta.hs28
-rw-r--r--test/Tests/Readers/Org/Meta.hs55
2 files changed, 44 insertions, 39 deletions
diff --git a/src/Text/Pandoc/Readers/Org/Meta.hs b/src/Text/Pandoc/Readers/Org/Meta.hs
index 7ee64c2e5..fdb7abe7c 100644
--- a/src/Text/Pandoc/Readers/Org/Meta.hs
+++ b/src/Text/Pandoc/Readers/Org/Meta.hs
@@ -74,11 +74,11 @@ metaKey = T.toLower <$> many1Char (noneOf ": \n\r")
exportSettingHandlers :: PandocMonad m => Map Text (OrgParser m ())
exportSettingHandlers = Map.fromList
[ ("result" , fmap pure anyLine `parseThen` discard) -- RESULT is never an export setting
- , ("author" , commaSepInlines `parseThen` setField "author")
- , ("keywords" , commaSepInlines `parseThen` setField "keywords")
+ , ("author" , lineOfInlines `parseThen` collectLines "author")
+ , ("keywords" , lineOfInlines `parseThen` collectLines "keywords")
, ("date" , lineOfInlines `parseThen` setField "date")
- , ("description", lineOfInlines `parseThen` collectSepBy B.SoftBreak "description")
- , ("title" , lineOfInlines `parseThen` collectSepBy B.Space "title")
+ , ("description", lineOfInlines `parseThen` collectLines "description")
+ , ("title" , lineOfInlines `parseThen` collectLines "title")
, ("nocite" , lineOfInlines `parseThen` collectAsList "nocite")
, ("latex_class", fmap pure anyLine `parseThen` setField "documentclass")
, ("latex_class_options", (pure . T.filter (`notElem` ("[]" :: String)) <$> anyLine)
@@ -101,8 +101,8 @@ parseThen p modMeta = do
discard :: a -> Meta -> Meta
discard = const id
-collectSepBy :: Inline -> Text -> Inlines -> Meta -> Meta
-collectSepBy sep key value meta =
+collectLines :: Text -> Inlines -> Meta -> Meta
+collectLines key value meta =
let value' = appendValue meta (B.toList value)
in B.setMeta key value' meta
where
@@ -117,7 +117,7 @@ collectSepBy sep key value meta =
collectInlines :: MetaValue -> [Inline]
collectInlines = \case
MetaInlines inlns -> inlns
- MetaList ml -> intercalate [sep] $ map collectInlines ml
+ MetaList ml -> intercalate [B.SoftBreak] $ map collectInlines ml
MetaString s -> [B.Str s]
MetaBlocks blks -> blocksToInlines blks
MetaMap _map -> []
@@ -138,16 +138,6 @@ collectAsList key value meta =
setField :: ToMetaValue a => Text -> a -> Meta -> Meta
setField field value meta = B.setMeta field (B.toMetaValue value) meta
-lineOfInlines :: PandocMonad m => OrgParser m (F Inlines)
-lineOfInlines = inlinesTillNewline
-
-commaSepInlines :: PandocMonad m => OrgParser m (F [Inlines])
-commaSepInlines = do
- itemStrs <- many1Char (noneOf ",\n") `sepBy1` char ','
- newline
- items <- mapM (parseFromString inlinesTillNewline . (<> "\n")) itemStrs
- return $ sequence items
-
-- | Read an format specific meta definition
metaExportSnippet :: Monad m => Text -> OrgParser m (F Inlines)
metaExportSnippet format = pure . B.rawInline format <$> anyLine
@@ -233,8 +223,8 @@ emphChars = do
skipSpaces
safeRead <$> anyLine
-inlinesTillNewline :: PandocMonad m => OrgParser m (F Inlines)
-inlinesTillNewline = do
+lineOfInlines :: PandocMonad m => OrgParser m (F Inlines)
+lineOfInlines = do
updateLastPreCharPos
trimInlinesF . mconcat <$> manyTill inline newline
diff --git a/test/Tests/Readers/Org/Meta.hs b/test/Tests/Readers/Org/Meta.hs
index 27fd20744..ab6de231b 100644
--- a/test/Tests/Readers/Org/Meta.hs
+++ b/test/Tests/Readers/Org/Meta.hs
@@ -46,18 +46,24 @@ tests =
meta = setMeta "title" (MetaInlines titleInline) nullMeta
in Pandoc meta mempty
- , "Author" =:
- "#+author: John /Emacs-Fanboy/ Doe" =?>
- let author = toList . spcSep $ [ "John", emph "Emacs-Fanboy", "Doe" ]
- meta = setMeta "author" (MetaList [MetaInlines author]) nullMeta
- in Pandoc meta mempty
+ , testGroup "Author"
+ [ "sets 'author' field" =:
+ "#+author: John /Emacs-Fanboy/ Doe" =?>
+ let author = toList . spcSep $ [ "John", emph "Emacs-Fanboy", "Doe" ]
+ meta = setMeta "author" (MetaInlines author) nullMeta
+ in Pandoc meta mempty
- , "Multiple authors" =:
- "#+author: James Dewey Watson, Francis Harry Compton Crick " =?>
- let watson = MetaInlines $ toList "James Dewey Watson"
- crick = MetaInlines $ toList "Francis Harry Compton Crick"
- meta = setMeta "author" (MetaList [watson, crick]) nullMeta
- in Pandoc meta mempty
+ , "Multiple author lines" =:
+ T.unlines [ "#+author: James Dewey Watson,"
+ , "#+author: Francis Harry Compton Crick"
+ ] =?>
+ let watson = toList "James Dewey Watson,"
+ crick = toList "Francis Harry Compton Crick"
+ meta = setMeta "author"
+ (MetaInlines (watson ++ SoftBreak : crick))
+ nullMeta
+ in Pandoc meta mempty
+ ]
, "Date" =:
"#+Date: Feb. *28*, 2014" =?>
@@ -83,6 +89,14 @@ tests =
in Pandoc meta mempty
]
+ , "Keywords" =:
+ T.unlines [ "#+KEYWORDS: pandoc, testing,"
+ , "#+KEYWORDS: Org"
+ ] =?>
+ let keywords = toList $ "pandoc, testing," <> softbreak <> "Org"
+ meta = setMeta "keywords" (MetaInlines keywords) nullMeta
+ in Pandoc meta mempty
+
, "Properties drawer" =:
T.unlines [ " :PROPERTIES:"
, " :setting: foo"
@@ -97,11 +111,20 @@ tests =
meta = setMeta "header-includes" inclList nullMeta
in Pandoc meta mempty
- , "LaTeX_class option is translated to documentclass" =:
+ , testGroup "LaTeX_CLASS"
+ [ "LaTeX_class option is translated to documentclass" =:
"#+LATEX_CLASS: article" =?>
let meta = setMeta "documentclass" (MetaString "article") nullMeta
in Pandoc meta mempty
+ , "last definition takes precedence" =:
+ T.unlines [ "#+LATEX_CLASS: this will not be used"
+ , "#+LATEX_CLASS: report"
+ ] =?>
+ let meta = setMeta "documentclass" (MetaString "report") nullMeta
+ in Pandoc meta mempty
+ ]
+
, "LaTeX_class_options is translated to classoption" =:
"#+LATEX_CLASS_OPTIONS: [a4paper]" =?>
let meta = setMeta "classoption" (MetaString "a4paper") nullMeta
@@ -114,14 +137,6 @@ tests =
meta = setMeta "header-includes" inclList nullMeta
in Pandoc meta mempty
- , "later meta definitions take precedence" =:
- T.unlines [ "#+AUTHOR: this will not be used"
- , "#+author: Max"
- ] =?>
- let author = MetaInlines [Str "Max"]
- meta = setMeta "author" (MetaList [author]) nullMeta
- in Pandoc meta mempty
-
, "Logbook drawer" =:
T.unlines [ " :LogBook:"
, " - State \"DONE\" from \"TODO\" [2014-03-03 Mon 11:00]"