aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorAlbert Krewinkel <[email protected]>2025-10-18 17:12:31 +0200
committerAlbert Krewinkel <[email protected]>2025-10-18 17:35:23 +0200
commit13a5b1a4df90813cb0e622fd7816ec633f2af9a6 (patch)
tree36debc2095ef9a33546e6dc54d410a101ac90497
parent941b5662d794035f7f400abd41e9d63d3213e95d (diff)
Org reader: parse parameter lists on unknown blocks.
The reader tries to parse the rest of the opening line of a block, e.g., `#+begin_myblock …`, as a parameters list. It first assumes that the parameters are in lisp-style (`:key value`), then alternatively tries to read python-style key-value pairs (`key=value`) and falls back to reading the entire remaining line as a single `parameter` attribute. This method is also applied to dynamic blocks. Closes: #11188
-rw-r--r--src/Text/Pandoc/Readers/Org/Blocks.hs29
-rw-r--r--test/command/11188.md80
2 files changed, 101 insertions, 8 deletions
diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs
index 3a082dc2c..e95874ca8 100644
--- a/src/Text/Pandoc/Readers/Org/Blocks.hs
+++ b/src/Text/Pandoc/Readers/Org/Blocks.hs
@@ -189,7 +189,7 @@ orgBlock = try $ do
"latex" -> rawBlockLines (return . B.rawBlock (T.toLower blkType))
"ascii" -> rawBlockLines (return . B.rawBlock (T.toLower blkType))
"example" -> exampleBlock blockAttrs
- "quote" -> parseBlockLines (fmap B.blockQuote)
+ "quote" -> \x -> ignHeaders *> parseBlockLines (fmap B.blockQuote) x
"verse" -> verseBlock
"src" -> codeBlock blockAttrs
"note" -> admonitionBlock "note" blockAttrs
@@ -201,9 +201,11 @@ orgBlock = try $ do
-- case-sensitive checks
case blkType of
"abstract" -> metadataBlock
- _ -> parseBlockLines $
- let (ident, classes, kv) = attrFromBlockAttributes blockAttrs
- in fmap $ B.divWith (ident, classes ++ [blkType], kv)
+ _ -> \bt -> do
+ params <- blockParameters
+ let (ident, classes, kv) = attrFromBlockAttributes blockAttrs
+ toDiv = (B.divWith (ident, classes ++ [blkType], kv <> params))
+ parseBlockLines (fmap toDiv) bt
where
blockHeaderStart :: Monad m => OrgParser m Text
blockHeaderStart = try $ do
@@ -215,7 +217,7 @@ orgBlock = try $ do
admonitionBlock :: PandocMonad m
=> Text -> BlockAttributes -> Text -> OrgParser m (F Blocks)
admonitionBlock blockType blockAttrs rawtext = do
- bls <- parseBlockLines id rawtext
+ bls <- ignHeaders *> parseBlockLines id rawtext
let id' = fromMaybe mempty $ blockAttrName blockAttrs
pure $ fmap
(B.divWith (id', [blockType], []) .
@@ -236,7 +238,7 @@ rawBlockLines :: Monad m => (Text -> F Blocks) -> Text -> OrgParser m (F Block
rawBlockLines f blockType = ignHeaders *> (f <$> rawBlockContent blockType)
parseBlockLines :: PandocMonad m => (F Blocks -> F Blocks) -> Text -> OrgParser m (F Blocks)
-parseBlockLines f blockType = ignHeaders *> (f <$> parsedBlockContent)
+parseBlockLines f blockType = (f <$> parsedBlockContent)
where
parsedBlockContent :: PandocMonad m => OrgParser m (F Blocks)
parsedBlockContent = try $ do
@@ -311,6 +313,7 @@ verseBlock blockType = try $ do
-- metadata under a key of the same name.
metadataBlock :: PandocMonad m => Text -> OrgParser m (F Blocks)
metadataBlock blockType = try $ do
+ ignHeaders
content <- parseBlockLines id blockType
meta' <- orgStateMeta <$> getState
updateState $ \st ->
@@ -452,13 +455,23 @@ dynamicBlock :: PandocMonad m => OrgParser m (F Blocks)
dynamicBlock = try $ do
metaLineStart *> stringAnyCase "begin:" *> spaces
blockname <- optionMaybe orgArgWord
- ignHeaders
+ blockArgs <- blockParameters
contents <- do
raw <- rawBlockContent' $ metaLineStart *> stringAnyCase "end:"
parseFromString blocks (raw <> "\n")
- let attr = ("", maybe [] (:[]) blockname, [])
+ let attr = ("", maybe [] (:[]) blockname, blockArgs)
return $ B.divWith attr <$> contents
+-- | Parse block arguments; in order, this tries to parse a Lisp-style
+-- argument list, a set of key-value pairs using /equals/, and as a
+-- fallback the whole line as a single /parameters/ argument.
+blockParameters :: PandocMonad m => OrgParser m [(Text, Text)]
+blockParameters = choice
+ [ try $ manyTill ((,) <$> orgArgKey <*> orgParamValue) newline
+ , try $ manyTill ((,) <$> (spaces *> orgArgWord <* char '=') <*> orgArgWord)
+ newline
+ , (\x -> [ ("parameters", x) | not (T.null x)]) <$> (skipSpaces *> anyLine)
+ ]
--
-- Drawers
diff --git a/test/command/11188.md b/test/command/11188.md
new file mode 100644
index 000000000..a982b2dff
--- /dev/null
+++ b/test/command/11188.md
@@ -0,0 +1,80 @@
+Parsing PARAMETERS of Org-mode blocks
+
+```
+% pandoc -f org --to=native
+#+attr_html: :width 10px
+#+BEGIN_myex :this that
+huhu
+#+END_myex
+^D
+[ Div
+ ( ""
+ , [ "myex" ]
+ , [ ( "width" , "10px" ) , ( "this" , "that" ) ]
+ )
+ [ Para [ Str "huhu" ] ]
+]
+```
+
+Python-style parameters are accepted, too.
+
+```
+% pandoc -f org --to=native
+#+BEGIN_myblock width=10px
+[[image.svg][logo]]
+#+END_myblock
+^D
+[ Div
+ ( "" , [ "myblock" ] , [ ( "width" , "10px" ) ] )
+ [ Para
+ [ Span
+ ( ""
+ , [ "spurious-link" ]
+ , [ ( "target" , "image.svg" ) ]
+ )
+ [ Emph [ Str "logo" ] ]
+ ]
+ ]
+]
+```
+
+The fallback is to put the remainder of the line into a `parameters`
+attribute.
+
+```
+% pandoc -f org --to=native
+#+BEGIN_myblock these are parameters in an unsupported format
+/OK/
+#+END_myblock
+^D
+[ Div
+ ( ""
+ , [ "myblock" ]
+ , [ ( "parameters"
+ , "these are parameters in an unsupported format"
+ )
+ ]
+ )
+ [ Para [ Emph [ Str "OK" ] ] ]
+]
+```
+
+Also works on dynamic blocks.
+
+```
+% pandoc -f org --to=markdown
+#+BEGIN: clocktable :scope subtree :maxlevel 3
+#+CAPTION: Clock summary at [2025-10-18 Sat 17:23]
+| Headline | Time |
+|--------------+--------|
+| *Total time* | *0:00* |
+#+END:
+^D
+::: {.clocktable scope="subtree" maxlevel="3"}
+ Headline Time
+ ---------------- ----------
+ **Total time** **0:00**
+
+ : Clock summary at \[2025-10-18 Sat 17:23\]
+:::
+```