Org reader: read LaTeX_header as header-includes

LaTeX-specific header commands can be defined in `#+LaTeX_header` lines.
They are parsed as format-specific inlines to ensure that they will only
show up in LaTeX output.
This commit is contained in:
Albert Krewinkel 2016-08-29 14:10:57 +02:00
parent 75df104215
commit a257488343
No known key found for this signature in database
GPG key ID: 388DC0B21F631124
2 changed files with 38 additions and 9 deletions

View file

@ -1,4 +1,5 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TupleSections #-}
{-
Copyright (C) 2014-2016 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
@ -56,9 +57,9 @@ metaLine = mempty <$ metaLineStart <* (optionLine <|> declarationLine)
declarationLine :: OrgParser ()
declarationLine = try $ do
key <- map toLower <$> metaKey
value <- metaValue key
(key', value) <- metaValue key
updateState $ \st ->
let meta' = B.setMeta key <$> value <*> pure nullMeta
let meta' = B.setMeta key' <$> value <*> pure nullMeta
in st { orgStateMeta = meta' <> orgStateMeta st }
metaKey :: OrgParser String
@ -66,13 +67,17 @@ metaKey = map toLower <$> many1 (noneOf ": \n\r")
<* char ':'
<* skipSpaces
metaValue :: String -> OrgParser (F MetaValue)
metaValue key = do
case key of
"author" -> metaInlinesCommaSeparated
"title" -> metaInlines
"date" -> metaInlines
_ -> metaString
metaValue :: String -> OrgParser (String, (F MetaValue))
metaValue key =
let inclKey = "header-includes"
in case key of
"author" -> (key,) <$> metaInlinesCommaSeparated
"title" -> (key,) <$> metaInlines
"date" -> (key,) <$> metaInlines
"header-includes" -> (key,) <$> accumulatingList key metaInlines
"latex_header" -> (inclKey,) <$>
accumulatingList inclKey (metaExportSnippet "latex")
_ -> (key,) <$> metaString
metaInlines :: OrgParser (F MetaValue)
metaInlines = fmap (MetaInlines . B.toList) <$> inlinesTillNewline
@ -88,6 +93,23 @@ metaInlinesCommaSeparated = do
metaString :: OrgParser (F MetaValue)
metaString = return . MetaString <$> anyLine
-- | Read an format specific meta definition
metaExportSnippet :: String -> OrgParser (F MetaValue)
metaExportSnippet format =
return . MetaInlines . B.toList . B.rawInline format <$> anyLine
-- | Accumulate the result of the @parser@ in a list under @key@.
accumulatingList :: String
-> OrgParser (F MetaValue)
-> OrgParser (F MetaValue)
accumulatingList key p = do
value <- p
meta' <- orgStateMeta <$> getState
return $ (\m v -> MetaList (curList m ++ [v])) <$> meta' <*> value
where curList m = case lookupMeta key m of
Just (MetaList ms) -> ms
Just x -> [x]
_ -> []
--
-- export options

View file

@ -496,6 +496,13 @@ tests =
] =?>
(mempty::Blocks)
, "LaTeX_headers options are translated to header-includes" =:
"#+LaTeX_header: \\usepackage{tikz}" =?>
let latexInlines = rawInline "latex" "\\usepackage{tikz}"
inclList = MetaList [MetaInlines (toList latexInlines)]
meta = setMeta "header-includes" inclList nullMeta
in Pandoc meta mempty
, "later meta definitions take precedence" =:
unlines [ "#+AUTHOR: this will not be used"
, "#+author: Max"