Skip to content

Commit df416da

Browse files
committed
Don't load renderers until requested
1 parent bf1fe20 commit df416da

File tree

20 files changed

+217
-401
lines changed

20 files changed

+217
-401
lines changed

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

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

Lines changed: 2 additions & 8 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
)
@@ -269,12 +267,8 @@ fileHash path = do
269267
else err (mconcat ["Dependency ", pack fp, " does not exist."]) >> return 0
270268

271269
-- | Find an executable.
272-
executable :: Toolkit -> PlotM (Maybe Executable)
273-
executable tk =
274-
exeSelector tk
275-
>>= \name ->
276-
liftIO $
277-
findExecutable name <&> fmap exeFromPath
270+
executable :: Toolkit -> PlotM Executable
271+
executable tk = exeSelector tk >>= return . exeFromPath
278272
where
279273
exeSelector Matplotlib = asksConfig matplotlibExe
280274
exeSelector PlotlyPython = asksConfig plotlyPythonExe

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

Lines changed: 17 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 (..),
@@ -38,7 +39,7 @@ import Data.String (IsString (..))
3839
import Data.Text (Text, pack, unpack)
3940
import Data.Yaml (FromJSON(..), ToJSON (toJSON), withText)
4041
import GHC.Generics (Generic)
41-
import System.FilePath (splitFileName, (</>))
42+
import System.FilePath (splitFileName, (</>), isAbsolute)
4243
import System.Info (os)
4344
import Text.Pandoc.Definition (Attr)
4445

@@ -95,16 +96,20 @@ cls Plotsjl = "plotsjl"
9596
cls PlantUML = "plantuml"
9697
cls SageMath = "sageplot"
9798

98-
-- | Executable program and directory where it can be found.
99-
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
100103

101104
exeFromPath :: FilePath -> Executable
102-
exeFromPath fp =
103-
let (dir, name) = splitFileName fp
104-
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)
105109

106110
pathToExe :: Executable -> FilePath
107-
pathToExe (Executable dir name) = dir </> unpack name
111+
pathToExe (AbsExe dir name) = dir </> unpack name
112+
pathToExe (RelExe name) = unpack name
108113

109114
-- | Source context for plotting scripts
110115
type Script = Text
@@ -275,10 +280,15 @@ data OutputSpec = OutputSpec
275280
oCWD :: FilePath
276281
}
277282

283+
data AvailabilityCheck
284+
= CommandSuccess (Executable -> Text)
285+
| ExecutableExists
286+
278287
data Renderer = Renderer
279288
{ rendererToolkit :: Toolkit,
280289
rendererCapture :: FigureSpec -> FilePath -> Script,
281290
rendererCommand :: OutputSpec -> Text,
291+
rendererAvailability :: AvailabilityCheck,
282292
rendererSupportedSaveFormats :: [SaveFormat],
283293
rendererChecks :: [Script -> CheckResult],
284294
rendererLanguage :: Text,

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

Lines changed: 2 additions & 6 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'
@@ -109,7 +105,7 @@ parseFigureSpec block@(CodeBlock (id', classes, attrs) _) = do
109105
-- Decide between reading from file or using document content
110106
content <- parseContent block
111107

112-
defaultExe <- fromJust <$> (executable rendererToolkit)
108+
defaultExe <- executable rendererToolkit
113109

114110
let caption = Map.findWithDefault mempty (tshow CaptionK) attrs'
115111
fsExecutable = maybe defaultExe (exeFromPath . unpack) $ Map.lookup (tshow ExecutableK) attrs'

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

Lines changed: 34 additions & 37 deletions
Original file line numberDiff line numberDiff line change
@@ -27,16 +27,14 @@ module Text.Pandoc.Filter.Plot.Renderers
2727
where
2828

2929
import Control.Concurrent.Async.Lifted (forConcurrently)
30-
import Control.Concurrent.MVar (putMVar, takeMVar)
3130
import Control.Monad.Reader (local)
32-
import Control.Monad.State.Strict
33-
( MonadState (get, put),
34-
)
31+
import Data.Functor ((<&>))
3532
import Data.List ((\\))
3633
import Data.Map.Strict (Map)
3734
import qualified Data.Map.Strict as M
3835
import Data.Maybe (catMaybes, isJust)
3936
import Data.Text (Text, pack)
37+
import System.Exit (ExitCode (..))
4038
import Text.Pandoc.Filter.Plot.Monad
4139
import Text.Pandoc.Filter.Plot.Monad.Logging
4240
( Logger (lVerbosity),
@@ -67,41 +65,25 @@ import Text.Pandoc.Filter.Plot.Renderers.Plotsjl
6765
( plotsjl, plotsjlSupportedSaveFormats )
6866
import Text.Pandoc.Filter.Plot.Renderers.SageMath
6967
( sagemath, sagemathSupportedSaveFormats )
68+
import System.Directory (findExecutable)
7069

7170
-- | Get the renderer associated with a toolkit.
7271
-- If the renderer has not been used before,
7372
-- initialize it and store where it is. It will be re-used.
74-
renderer :: Toolkit -> PlotM (Maybe Renderer)
75-
renderer tk = do
76-
PlotState varHashes varRenderers <- get
77-
renderers <- liftIO $ takeMVar varRenderers
78-
(r', rs') <- case M.lookup tk renderers of
79-
Nothing -> do
80-
debug $ mconcat ["Looking for renderer for ", pack $ show tk]
81-
r' <- sel tk
82-
let rs' = M.insert tk r' renderers
83-
return (r', rs')
84-
Just e -> do
85-
debug $ mconcat ["Renderer for \"", pack $ show tk, "\" already initialized."]
86-
return (e, renderers)
87-
liftIO $ putMVar varRenderers rs'
88-
put $ PlotState varHashes varRenderers
89-
return r'
90-
where
91-
sel :: Toolkit -> PlotM (Maybe Renderer)
92-
sel Matplotlib = matplotlib
93-
sel PlotlyPython = plotlyPython
94-
sel PlotlyR = plotlyR
95-
sel Matlab = matlab
96-
sel Mathematica = mathematica
97-
sel Octave = octave
98-
sel GGPlot2 = ggplot2
99-
sel GNUPlot = gnuplot
100-
sel Graphviz = graphviz
101-
sel Bokeh = bokeh
102-
sel Plotsjl = plotsjl
103-
sel PlantUML = plantuml
104-
sel SageMath = sagemath
73+
renderer :: Toolkit -> PlotM Renderer
74+
renderer Matplotlib = matplotlib
75+
renderer PlotlyPython = plotlyPython
76+
renderer PlotlyR = plotlyR
77+
renderer Matlab = matlab
78+
renderer Mathematica = mathematica
79+
renderer Octave = octave
80+
renderer GGPlot2 = ggplot2
81+
renderer GNUPlot = gnuplot
82+
renderer Graphviz = graphviz
83+
renderer Bokeh = bokeh
84+
renderer Plotsjl = plotsjl
85+
renderer PlantUML = plantuml
86+
renderer SageMath = sagemath
10587

10688
-- | Save formats supported by this renderer.
10789
supportedSaveFormats :: Toolkit -> [SaveFormat]
@@ -157,14 +139,29 @@ unavailableToolkits conf = runPlotM Nothing conf unavailableToolkitsM
157139
availableToolkitsM :: PlotM [Toolkit]
158140
availableToolkitsM = asNonStrictAndSilent $ do
159141
mtks <- forConcurrently toolkits $ \tk -> do
160-
available <- isJust <$> renderer tk
161-
if available
142+
r <- renderer tk
143+
exe <- executable tk
144+
a <- isAvailable exe (rendererAvailability r)
145+
if a
162146
then return $ Just tk
163147
else return Nothing
164148
return $ catMaybes mtks
165149
where
166150
asNonStrictAndSilent = local (\(RuntimeEnv f c l d) -> RuntimeEnv f (c{strictMode = False}) (l{lVerbosity = Silent}) d)
167151

152+
-- | Check that the supplied command results in
153+
-- an exit code of 0 (i.e. no errors)
154+
commandSuccess :: Text -> PlotM Bool
155+
commandSuccess s = do
156+
cwd <- asks envCWD
157+
(ec, _) <- runCommand cwd s
158+
debug $ mconcat ["Command ", s, " resulted in ", pack $ show ec]
159+
return $ ec == ExitSuccess
160+
161+
isAvailable :: Executable -> AvailabilityCheck -> PlotM Bool
162+
isAvailable exe (CommandSuccess f) = commandSuccess (f exe)
163+
isAvailable exe (ExecutableExists) = liftIO $ findExecutable (pathToExe exe) <&> isJust
164+
168165
-- | Monadic version of @unavailableToolkits@
169166
unavailableToolkitsM :: PlotM [Toolkit]
170167
unavailableToolkitsM = (\\) toolkits <$> availableToolkitsM

src/Text/Pandoc/Filter/Plot/Renderers/Bokeh.hs

Lines changed: 12 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -22,39 +22,28 @@ import Data.Monoid (Any (..))
2222
import qualified Data.Text as T
2323
import Text.Pandoc.Filter.Plot.Renderers.Prelude
2424

25-
bokeh :: PlotM (Maybe Renderer)
25+
bokeh :: PlotM Renderer
2626
bokeh = do
27-
avail <- bokehAvailable
28-
if not avail
29-
then return Nothing
30-
else do
3127
cmdargs <- asksConfig bokehCmdArgs
3228
return $
33-
return
34-
Renderer
35-
{ rendererToolkit = Bokeh,
36-
rendererCapture = appendCapture bokehCaptureFragment,
37-
rendererCommand = bokehCommand cmdargs,
38-
rendererSupportedSaveFormats = bokehSupportedSaveFormats,
39-
rendererChecks = [bokehCheckIfShow],
40-
rendererLanguage = "python",
41-
rendererComment = mappend "# ",
42-
rendererScriptExtension = ".py"
43-
}
29+
Renderer
30+
{ rendererToolkit = Bokeh,
31+
rendererCapture = appendCapture bokehCaptureFragment,
32+
rendererCommand = bokehCommand cmdargs,
33+
rendererAvailability = CommandSuccess $ \exe -> [st|#{pathToExe exe} -c "import bokeh; import selenium"|],
34+
rendererSupportedSaveFormats = bokehSupportedSaveFormats,
35+
rendererChecks = [bokehCheckIfShow],
36+
rendererLanguage = "python",
37+
rendererComment = mappend "# ",
38+
rendererScriptExtension = ".py"
39+
}
4440

4541
bokehSupportedSaveFormats :: [SaveFormat]
4642
bokehSupportedSaveFormats = [PNG, SVG, HTML]
4743

4844
bokehCommand :: Text -> OutputSpec -> Text
4945
bokehCommand cmdargs OutputSpec {..} = [st|#{pathToExe oExecutable} #{cmdargs} "#{oScriptPath}"|]
5046

51-
bokehAvailable :: PlotM Bool
52-
bokehAvailable = do
53-
mexe <- executable Bokeh
54-
case mexe of
55-
Nothing -> return False
56-
Just (Executable dir exe) -> withPrependedPath dir $ asks envCWD >>= flip commandSuccess [st|#{exe} -c "import bokeh; import selenium"|]
57-
5847
-- | Check if `bokeh.io.show()` calls are present in the script,
5948
-- which would halt pandoc-plot
6049
bokehCheckIfShow :: Script -> CheckResult

src/Text/Pandoc/Filter/Plot/Renderers/GGPlot2.hs

Lines changed: 12 additions & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -21,40 +21,28 @@ where
2121
import qualified Data.Text as T
2222
import Text.Pandoc.Filter.Plot.Renderers.Prelude
2323

24-
ggplot2 :: PlotM (Maybe Renderer)
24+
ggplot2 :: PlotM Renderer
2525
ggplot2 = do
26-
avail <- ggplot2Available
27-
if not avail
28-
then return Nothing
29-
else do
3026
cmdargs <- asksConfig ggplot2CmdArgs
3127
return $
32-
return
33-
Renderer
34-
{ rendererToolkit = GGPlot2,
35-
rendererCapture = ggplot2Capture,
36-
rendererCommand = ggplot2Command cmdargs,
37-
rendererSupportedSaveFormats = ggplot2SupportedSaveFormats,
38-
rendererChecks = mempty,
39-
rendererLanguage = "r",
40-
rendererComment = mappend "# ",
41-
rendererScriptExtension = ".r"
42-
}
28+
Renderer
29+
{ rendererToolkit = GGPlot2,
30+
rendererCapture = ggplot2Capture,
31+
rendererCommand = ggplot2Command cmdargs,
32+
rendererAvailability = CommandSuccess $ \exe -> [st|#{pathToExe exe} -e "if(!require('ggplot2')) {quit(status=1)}"|],
33+
rendererSupportedSaveFormats = ggplot2SupportedSaveFormats,
34+
rendererChecks = mempty,
35+
rendererLanguage = "r",
36+
rendererComment = mappend "# ",
37+
rendererScriptExtension = ".r"
38+
}
4339

4440
ggplot2SupportedSaveFormats :: [SaveFormat]
4541
ggplot2SupportedSaveFormats = [PNG, PDF, SVG, JPG, EPS, TIF]
4642

4743
ggplot2Command :: Text -> OutputSpec -> Text
4844
ggplot2Command cmdargs OutputSpec {..} = [st|#{pathToExe oExecutable} #{cmdargs} "#{oScriptPath}"|]
4945

50-
ggplot2Available :: PlotM Bool
51-
ggplot2Available = do
52-
mexe <- executable GGPlot2
53-
case mexe of
54-
Nothing -> return False
55-
Just (Executable dir exe) ->
56-
withPrependedPath dir $ asks envCWD >>= flip commandSuccess [st|#{exe} -e "if(!require('ggplot2')) {quit(status=1)}"|]
57-
5846
ggplot2Capture :: FigureSpec -> FilePath -> Script
5947
ggplot2Capture fs fp =
6048
T.unlines

0 commit comments

Comments
 (0)