Skip to content

Commit 197e2d9

Browse files
committed
Support for pandoc 3 (#58)
1 parent 408007d commit 197e2d9

File tree

9 files changed

+37
-80
lines changed

9 files changed

+37
-80
lines changed

CHANGELOG.md

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,10 @@
22

33
pandoc-plot uses [Semantic Versioning](http://semver.org/spec/v2.0.0.html)
44

5+
## Release 1.6.0
6+
7+
* Support for pandoc 3. Support for older pandoc version has also been dropped (pandoc 2.19 and earlier).
8+
59
## Release 1.5.5
610

711
* Fixed an issue where there was a race condition when rendering multiple identical figures (#53).

executable/Main.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -262,7 +262,7 @@ showFullVersion = do
262262
putStrLn $
263263
mconcat
264264
[ "Compiled with pandoc ",
265-
unpack pandocVersion,
265+
V.showVersion pandocVersion,
266266
" and pandoc-types ",
267267
V.showVersion pandocTypesVersion,
268268
" using GHC ",

pandoc-plot.cabal

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
cabal-version: 2.2
22
name: pandoc-plot
3-
version: 1.5.5
3+
version: 1.6.0
44
synopsis: A Pandoc filter to include figures generated from code blocks using your plotting toolkit of choice.
55
description: A Pandoc filter to include figures generated from code blocks.
66
Keep the document and code in the same location. Output is
@@ -99,8 +99,8 @@ library
9999
, directory >= 1.2.7 && < 2
100100
, filepath >= 1.4 && < 2
101101
, hashable >= 1 && < 2
102-
, pandoc >= 2.11 && < 3
103-
, pandoc-types >= 1.22 && < 1.23
102+
, pandoc >= 3 && < 4
103+
, pandoc-types >= 1.23 && < 1.24
104104
, lifted-async >= 0.10 && < 1
105105
, lifted-base >= 0.2 && < 1
106106
, shakespeare >= 2.0 && < 3

src/Text/Pandoc/Filter/Plot.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -219,7 +219,7 @@ makeEither block =
219219
parseFigureSpec block
220220
>>= \case
221221
NotAFigure -> return $ Right block
222-
Figure fs -> runScriptIfNecessary fs >>= handleResult fs
222+
PFigure fs -> runScriptIfNecessary fs >>= handleResult fs
223223
MissingToolkit tk -> return $ Left $ ToolkitNotInstalledError tk
224224
UnsupportedSaveFormat tk sv -> return $ Left $ IncompatibleSaveFormatError sv tk
225225
where

src/Text/Pandoc/Filter/Plot/Clean.hs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -31,6 +31,7 @@ import System.FilePath (takeExtension)
3131
import Text.Pandoc.Class (runIO)
3232
import Text.Pandoc.Definition (Block, Pandoc)
3333
import Text.Pandoc.Error (handleError)
34+
import Text.Pandoc.Format (FlavoredFormat(..))
3435
import Text.Pandoc.Filter.Plot.Monad
3536
import Text.Pandoc.Filter.Plot.Parse
3637
import qualified Text.Pandoc.Options as P
@@ -61,10 +62,10 @@ outputDirs ::
6162
Walkable Block b =>
6263
b ->
6364
PlotM [FilePath]
64-
outputDirs = fmap (catMaybes . nub) . sequence . query (\b -> [hasDirectory <$> parseFigureSpec b])
65+
outputDirs = fmap (nub . catMaybes) . sequence . query (\b -> [hasDirectory <$> parseFigureSpec b])
6566
where
6667
hasDirectory :: ParseFigureResult -> Maybe FilePath
67-
hasDirectory (Figure fs) = Just $ directory fs
68+
hasDirectory (PFigure fs) = Just $ directory fs
6869
hasDirectory _ = Nothing
6970

7071
-- | PlotM version of @cleanOutputDirs@
@@ -91,7 +92,7 @@ readDoc fp =
9192
=<< runIO
9293
( do
9394
let fmt = fromMaybe mempty (formatFromFilePath fp)
94-
(reader, exts) <- P.getReader fmt
95+
(reader, exts) <- P.getReader $ FlavoredFormat fmt mempty
9596
let readerOpts = def {P.readerExtensions = exts}
9697
case reader of
9798
P.TextReader fct -> do

src/Text/Pandoc/Filter/Plot/Embed.hs

Lines changed: 6 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -30,15 +30,14 @@ import Text.HTML.TagSoup
3030
(~/=),
3131
(~==),
3232
)
33-
import Text.Pandoc.Builder
33+
import Text.Pandoc.Builder as Builder
3434
( Inlines,
3535
fromList,
36-
imageWith,
36+
simpleFigureWith,
3737
link,
38-
para,
3938
str,
4039
toList,
41-
)
40+
)
4241
import Text.Pandoc.Class (runPure)
4342
import Text.Pandoc.Definition (Attr, Block (..), Format, Pandoc (..))
4443
import Text.Pandoc.Error (handleError)
@@ -63,10 +62,9 @@ toFigure fmt spec = do
6362
sourceLabel <- asksConfig sourceCodeLabel -- Allow the possibility for non-english labels
6463
let srcLink = link scp mempty (str sourceLabel)
6564
attrs' = blockAttrs spec
66-
withSource' = withSource spec
6765
captionText = fromList $ fromMaybe mempty (captionReader fmt $ caption spec)
6866
captionLinks = mconcat [" (", srcLink, ")"]
69-
caption' = if withSource' then captionText <> captionLinks else captionText
67+
caption' = if withSource spec then captionText <> captionLinks else captionText
7068
builder attrs' target caption'
7169
where
7270
builder = case saveFormat spec of
@@ -80,14 +78,8 @@ figure ::
8078
Inlines ->
8179
PlotM Block
8280
figure as fp caption' =
83-
return . head . toList . para $
84-
imageWith as (pack fp) title caption'
85-
where
86-
-- To render images as figures with captions, the target title
87-
-- must be "fig:"
88-
-- Janky? yes
89-
-- In case there is no caption, make this an image instead of a figure
90-
title = if caption' /= mempty then "fig:" else mempty
81+
return . head . toList $
82+
simpleFigureWith as caption' (pack fp) mempty
9183

9284
-- TODO: also add the case where SVG plots can be
9385
-- embedded in HTML output

src/Text/Pandoc/Filter/Plot/Parse.hs

Lines changed: 5 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -39,6 +39,7 @@ import Text.Pandoc.Definition
3939
Inline,
4040
Pandoc (..),
4141
)
42+
import Text.Pandoc.Format (parseFlavoredFormat)
4243
import Text.Pandoc.Filter.Plot.Monad
4344
import Text.Pandoc.Filter.Plot.Renderers
4445
import Text.Pandoc.Options (ReaderOptions (..))
@@ -51,7 +52,7 @@ data ParseFigureResult
5152
-- | The block is not meant to become a figure
5253
= NotAFigure
5354
-- | The block is meant to become a figure
54-
| Figure FigureSpec
55+
| PFigure FigureSpec
5556
-- | The block is meant to become a figure, but the plotting toolkit is missing
5657
| MissingToolkit Toolkit
5758
-- | The block is meant to become a figure, but the figure format is incompatible
@@ -126,7 +127,7 @@ parseFigureSpec block@(CodeBlock (id', classes, attrs) _) = do
126127
in err msg
127128

128129
-- Ensure that the save format makes sense given the final conversion format, if known
129-
return $ Figure (FigureSpec {..})
130+
return $ PFigure (FigureSpec {..})
130131
-- Base case: block is not a CodeBlock
131132
parseFigureSpec _ = return NotAFigure
132133

@@ -162,7 +163,8 @@ plotToolkit _ = Nothing
162163
captionReader :: Format -> Text -> Maybe [Inline]
163164
captionReader (Format f) t = either (const Nothing) (Just . extractFromBlocks) $
164165
runPure $ do
165-
(reader, exts) <- getReader f
166+
fmt <- parseFlavoredFormat f
167+
(reader, exts) <- getReader fmt
166168
let readerOpts = def {readerExtensions = exts}
167169
-- Assuming no ByteString readers...
168170
case reader of

tests/Common.hs

Lines changed: 12 additions & 53 deletions
Original file line numberDiff line numberDiff line change
@@ -179,20 +179,16 @@ testWithSource tk =
179179
addDirectory tempDir $
180180
addCaption expected $
181181
codeBlock tk (trivialContent tk)
182-
blockNoSource <- runPlotM Nothing defaultTestConfig $ make noSource
182+
blockNoSource <- runPlotM Nothing defaultTestConfig $ make noSource
183183
blockWithSource <- runPlotM Nothing defaultTestConfig $ make withSource
184184

185185
-- In the case where source=false, the caption is used verbatim.
186186
-- Otherwise, links will be appended to the caption; hence, the caption
187187
-- is no longer equal to the initial value
188-
assertEqual "" (B.toList $ fromString expected) (extractCaption blockNoSource)
189-
assertNotEqual "" (B.toList $ fromString expected) (extractCaption blockWithSource)
188+
assertEqual "" [B.Plain $ B.toList (fromString expected)] (extractCaption blockNoSource)
189+
assertNotEqual "" [B.Plain $ B.toList (fromString expected)] (extractCaption blockWithSource)
190190
where
191-
extractCaption (B.Para blocks) = extractImageCaption . head $ blocks
192-
extractCaption _ = mempty
193-
194-
extractImageCaption (Image _ c _) = c
195-
extractImageCaption _ = mempty
191+
extractCaption (B.Figure _ (Caption _ caption) _) = caption
196192

197193
-------------------------------------------------------------------------------
198194
-- Test that it is possible to change the source code label in captions
@@ -212,17 +208,12 @@ testSourceLabel tk =
212208
codeBlock tk (trivialContent tk)
213209
blockWithSource <- runPlotM Nothing defaultTestConfig {sourceCodeLabel = "Test label"} $ make withSource
214210

215-
-- The caption will look like [Space, Str "(", Link ... ]. Hence, we skip the first elements with (!!)
216-
let resultCaption = linkLabel $ (!! 2) . B.toList $ extractCaption blockWithSource
217-
assertEqual "" (B.str "Test label") resultCaption
211+
let [Plain [Space, _, B.Link _ ils _, _]] = extractCaption blockWithSource
212+
assertEqual "" (B.toList $ B.str "Test label") ils
218213
where
219-
extractCaption (B.Para blocks) = extractImageCaption . head $ blocks
220-
extractCaption _ = mempty
221-
222-
extractImageCaption (Image _ c _) = B.fromList c
223-
extractImageCaption _ = mempty
214+
extractCaption (B.Figure _ (Caption _ caption) _) = caption
224215

225-
linkLabel (B.Link _ ils _) = B.fromList ils
216+
linkLabel (B.Plain [B.Link _ ils _]) = B.fromList ils
226217
linkLabel _ = mempty
227218

228219
-------------------------------------------------------------------------------
@@ -276,7 +267,7 @@ testMarkdownFormattingCaption1 tk =
276267

277268
-- Note that this test is fragile, in the sense that the expected result must be carefully
278269
-- constructed
279-
let expected = [B.Strong [B.Str "caption"]]
270+
let expected = [B.Plain [B.Strong [B.Str "caption"]]]
280271
cb =
281272
addDirectory tempDir $
282273
addCaption "**caption**" $
@@ -285,11 +276,7 @@ testMarkdownFormattingCaption1 tk =
285276
result <- runPlotM Nothing (defaultTestConfig {captionFormat = fmt}) $ make cb
286277
assertIsInfix expected (extractCaption result)
287278
where
288-
extractCaption (B.Para blocks) = extractImageCaption . head $ blocks
289-
extractCaption _ = mempty
290-
291-
extractImageCaption (Image _ c _) = c
292-
extractImageCaption _ = mempty
279+
extractCaption (B.Figure _ (Caption _ caption) _) = caption
293280

294281
-------------------------------------------------------------------------------
295282
-- Test that Markdown bold formatting in captions is correctly rendered
@@ -302,7 +289,7 @@ testMarkdownFormattingCaption2 tk =
302289

303290
-- Note that this test is fragile, in the sense that the expected result must be carefully
304291
-- constructed
305-
let expected = [Link ("", [], []) [Str "title"] ("https://google.com", "")]
292+
let expected = [B.Plain [Link ("", [], []) [Str "title"] ("https://google.com", "")]]
306293
cb =
307294
addDirectory tempDir $
308295
addCaption "[title](https://google.com)" $
@@ -311,35 +298,7 @@ testMarkdownFormattingCaption2 tk =
311298
result <- runPlotM Nothing (defaultTestConfig {captionFormat = fmt}) $ make cb
312299
assertIsInfix expected (extractCaption result)
313300
where
314-
extractCaption (B.Para blocks) = extractImageCaption . head $ blocks
315-
extractCaption _ = mempty
316-
317-
extractImageCaption (Image _ c _) = c
318-
extractImageCaption _ = mempty
319-
320-
-------------------------------------------------------------------------------
321-
-- Test that Markdown bold formatting in captions is correctly rendered
322-
testFigureWithoutCaption :: Toolkit -> TestTree
323-
testFigureWithoutCaption tk =
324-
testCase "appropriately build an image if no caption" $ do
325-
let postfix = unpack . cls $ tk
326-
tempDir <- (</> "test-image-if-no-caption-" <> postfix) <$> getTemporaryDirectory
327-
ensureDirectoryExistsAndEmpty tempDir
328-
329-
-- Note that this test is fragile, in the sense that the expected result must be carefully
330-
-- constructed
331-
let cb =
332-
addDirectory tempDir $ codeBlock tk (trivialContent tk)
333-
fmt = B.Format "markdown"
334-
result <- runPlotM Nothing (defaultTestConfig {captionFormat = fmt}) $ make cb
335-
assertEqual "" (Just mempty) (extractTitle result)
336-
where
337-
extractTitle (B.Para blocks) = extractImageCaption . head $ blocks
338-
extractTitle _ = Nothing
339-
340-
extractImageCaption (Image _ _ (_, title)) = Just title
341-
extractImageCaption _ = Nothing
342-
301+
extractCaption (B.Figure _ (Caption _ caption) _) = caption
343302

344303
-------------------------------------------------------------------------------
345304
-- Test that cleanOutpuDirs correctly cleans the output directory specified in a block.

tests/Main.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -58,7 +58,6 @@ toolkitSuite tk =
5858
testOverrideConfiguration,
5959
testMarkdownFormattingCaption1,
6060
testMarkdownFormattingCaption2,
61-
testFigureWithoutCaption,
6261
testCleanOutputDirs,
6362
testChecksFail
6463
]
@@ -109,7 +108,7 @@ testCaptionReader =
109108
-- Note that this test is fragile, in the sense that the expected result must be carefully
110109
-- constructed
111110
let caption = "Here is a [link](https://www.google.com) in a caption."
112-
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."]
111+
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."]
113112
fmt = B.Format "markdown+tex_math_dollars"
114113
parsed = captionReader fmt caption
115114

0 commit comments

Comments
 (0)