Org reader: read markup only for special meta keys
Most meta-keys should be read as normal string values, only a few are interpreted as marked-up text.
This commit is contained in:
parent
bed5f700ce
commit
153970bef5
2 changed files with 22 additions and 7 deletions
|
@ -55,20 +55,35 @@ metaLine = mempty <$ metaLineStart <* (optionLine <|> declarationLine)
|
|||
|
||||
declarationLine :: OrgParser ()
|
||||
declarationLine = try $ do
|
||||
key <- metaKey
|
||||
value <- metaInlines
|
||||
key <- map toLower <$> metaKey
|
||||
value <- metaValue key
|
||||
updateState $ \st ->
|
||||
let meta' = B.setMeta key <$> value <*> pure nullMeta
|
||||
in st { orgStateMeta = orgStateMeta st <> meta' }
|
||||
|
||||
metaInlines :: OrgParser (F MetaValue)
|
||||
metaInlines = fmap (MetaInlines . B.toList) <$> inlinesTillNewline
|
||||
|
||||
metaKey :: OrgParser String
|
||||
metaKey = map toLower <$> many1 (noneOf ": \n\r")
|
||||
<* char ':'
|
||||
<* skipSpaces
|
||||
|
||||
metaValue :: String -> OrgParser (F MetaValue)
|
||||
metaValue key = do
|
||||
case key of
|
||||
"author" -> metaInlines
|
||||
"title" -> metaInlines
|
||||
"date" -> metaInlines
|
||||
_ -> metaString
|
||||
|
||||
metaInlines :: OrgParser (F MetaValue)
|
||||
metaInlines = fmap (MetaInlines . B.toList) <$> inlinesTillNewline
|
||||
|
||||
metaString :: OrgParser (F MetaValue)
|
||||
metaString = return . MetaString <$> anyLine
|
||||
|
||||
|
||||
--
|
||||
-- export options
|
||||
--
|
||||
optionLine :: OrgParser ()
|
||||
optionLine = try $ do
|
||||
key <- metaKey
|
||||
|
|
|
@ -478,8 +478,8 @@ tests =
|
|||
|
||||
, "Description" =:
|
||||
"#+DESCRIPTION: Explanatory text" =?>
|
||||
let description = toList . spcSep $ [ "Explanatory", "text" ]
|
||||
meta = setMeta "description" (MetaInlines description) $ nullMeta
|
||||
let description = "Explanatory text"
|
||||
meta = setMeta "description" (MetaString description) $ nullMeta
|
||||
in Pandoc meta mempty
|
||||
|
||||
, "Properties drawer" =:
|
||||
|
|
Loading…
Reference in a new issue