Reorder block arguments parsing code
Group code used to parse block arguments together in one place. This seems better than having part of the code mixed between unrelated parsing state changing functions.
This commit is contained in:
parent
d5f367d04b
commit
40fb102417
1 changed files with 18 additions and 13 deletions
|
@ -172,19 +172,6 @@ recordAnchorId :: String -> OrgParser ()
|
|||
recordAnchorId i = updateState $ \s ->
|
||||
s{ orgStateAnchorIds = i : (orgStateAnchorIds s) }
|
||||
|
||||
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
|
||||
|
||||
resetBlockAttributes :: OrgParser ()
|
||||
resetBlockAttributes = updateState $ \s ->
|
||||
s{ orgStateBlockAttributes = orgStateBlockAttributes def }
|
||||
|
||||
updateLastForbiddenCharPos :: OrgParser ()
|
||||
updateLastForbiddenCharPos = getPosition >>= \p ->
|
||||
updateState $ \s -> s{ orgStateLastForbiddenCharPos = Just p}
|
||||
|
@ -312,9 +299,18 @@ block = choice [ mempty <$ blanklines
|
|||
, paraOrPlain
|
||||
] <?> "block"
|
||||
|
||||
--
|
||||
-- Block Attributes
|
||||
--
|
||||
|
||||
-- | Parse optional block attributes (like #+TITLE or #+NAME)
|
||||
optionalAttributes :: OrgParser (F Blocks) -> OrgParser (F Blocks)
|
||||
optionalAttributes parser = try $
|
||||
resetBlockAttributes *> parseBlockAttributes *> parser
|
||||
where
|
||||
resetBlockAttributes :: OrgParser ()
|
||||
resetBlockAttributes = updateState $ \s ->
|
||||
s{ orgStateBlockAttributes = orgStateBlockAttributes def }
|
||||
|
||||
parseBlockAttributes :: OrgParser ()
|
||||
parseBlockAttributes = do
|
||||
|
@ -339,6 +335,15 @@ lookupInlinesAttr attr = try $ do
|
|||
(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
|
||||
|
||||
|
||||
--
|
||||
-- Org Blocks (#+BEGIN_... / #+END_...)
|
||||
|
|
Loading…
Reference in a new issue