Skip to content

Commit

Permalink
Fixed a test case that depended on caption structure
Browse files Browse the repository at this point in the history
  • Loading branch information
LaurentRDC committed Sep 27, 2024
1 parent a125b56 commit 215dbaf
Show file tree
Hide file tree
Showing 4 changed files with 28 additions and 14 deletions.
13 changes: 10 additions & 3 deletions src/Text/Pandoc/Filter/Plot/Embed.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,6 @@ module Text.Pandoc.Filter.Plot.Embed
where

import Data.Default (def)
import Data.Maybe (fromMaybe)
import Data.Text (Text, pack)
import qualified Data.Text.IO as T
import Text.HTML.TagSoup
Expand Down Expand Up @@ -63,11 +62,19 @@ toFigure fmt spec = do
target <- figurePath spec
scp <- pack <$> sourceCodePath spec
sourceLabel <- asksConfig sourceCodeLabel -- Allow the possibility for non-english labels

cap <- case (captionReader fmt $ caption spec) of
Left exc -> do
err $ "Unable to parse caption: " <> (pack $ show exc)
pure mempty
Right c -> do
debug $ "Parsed caption: " <> (pack $ show c)
pure $ fromList c

let srcLink = link scp mempty (str sourceLabel)
attrs' = blockAttrs spec
captionText = fromList $ fromMaybe mempty (captionReader fmt $ caption spec)
captionLinks = mconcat [" (", srcLink, ")"]
caption' = if withSource spec then captionText <> captionLinks else captionText
caption' = if withSource spec then cap <> captionLinks else cap
builder attrs' target caption'
where
builder = case saveFormat spec of
Expand Down
5 changes: 3 additions & 2 deletions src/Text/Pandoc/Filter/Plot/Parse.hs
Original file line number Diff line number Diff line change
Expand Up @@ -44,6 +44,7 @@ import Text.Pandoc.Filter.Plot.Renderers
import Text.Pandoc.Format (parseFlavoredFormat)
import Text.Pandoc.Options (ReaderOptions (..))
import Text.Pandoc.Readers (Reader (..), getReader)
import Text.Pandoc (PandocError)

tshow :: (Show a) => a -> Text
tshow = pack . show
Expand Down Expand Up @@ -162,8 +163,8 @@ plotToolkit (CodeBlock (_, classes, _) _) =
plotToolkit _ = Nothing

-- | Reader a caption, based on input document format
captionReader :: Format -> Text -> Maybe [Inline]
captionReader (Format f) t = either (const Nothing) (Just . extractFromBlocks) $
captionReader :: Format -> Text -> Either PandocError [Inline]
captionReader (Format f) t = fmap extractFromBlocks $
runPure $ do
fmt <- parseFlavoredFormat f
(reader, exts) <- getReader fmt
Expand Down
18 changes: 11 additions & 7 deletions tests/Common.hs
Original file line number Diff line number Diff line change
Expand Up @@ -380,12 +380,13 @@ testAttributesPreservedOnFigure tk =
-- constructed
let expectedAttrs = ("hello", [cls tk], [("key1", "val1"), ("key2", "val2")])
cb =
setAttrs expectedAttrs $
addDirectory tempDir $
addCaption "[title](https://google.com)" $
codeBlock tk (trivialContent tk)
addCaption "This is a caption [title](https://google.com)" $
setAttrs expectedAttrs $
codeBlock tk (trivialContent tk)
fmt = B.Format "markdown"
Figure (id', _, keyvals) _ _ <-

block <-
runPlotM
Nothing
( defaultTestConfig
Expand All @@ -394,9 +395,12 @@ testAttributesPreservedOnFigure tk =
}
)
$ make cb
let (expectedId, _, expectedKeyVals) = expectedAttrs
assertEqual "identifier" expectedId id'
assertEqual "key-value pairs" expectedKeyVals keyvals
case block of
Figure (id', _, keyvals) _ _ -> do
let (expectedId, _, expectedKeyVals) = expectedAttrs
assertEqual "identifier" expectedId id'
assertEqual "key-value pairs" expectedKeyVals keyvals
other -> assertFailure $ "Unexpected block: " <> show block
where
extractCaption (B.Figure _ (Caption _ caption) _) = caption

Expand Down
6 changes: 4 additions & 2 deletions tests/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -109,11 +109,13 @@ testCaptionReader =
-- Note that this test is fragile, in the sense that the expected result must be carefully
-- constructed
let caption = "Here is a [link](https://www.google.com) in a caption."
expected = Just [Str "Here", Space, Str "is", Space, Str "a", Space, Link ("", [], []) [Str "link"] ("https://www.google.com", ""), Space, Str "in", Space, Str "a", Space, Str "caption."]
expected = [Str "Here", Space, Str "is", Space, Str "a", Space, Link ("", [], []) [Str "link"] ("https://www.google.com", ""), Space, Str "in", Space, Str "a", Space, Str "caption."]
fmt = B.Format "markdown+tex_math_dollars"
parsed = captionReader fmt caption

assertEqual "" expected parsed
case parsed of
Left exc -> assertFailure $ show exc
Right result -> assertEqual "" expected result

testHtmlBodyEmbedding :: TestTree
testHtmlBodyEmbedding =
Expand Down

0 comments on commit 215dbaf

Please sign in to comment.