Org reader: refactor block attribute handling

A parser state attribute was used to keep track of block attributes
defined in meta-lines.  Global state is undesirable, so block attributes
are no longer saved as part of the parser state.  Old functions and the
respective part of the parser state are removed.
This commit is contained in:
Albert Krewinkel 2016-05-12 23:11:26 +02:00
parent dd649f19a9
commit 1dda535378
2 changed files with 76 additions and 82 deletions

View file

@ -49,10 +49,10 @@ import qualified Text.TeXMath.Readers.MathML.EntityMap as MathMLEntityMap
import Control.Arrow (first) import Control.Arrow (first)
import Control.Monad (foldM, guard, mplus, mzero, when) import Control.Monad (foldM, guard, mplus, mzero, when)
import Control.Monad.Reader ( Reader, runReader ) import Control.Monad.Reader ( Reader, runReader )
import Data.Char (isAlphaNum, isSpace, toLower) import Data.Char (isAlphaNum, isSpace, toLower, toUpper)
import Data.List (intersperse, isPrefixOf, isSuffixOf) import Data.List ( foldl', intersperse, isPrefixOf, isSuffixOf )
import qualified Data.Map as M import qualified Data.Map as M
import Data.Maybe (fromMaybe, isJust) import Data.Maybe ( fromMaybe, isNothing )
import Network.HTTP (urlEncode) import Network.HTTP (urlEncode)
@ -273,11 +273,9 @@ parseBlocks = mconcat <$> manyTill block eof
block :: OrgParser (F Blocks) block :: OrgParser (F Blocks)
block = choice [ mempty <$ blanklines block = choice [ mempty <$ blanklines
, optionalAttributes $ choice , table
[ orgBlock , orgBlock
, figure , figure
, table
]
, example , example
, drawer , drawer
, specialLine , specialLine
@ -289,50 +287,53 @@ block = choice [ mempty <$ blanklines
, paraOrPlain , paraOrPlain
] <?> "block" ] <?> "block"
-- --
-- Block Attributes -- Block Attributes
-- --
-- | Parse optional block attributes (like #+TITLE or #+NAME) -- | Attributes that may be added to figures (like a name or caption).
optionalAttributes :: OrgParser (F Blocks) -> OrgParser (F Blocks) data BlockAttributes = BlockAttributes
optionalAttributes parser = try $ { blockAttrName :: Maybe String
resetBlockAttributes *> parseBlockAttributes *> parser , blockAttrCaption :: Maybe (F Inlines)
}
stringyMetaAttribute :: (String -> Bool) -> OrgParser (String, String)
stringyMetaAttribute attrCheck = try $ do
metaLineStart
attrName <- map toUpper <$> many1Till nonspaceChar (char ':')
guard $ attrCheck attrName
skipSpaces
attrValue <- manyTill anyChar newline
return (attrName, attrValue)
blockAttributes :: OrgParser BlockAttributes
blockAttributes = try $ do
kv <- many (stringyMetaAttribute attrCheck)
let caption = foldl' (appendValues "CAPTION") Nothing kv
let name = lookup "NAME" kv
caption' <- maybe (return Nothing)
(fmap Just . parseFromString parseInlines)
caption
return $ BlockAttributes
{ blockAttrName = name
, blockAttrCaption = caption'
}
where where
resetBlockAttributes :: OrgParser () attrCheck :: String -> Bool
resetBlockAttributes = updateState $ \s -> attrCheck attr =
s{ orgStateBlockAttributes = orgStateBlockAttributes def } case attr of
"NAME" -> True
"CAPTION" -> True
_ -> False
parseBlockAttributes :: OrgParser () appendValues :: String -> Maybe String -> (String, String) -> Maybe String
parseBlockAttributes = do appendValues attrName accValue (key, value) =
attrs <- many attribute if key /= attrName
mapM_ (uncurry parseAndAddAttribute) attrs then accValue
where else case accValue of
attribute :: OrgParser (String, String) Just acc -> Just $ acc ++ ' ':value
attribute = try $ do Nothing -> Just value
key <- metaLineStart *> many1Till nonspaceChar (char ':')
val <- skipSpaces *> anyLine
return (map toLower key, val)
parseAndAddAttribute :: String -> String -> OrgParser ()
parseAndAddAttribute key value = do
let key' = map toLower key
() <$ addBlockAttribute key' value
lookupInlinesAttr :: String -> OrgParser (Maybe (F Inlines))
lookupInlinesAttr attr = try $ do
val <- lookupBlockAttribute attr
maybe (return Nothing)
(fmap Just . parseFromString parseInlines)
val
addBlockAttribute :: String -> String -> OrgParser ()
addBlockAttribute key val = updateState $ \s ->
let attrs = orgStateBlockAttributes s
in s{ orgStateBlockAttributes = M.insert key val attrs }
lookupBlockAttribute :: String -> OrgParser (Maybe String)
lookupBlockAttribute key =
M.lookup key . orgStateBlockAttributes <$> getState
-- --
@ -346,6 +347,7 @@ updateIndent (_, blkType) indent = (indent, blkType)
orgBlock :: OrgParser (F Blocks) orgBlock :: OrgParser (F Blocks)
orgBlock = try $ do orgBlock = try $ do
blockAttrs <- blockAttributes
blockProp@(_, blkType) <- blockHeaderStart blockProp@(_, blkType) <- blockHeaderStart
($ blockProp) $ ($ blockProp) $
case blkType of case blkType of
@ -356,7 +358,7 @@ orgBlock = try $ do
"example" -> withRaw' (return . exampleCode) "example" -> withRaw' (return . exampleCode)
"quote" -> withParsed (fmap B.blockQuote) "quote" -> withParsed (fmap B.blockQuote)
"verse" -> verseBlock "verse" -> verseBlock
"src" -> codeBlock "src" -> codeBlock blockAttrs
_ -> withParsed (fmap $ divWithClass blkType) _ -> withParsed (fmap $ divWithClass blkType)
blockHeaderStart :: OrgParser (Int, String) blockHeaderStart :: OrgParser (Int, String)
@ -410,20 +412,20 @@ followingResultsBlock =
*> blankline *> blankline
*> block) *> block)
codeBlock :: BlockProperties -> OrgParser (F Blocks) codeBlock :: BlockAttributes -> BlockProperties -> OrgParser (F Blocks)
codeBlock blkProp = do codeBlock blockAttrs blkProp = do
skipSpaces skipSpaces
(classes, kv) <- codeHeaderArgs <|> (mempty <$ ignHeaders) (classes, kv) <- codeHeaderArgs <|> (mempty <$ ignHeaders)
id' <- fromMaybe "" <$> lookupBlockAttribute "name"
leadingIndent <- lookAhead indentation leadingIndent <- lookAhead indentation
content <- rawBlockContent (updateIndent blkProp leadingIndent) content <- rawBlockContent (updateIndent blkProp leadingIndent)
resultsContent <- followingResultsBlock resultsContent <- followingResultsBlock
let id' = fromMaybe mempty $ blockAttrName blockAttrs
let includeCode = exportsCode kv let includeCode = exportsCode kv
let includeResults = exportsResults kv let includeResults = exportsResults kv
let codeBlck = B.codeBlockWith ( id', classes, kv ) content let codeBlck = B.codeBlockWith ( id', classes, kv ) content
labelledBlck <- maybe (pure codeBlck) let labelledBlck = maybe (pure codeBlck)
(labelDiv codeBlck) (labelDiv codeBlck)
<$> lookupInlinesAttr "caption" (blockAttrCaption blockAttrs)
let resultBlck = fromMaybe mempty resultsContent let resultBlck = fromMaybe mempty resultsContent
return $ (if includeCode then labelledBlck else mempty) return $ (if includeCode then labelledBlck else mempty)
<> (if includeResults then resultBlck else mempty) <> (if includeResults then resultBlck else mempty)
@ -579,47 +581,42 @@ drawerEnd = try $
-- Figures -- Figures
-- --
-- Figures (Image on a line by itself, preceded by name and/or caption)
-- | Figures (Image on a line by itself, preceded by name and/or caption)
figure :: OrgParser (F Blocks) figure :: OrgParser (F Blocks)
figure = try $ do figure = try $ do
(cap, nam) <- nameAndCaption figAttrs <- blockAttributes
src <- skipSpaces *> selfTarget <* skipSpaces <* P.newline src <- skipSpaces *> selfTarget <* skipSpaces <* P.newline
guard . not . isNothing . blockAttrCaption $ figAttrs
guard (isImageFilename src) guard (isImageFilename src)
return $ do let figName = fromMaybe mempty $ blockAttrName figAttrs
cap' <- cap let figCaption = fromMaybe mempty $ blockAttrCaption figAttrs
return $ B.para $ B.image src nam cap' return $ (B.para . B.image src (withFigPrefix figName) <$> figCaption)
where where
nameAndCaption =
do
maybeCap <- lookupInlinesAttr "caption"
maybeNam <- lookupBlockAttribute "name"
guard $ isJust maybeCap || isJust maybeNam
return ( fromMaybe mempty maybeCap
, withFigPrefix $ fromMaybe mempty maybeNam )
withFigPrefix cs = withFigPrefix cs =
if "fig:" `isPrefixOf` cs if "fig:" `isPrefixOf` cs
then cs then cs
else "fig:" ++ cs else "fig:" ++ cs
-- --
-- Comments, Options and Metadata -- Comments, Options and Metadata
--
specialLine :: OrgParser (F Blocks) specialLine :: OrgParser (F Blocks)
specialLine = fmap return . try $ metaLine <|> commentLine specialLine = fmap return . try $ metaLine <|> commentLine
metaLine :: OrgParser Blocks metaLine :: OrgParser Blocks
metaLine = try $ mempty metaLine = mempty <$ metaLineStart <* (optionLine <|> declarationLine)
<$ (metaLineStart *> (optionLine <|> declarationLine))
commentLine :: OrgParser Blocks
commentLine = try $ commentLineStart *> anyLine *> pure mempty
-- The order, in which blocks are tried, makes sure that we're not looking at -- The order, in which blocks are tried, makes sure that we're not looking at
-- the beginning of a block, so we don't need to check for it -- the beginning of a block, so we don't need to check for it
metaLineStart :: OrgParser String metaLineStart :: OrgParser ()
metaLineStart = try $ mappend <$> many spaceChar <*> string "#+" metaLineStart = try $ skipSpaces <* string "#+"
commentLineStart :: OrgParser String commentLine :: OrgParser Blocks
commentLineStart = try $ mappend <$> many spaceChar <*> string "# " commentLine = commentLineStart *> anyLine *> pure mempty
commentLineStart :: OrgParser ()
commentLineStart = try $ skipSpaces <* string "# "
declarationLine :: OrgParser () declarationLine :: OrgParser ()
declarationLine = try $ do declarationLine = try $ do
@ -738,11 +735,12 @@ data OrgTable = OrgTable
table :: OrgParser (F Blocks) table :: OrgParser (F Blocks)
table = try $ do table = try $ do
blockAttrs <- blockAttributes
lookAhead tableStart lookAhead tableStart
do do
rows <- tableRows rows <- tableRows
cptn <- fromMaybe (pure "") <$> lookupInlinesAttr "caption" let caption = fromMaybe (return mempty) $ blockAttrCaption blockAttrs
return $ (<$> cptn) . orgToPandocTable . normalizeTable =<< rowsToTable rows return $ (<$> caption) . orgToPandocTable . normalizeTable =<< rowsToTable rows
orgToPandocTable :: OrgTable orgToPandocTable :: OrgTable
-> Inlines -> Inlines

View file

@ -68,8 +68,6 @@ import Text.Pandoc.Parsing ( HasHeaderMap(..)
type OrgNoteRecord = (String, F Blocks) type OrgNoteRecord = (String, F Blocks)
-- | Table of footnotes -- | Table of footnotes
type OrgNoteTable = [OrgNoteRecord] type OrgNoteTable = [OrgNoteRecord]
-- | Map of org block attributes (e.g. LABEL, CAPTION, NAME, etc)
type OrgBlockAttributes = M.Map String String
-- | Map of functions for link transformations. The map key is refers to the -- | Map of functions for link transformations. The map key is refers to the
-- link-type, the corresponding function transforms the given link string. -- link-type, the corresponding function transforms the given link string.
type OrgLinkFormatters = M.Map String (String -> String) type OrgLinkFormatters = M.Map String (String -> String)
@ -84,7 +82,6 @@ data ExportSettings = ExportSettings
data OrgParserState = OrgParserState data OrgParserState = OrgParserState
{ orgStateOptions :: ReaderOptions { orgStateOptions :: ReaderOptions
, orgStateAnchorIds :: [String] , orgStateAnchorIds :: [String]
, orgStateBlockAttributes :: OrgBlockAttributes
, orgStateEmphasisCharStack :: [Char] , orgStateEmphasisCharStack :: [Char]
, orgStateEmphasisNewlines :: Maybe Int , orgStateEmphasisNewlines :: Maybe Int
, orgStateExportSettings :: ExportSettings , orgStateExportSettings :: ExportSettings
@ -140,7 +137,6 @@ defaultOrgParserState :: OrgParserState
defaultOrgParserState = OrgParserState defaultOrgParserState = OrgParserState
{ orgStateOptions = def { orgStateOptions = def
, orgStateAnchorIds = [] , orgStateAnchorIds = []
, orgStateBlockAttributes = M.empty
, orgStateEmphasisCharStack = [] , orgStateEmphasisCharStack = []
, orgStateEmphasisNewlines = Nothing , orgStateEmphasisNewlines = Nothing
, orgStateExportSettings = def , orgStateExportSettings = def