Skip to content

Commit f0af92a

Browse files
authored
Merge pull request #47 from LaurentRDC/specifying-executable
Overhauled executable handling
2 parents f24a05d + 4d7e487 commit f0af92a

File tree

25 files changed

+292
-483
lines changed

25 files changed

+292
-483
lines changed

.github/workflows/ci.yml

Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -176,6 +176,17 @@ jobs:
176176
exit 1
177177
fi
178178
pandoc-plot clean tests/issue30.md
179+
180+
# The idea here is to install some random package (npstreams) to
181+
# check whether the plots will be rendered in the appropriate
182+
# environment
183+
python -m venv ./issue46
184+
./issue46/bin/python -m pip install npstreams matplotlib
185+
pandoc --filter pandoc-plot -i tests/issue46.md -t native
186+
if [ $(ls "plots" | wc -l) != 2 ]; then
187+
exit 1
188+
fi
189+
pandoc-plot clean tests/issue46.md
179190
180191
- name: Build documentation
181192
run: source tools/mkmanual.sh

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.5.2
6+
7+
* Overhauled the way executables are handled. This fixes an issue where executables specified in documents (rather than configuration) were ignored (#46).
8+
59
## Release 1.5.1
610

711
* Figures with no captions (and no link to the source script), will now be shown as an image, without figure numbering (#37).

cabal.project

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,2 +1 @@
1-
packages: pandoc-plot.cabal
2-
allow-newer: all
1+
packages: pandoc-plot.cabal

executable/Main.hs

Lines changed: 5 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,6 @@ module Main where
99

1010
import Control.Monad (join, msum, void, when)
1111
import Data.List (intersperse, (\\))
12-
import Data.Maybe (fromJust)
1312
import Data.Text (unpack)
1413
import qualified Data.Text.IO as TIO
1514
import Data.Version (parseVersion, showVersion)
@@ -58,15 +57,15 @@ import Text.Pandoc.Filter.Plot
5857
plotFilter,
5958
)
6059
import Text.Pandoc.Filter.Plot.Internal
61-
( Executable (..),
62-
cleanOutputDirs,
60+
( cleanOutputDirs,
6361
cls,
6462
configurationPathMeta,
6563
executable,
6664
readDoc,
6765
runPlotM,
6866
supportedSaveFormats,
69-
toolkits,
67+
toolkits,
68+
pathToExe
7069
)
7170
import Text.Pandoc.JSON (toJSONFilter)
7271
import Text.ParserCombinators.ReadP (readP_to_S)
@@ -286,8 +285,8 @@ showAvailableToolkits mfp = do
286285
toolkitInfo avail conf tk = do
287286
putStrLn $ "Toolkit: " <> show tk
288287
when avail $ do
289-
Executable dir exe <- fmap fromJust $ runPlotM Nothing conf $ executable tk
290-
putStrLn $ " Executable: " <> (dir </> unpack exe)
288+
exe <- runPlotM Nothing conf $ executable tk
289+
putStrLn $ " Executable: " <> (pathToExe exe)
291290
putStrLn $ " Code block trigger: " <> (unpack . cls $ tk)
292291
putStrLn $ " Supported save formats: " <> (mconcat . intersperse ", " . fmap show $ supportedSaveFormats tk)
293292
putStrLn mempty

pandoc-plot.cabal

Lines changed: 7 additions & 4 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.1
3+
version: 1.5.2
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
@@ -14,7 +14,11 @@ maintainer: Laurent P. René de Cotret
1414
license: GPL-2.0-or-later
1515
license-file: LICENSE
1616
build-type: Simple
17-
tested-with: GHC == 8.10.4, GHC == 9.0.1
17+
tested-with: GHC == 8.10.4,
18+
GHC == 9.0.1,
19+
GHC == 9.0.1,
20+
GHC == 9.2.1,
21+
GHC == 9.2.2
1822
extra-source-files:
1923
CHANGELOG.md
2024
LICENSE
@@ -94,7 +98,7 @@ library
9498
, directory >= 1.2.7 && < 2
9599
, filepath >= 1.4 && < 2
96100
, hashable >= 1 && < 2
97-
, pandoc >= 2.10 && < 3
101+
, pandoc >= 2.11 && < 3
98102
, pandoc-types >= 1.22 && < 1.23
99103
, lifted-async >= 0.10 && < 1
100104
, lifted-base >= 0.2 && < 1
@@ -144,7 +148,6 @@ test-suite tests
144148
, containers
145149
, directory
146150
, filepath
147-
, hspec
148151
, hspec-expectations
149152
, pandoc-types >= 1.20 && <= 2
150153
, pandoc-plot

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

Lines changed: 5 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -74,7 +74,6 @@ import Control.Monad.State.Strict
7474
evalStateT,
7575
)
7676
import Data.ByteString.Lazy (toStrict)
77-
import Data.Functor ((<&>))
7877
import Data.Hashable (hash)
7978
import Data.Map.Strict (Map)
8079
import qualified Data.Map.Strict as M
@@ -84,7 +83,6 @@ import Data.Text.Encoding (decodeUtf8With)
8483
import Data.Text.Encoding.Error (lenientDecode)
8584
import System.Directory
8685
( doesFileExist,
87-
findExecutable,
8886
getCurrentDirectory,
8987
getModificationTime,
9088
)
@@ -141,7 +139,6 @@ runPlotM fmt conf v = do
141139
cwd <- getCurrentDirectory
142140
st <-
143141
PlotState <$> newMVar mempty
144-
<*> newMVar mempty
145142
let verbosity = logVerbosity conf
146143
sink = logSink conf
147144
withLogger verbosity sink $
@@ -224,27 +221,23 @@ throwStrictError msg = do
224221
logger <- askLogger
225222
liftIO $ terminateLogging logger >> exitFailure
226223

227-
-- Plot state is used for caching.
228-
-- One part consists of a map of filepaths to hashes
224+
-- Plot state is used for caching a map of filepaths to hashes
229225
-- This allows multiple plots to depend on the same file/directory, and the file hashes
230226
-- will only be calculated once. This is OK because pandoc-plot will not run for long.
231227
-- We note that because figures are rendered possibly in parallel, access to
232228
-- the state must be synchronized; otherwise, each thread might compute its own
233229
-- hashes.
234-
-- The other part is comprised of a map of toolkits to renderers (possibly missing)
235-
-- This means that checking if renderers are available will only be done once.
236230
type FileHash = Word
237231

238232
data PlotState
239233
= PlotState
240234
(MVar (Map FilePath FileHash))
241-
(MVar (Map Toolkit (Maybe Renderer)))
242235

243236
-- | Get a filehash. If the file hash has been computed before,
244237
-- it is reused. Otherwise, the filehash is calculated and stored.
245238
fileHash :: FilePath -> PlotM FileHash
246239
fileHash path = do
247-
PlotState varHashes varExes <- get
240+
PlotState varHashes <- get
248241
hashes <- liftIO $ takeMVar varHashes
249242
(fh, hashes') <- case M.lookup path hashes of
250243
Nothing -> do
@@ -256,7 +249,7 @@ fileHash path = do
256249
debug $ mconcat ["Hash of dependency ", pack path, " already calculated."]
257250
return (h, hashes)
258251
liftIO $ putMVar varHashes hashes'
259-
put $ PlotState varHashes varExes
252+
put $ PlotState varHashes
260253
return fh
261254
where
262255
-- As a proxy for the state of a file dependency, we use the modification time
@@ -269,12 +262,8 @@ fileHash path = do
269262
else err (mconcat ["Dependency ", pack fp, " does not exist."]) >> return 0
270263

271264
-- | Find an executable.
272-
executable :: Toolkit -> PlotM (Maybe Executable)
273-
executable tk =
274-
exeSelector tk
275-
>>= \name ->
276-
liftIO $
277-
findExecutable name <&> fmap exeFromPath
265+
executable :: Toolkit -> PlotM Executable
266+
executable tk = exeSelector tk >>= return . exeFromPath
278267
where
279268
exeSelector Matplotlib = asksConfig matplotlibExe
280269
exeSelector PlotlyPython = asksConfig plotlyPythonExe

src/Text/Pandoc/Filter/Plot/Monad/Types.hs

Lines changed: 24 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,7 @@
1414
module Text.Pandoc.Filter.Plot.Monad.Types
1515
( Toolkit (..),
1616
Renderer (..),
17+
AvailabilityCheck(..),
1718
Script,
1819
CheckResult (..),
1920
InclusionKey (..),
@@ -26,6 +27,7 @@ module Text.Pandoc.Filter.Plot.Monad.Types
2627
inclusionKeys,
2728
Executable (..),
2829
exeFromPath,
30+
pathToExe,
2931
-- Utilities
3032
isWindows,
3133
)
@@ -37,7 +39,7 @@ import Data.String (IsString (..))
3739
import Data.Text (Text, pack, unpack)
3840
import Data.Yaml (FromJSON(..), ToJSON (toJSON), withText)
3941
import GHC.Generics (Generic)
40-
import System.FilePath (splitFileName)
42+
import System.FilePath (splitFileName, (</>), isAbsolute)
4143
import System.Info (os)
4244
import Text.Pandoc.Definition (Attr)
4345

@@ -94,13 +96,20 @@ cls Plotsjl = "plotsjl"
9496
cls PlantUML = "plantuml"
9597
cls SageMath = "sageplot"
9698

97-
-- | Executable program and directory where it can be found.
98-
data Executable = Executable FilePath Text
99+
-- | Executable program, and sometimes the directory where it can be found.
100+
data Executable
101+
= AbsExe FilePath Text
102+
| RelExe Text
99103

100104
exeFromPath :: FilePath -> Executable
101-
exeFromPath fp =
102-
let (dir, name) = splitFileName fp
103-
in Executable dir (pack name)
105+
exeFromPath fp
106+
| isAbsolute fp = let (dir, name) = splitFileName fp
107+
in AbsExe dir (pack name)
108+
| otherwise = RelExe (pack fp)
109+
110+
pathToExe :: Executable -> FilePath
111+
pathToExe (AbsExe dir name) = dir </> unpack name
112+
pathToExe (RelExe name) = unpack name
104113

105114
-- | Source context for plotting scripts
106115
type Script = Text
@@ -170,6 +179,8 @@ inclusionKeys = enumFromTo (minBound :: InclusionKey) maxBound
170179
data FigureSpec = FigureSpec
171180
{ -- | Renderer to use for this figure.
172181
renderer_ :: !Renderer,
182+
-- | Executable to use in rendering this figure.
183+
fsExecutable :: Executable,
173184
-- | Figure caption.
174185
caption :: !Text,
175186
-- | Append link to source code in caption.
@@ -263,15 +274,21 @@ data OutputSpec = OutputSpec
263274
oScriptPath :: FilePath,
264275
-- | Figure output path
265276
oFigurePath :: FilePath,
277+
-- | Executable to use during rendering
278+
oExecutable :: Executable,
266279
-- | Current working directory
267280
oCWD :: FilePath
268281
}
269282

283+
data AvailabilityCheck
284+
= CommandSuccess (Executable -> Text)
285+
| ExecutableExists
286+
270287
data Renderer = Renderer
271288
{ rendererToolkit :: Toolkit,
272-
rendererExe :: Executable,
273289
rendererCapture :: FigureSpec -> FilePath -> Script,
274290
rendererCommand :: OutputSpec -> Text,
291+
rendererAvailability :: AvailabilityCheck,
275292
rendererSupportedSaveFormats :: [SaveFormat],
276293
rendererChecks :: [Script -> CheckResult],
277294
rendererLanguage :: Text,

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

Lines changed: 4 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -70,11 +70,7 @@ parseFigureSpec block@(CodeBlock (id', classes, attrs) _) = do
7070
Nothing -> return NotAFigure
7171
Just tk -> do
7272
r <- renderer tk
73-
case r of
74-
Nothing -> do
75-
err $ mconcat ["Renderer for ", tshow tk, " needed but is not installed"]
76-
return $ MissingToolkit tk
77-
Just r' -> figureSpec r'
73+
figureSpec r
7874
where
7975
attrs' = Map.fromList attrs
8076
preamblePath = unpack <$> Map.lookup (tshow PreambleK) attrs'
@@ -108,8 +104,11 @@ parseFigureSpec block@(CodeBlock (id', classes, attrs) _) = do
108104

109105
-- Decide between reading from file or using document content
110106
content <- parseContent block
107+
108+
defaultExe <- executable rendererToolkit
111109

112110
let caption = Map.findWithDefault mempty (tshow CaptionK) attrs'
111+
fsExecutable = maybe defaultExe (exeFromPath . unpack) $ Map.lookup (tshow ExecutableK) attrs'
113112
withSource = maybe defWithSource readBool (Map.lookup (tshow WithSourceK) attrs')
114113
script = mconcat $ intersperse "\n" [header, includeScript, content]
115114
directory = makeValid $ unpack $ Map.findWithDefault (pack $ defaultDirectory conf) (tshow DirectoryK) attrs'

0 commit comments

Comments
 (0)