aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Text/Pandoc/Readers/Org/Blocks.hs26
-rw-r--r--test/Tests/Readers/Org/Block/CodeBlock.hs6
2 files changed, 15 insertions, 17 deletions
diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs
index f2e8b1ab6..17e3ff986 100644
--- a/src/Text/Pandoc/Readers/Org/Blocks.hs
+++ b/src/Text/Pandoc/Readers/Org/Blocks.hs
@@ -294,24 +294,22 @@ verseBlock blockType = try $ do
codeBlock :: PandocMonad m => BlockAttributes -> Text -> OrgParser m (F Blocks)
codeBlock blockAttrs blockType = do
skipSpaces
- (classes, kv) <- codeHeaderArgs <|> (mempty <$ ignHeaders)
- content <- rawBlockContent blockType
- resultsContent <- option mempty babelResultsBlock
- let id' = fromMaybe mempty $ blockAttrName blockAttrs
- let codeBlck = B.codeBlockWith ( id', classes, kv ) content
- let labelledBlck = maybe (pure codeBlck)
- (labelDiv codeBlck)
- (blockAttrCaption blockAttrs)
+ (classes, kv) <- codeHeaderArgs <|> (mempty <$ ignHeaders)
+ content <- rawBlockContent blockType
+ resultsContent <- option mempty babelResultsBlock
+ let identifier = fromMaybe mempty $ blockAttrName blockAttrs
+ let codeBlk = B.codeBlockWith (identifier, classes, kv) content
+ let wrap = maybe pure addCaption (blockAttrCaption blockAttrs)
return $
- (if exportsCode kv then labelledBlck else mempty) <>
+ (if exportsCode kv then wrap codeBlk else mempty) <>
(if exportsResults kv then resultsContent else mempty)
where
- labelDiv :: Blocks -> F Inlines -> F Blocks
- labelDiv blk value =
- B.divWith nullAttr <$> (mappend <$> labelledBlock value <*> pure blk)
+ addCaption :: F Inlines -> Blocks -> F Blocks
+ addCaption caption blk = B.divWith ("", ["captioned-content"], [])
+ <$> (mkCaptionBlock caption <> pure blk)
- labelledBlock :: F Inlines -> F Blocks
- labelledBlock = fmap (B.plain . B.spanWith ("", ["label"], []))
+ mkCaptionBlock :: F Inlines -> F Blocks
+ mkCaptionBlock = fmap (B.divWith ("", ["caption"], []) . B.plain)
exportsResults :: [(Text, Text)] -> Bool
exportsResults = maybe False (`elem` ["results", "both"]) . lookup "exports"
diff --git a/test/Tests/Readers/Org/Block/CodeBlock.hs b/test/Tests/Readers/Org/Block/CodeBlock.hs
index adf6661ca..2648a6e1f 100644
--- a/test/Tests/Readers/Org/Block/CodeBlock.hs
+++ b/test/Tests/Readers/Org/Block/CodeBlock.hs
@@ -185,10 +185,10 @@ tests =
, "#+end_src"
] =?>
divWith
- nullAttr
+ ("", ["captioned-content"], [] )
(mappend
- (plain $ spanWith ("", ["label"], [])
- (spcSep [ "Functor", "laws", "in", "Haskell" ]))
+ (divWith ("", ["caption"], []) $
+ plain (spcSep [ "Functor", "laws", "in", "Haskell" ]))
(codeBlockWith ("functor-laws", ["haskell"], [])
(T.unlines [ "fmap id = id"
, "fmap (p . q) = (fmap p) . (fmap q)"