aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorAlbert Krewinkel <[email protected]>2025-10-18 11:37:43 +0200
committerAlbert Krewinkel <[email protected]>2025-10-18 17:34:38 +0200
commit941b5662d794035f7f400abd41e9d63d3213e95d (patch)
tree69de506a91bcb11ef3812001b963d04755db828f /src
parent36cea7c978d1ccbf1b913af33df2d492ef5d1d61 (diff)
Org reader: add support for dynamic blocks.
Diffstat (limited to 'src')
-rw-r--r--src/Text/Pandoc/Readers/Org/Blocks.hs33
1 files changed, 27 insertions, 6 deletions
diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs
index bc71b1d72..3a082dc2c 100644
--- a/src/Text/Pandoc/Readers/Org/Blocks.hs
+++ b/src/Text/Pandoc/Readers/Org/Blocks.hs
@@ -73,6 +73,7 @@ blocks = mconcat <$> manyTill block (void (lookAhead headerStart) <|> eof)
block :: PandocMonad m => OrgParser m (F Blocks)
block = choice [ mempty <$ blanklines
, table
+ , dynamicBlock
, orgBlock
, figure
, example
@@ -115,7 +116,7 @@ attrFromBlockAttributes BlockAttributes{..} =
stringyMetaAttribute :: Monad m => OrgParser m (Text, Text)
stringyMetaAttribute = try $ do
- metaLineStart *> notFollowedBy (stringAnyCase "begin_")
+ metaLineStart *> notFollowedBy (stringAnyCase "begin" *> oneOf ":_")
attrName <- T.toLower <$> many1TillChar nonspaceChar (char ':')
skipSpaces
attrValue <- anyLine <|> ("" <$ newline)
@@ -244,8 +245,13 @@ parseBlockLines f blockType = ignHeaders *> (f <$> parsedBlockContent)
-- | Read the raw string content of a block
rawBlockContent :: Monad m => Text -> OrgParser m Text
-rawBlockContent blockType = try $ do
- blkLines <- manyTill rawLine blockEnder
+rawBlockContent blockType = rawBlockContent' $
+ stringAnyCase ("#+end_" <> blockType)
+
+-- | Read the raw string content of a block
+rawBlockContent' :: Monad m => OrgParser m Text -> OrgParser m Text
+rawBlockContent' blockEnder = try $ do
+ blkLines <- manyTill rawLine (try $ skipSpaces <* blockEnder)
tabStop <- getOption readerTabStop
trimP <- orgStateTrimLeadBlkIndent <$> getState
-- split lines into indentation/contents tuples
@@ -265,9 +271,6 @@ rawBlockContent blockType = try $ do
rawLine :: Monad m => OrgParser m Text
rawLine = try $ ("" <$ blankline) <|> anyLine
- blockEnder :: Monad m => OrgParser m ()
- blockEnder = try $ skipSpaces <* stringAnyCase ("#+end_" <> blockType)
-
commaEscaped suff = case T.uncons suff of
Just (',', cs)
| "*" <- T.take 1 cs -> cs
@@ -440,6 +443,24 @@ orgParamValue = try $
--
+-- Dynamic block (#+begin: ... #+end:)
+--
+
+-- | Parses a Dynamic Block, i.e., a block delimited by #+BEGIN: and
+-- #+END:.
+dynamicBlock :: PandocMonad m => OrgParser m (F Blocks)
+dynamicBlock = try $ do
+ metaLineStart *> stringAnyCase "begin:" *> spaces
+ blockname <- optionMaybe orgArgWord
+ ignHeaders
+ contents <- do
+ raw <- rawBlockContent' $ metaLineStart *> stringAnyCase "end:"
+ parseFromString blocks (raw <> "\n")
+ let attr = ("", maybe [] (:[]) blockname, [])
+ return $ B.divWith attr <$> contents
+
+
+--
-- Drawers
--