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 :: OrgParser ()
|
||||||
declarationLine = try $ do
|
declarationLine = try $ do
|
||||||
key <- metaKey
|
key <- map toLower <$> metaKey
|
||||||
value <- metaInlines
|
value <- metaValue key
|
||||||
updateState $ \st ->
|
updateState $ \st ->
|
||||||
let meta' = B.setMeta key <$> value <*> pure nullMeta
|
let meta' = B.setMeta key <$> value <*> pure nullMeta
|
||||||
in st { orgStateMeta = orgStateMeta st <> meta' }
|
in st { orgStateMeta = orgStateMeta st <> meta' }
|
||||||
|
|
||||||
metaInlines :: OrgParser (F MetaValue)
|
|
||||||
metaInlines = fmap (MetaInlines . B.toList) <$> inlinesTillNewline
|
|
||||||
|
|
||||||
metaKey :: OrgParser String
|
metaKey :: OrgParser String
|
||||||
metaKey = map toLower <$> many1 (noneOf ": \n\r")
|
metaKey = map toLower <$> many1 (noneOf ": \n\r")
|
||||||
<* char ':'
|
<* char ':'
|
||||||
<* skipSpaces
|
<* 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 :: OrgParser ()
|
||||||
optionLine = try $ do
|
optionLine = try $ do
|
||||||
key <- metaKey
|
key <- metaKey
|
||||||
|
|
|
@ -478,8 +478,8 @@ tests =
|
||||||
|
|
||||||
, "Description" =:
|
, "Description" =:
|
||||||
"#+DESCRIPTION: Explanatory text" =?>
|
"#+DESCRIPTION: Explanatory text" =?>
|
||||||
let description = toList . spcSep $ [ "Explanatory", "text" ]
|
let description = "Explanatory text"
|
||||||
meta = setMeta "description" (MetaInlines description) $ nullMeta
|
meta = setMeta "description" (MetaString description) $ nullMeta
|
||||||
in Pandoc meta mempty
|
in Pandoc meta mempty
|
||||||
|
|
||||||
, "Properties drawer" =:
|
, "Properties drawer" =:
|
||||||
|
|
Loading…
Reference in a new issue