{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module Text.Pandoc.Filter.Plot.Renderers
( renderer,
preambleSelector,
parseExtraAttrs,
executable,
availableToolkits,
availableToolkitsM,
unavailableToolkits,
unavailableToolkitsM,
supportedSaveFormats,
OutputSpec (..),
Executable (..),
Renderer (..),
)
where
import Control.Concurrent.Async.Lifted (forConcurrently)
import Control.Monad.Reader (local)
import Data.Functor ((<&>))
import Data.List ((\\))
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as M
import Data.Maybe (catMaybes, isJust)
import Data.Text (Text, pack)
import System.Exit (ExitCode (..))
import Text.Pandoc.Filter.Plot.Monad
import Text.Pandoc.Filter.Plot.Monad.Logging
( Logger (lVerbosity),
)
import Text.Pandoc.Filter.Plot.Renderers.Bokeh
( bokeh, bokehSupportedSaveFormats )
import Text.Pandoc.Filter.Plot.Renderers.GGPlot2
( ggplot2, ggplot2SupportedSaveFormats )
import Text.Pandoc.Filter.Plot.Renderers.GNUPlot
( gnuplot, gnuplotSupportedSaveFormats )
import Text.Pandoc.Filter.Plot.Renderers.Graphviz
( graphviz, graphvizSupportedSaveFormats )
import Text.Pandoc.Filter.Plot.Renderers.Mathematica
( mathematica, mathematicaSupportedSaveFormats )
import Text.Pandoc.Filter.Plot.Renderers.Matlab
( matlab, matlabSupportedSaveFormats )
import Text.Pandoc.Filter.Plot.Renderers.Matplotlib
( matplotlib, matplotlibSupportedSaveFormats )
import Text.Pandoc.Filter.Plot.Renderers.Octave
( octave, octaveSupportedSaveFormats )
import Text.Pandoc.Filter.Plot.Renderers.PlantUML
( plantuml, plantumlSupportedSaveFormats )
import Text.Pandoc.Filter.Plot.Renderers.PlotlyPython
( plotlyPython, plotlyPythonSupportedSaveFormats )
import Text.Pandoc.Filter.Plot.Renderers.PlotlyR
( plotlyR, plotlyRSupportedSaveFormats )
import Text.Pandoc.Filter.Plot.Renderers.Plotsjl
( plotsjl, plotsjlSupportedSaveFormats )
import Text.Pandoc.Filter.Plot.Renderers.SageMath
( sagemath, sagemathSupportedSaveFormats )
import System.Directory (findExecutable)
renderer :: Toolkit -> PlotM Renderer
renderer :: Toolkit -> PlotM Renderer
renderer Toolkit
Matplotlib = PlotM Renderer
matplotlib
renderer Toolkit
PlotlyPython = PlotM Renderer
plotlyPython
renderer Toolkit
PlotlyR = PlotM Renderer
plotlyR
renderer Toolkit
Matlab = PlotM Renderer
matlab
renderer Toolkit
Mathematica = PlotM Renderer
mathematica
renderer Toolkit
Octave = PlotM Renderer
octave
renderer Toolkit
GGPlot2 = PlotM Renderer
ggplot2
renderer Toolkit
GNUPlot = PlotM Renderer
gnuplot
renderer Toolkit
Graphviz = PlotM Renderer
graphviz
renderer Toolkit
Bokeh = PlotM Renderer
bokeh
renderer Toolkit
Plotsjl = PlotM Renderer
plotsjl
renderer Toolkit
PlantUML = PlotM Renderer
plantuml
renderer Toolkit
SageMath = PlotM Renderer
sagemath
supportedSaveFormats :: Toolkit -> [SaveFormat]
supportedSaveFormats :: Toolkit -> [SaveFormat]
supportedSaveFormats Toolkit
Matplotlib = [SaveFormat]
matplotlibSupportedSaveFormats
supportedSaveFormats Toolkit
PlotlyPython = [SaveFormat]
plotlyPythonSupportedSaveFormats
supportedSaveFormats Toolkit
PlotlyR = [SaveFormat]
plotlyRSupportedSaveFormats
supportedSaveFormats Toolkit
Matlab = [SaveFormat]
matlabSupportedSaveFormats
supportedSaveFormats Toolkit
Mathematica = [SaveFormat]
mathematicaSupportedSaveFormats
supportedSaveFormats Toolkit
Octave = [SaveFormat]
octaveSupportedSaveFormats
supportedSaveFormats Toolkit
GGPlot2 = [SaveFormat]
ggplot2SupportedSaveFormats
supportedSaveFormats Toolkit
GNUPlot = [SaveFormat]
gnuplotSupportedSaveFormats
supportedSaveFormats Toolkit
Graphviz = [SaveFormat]
graphvizSupportedSaveFormats
supportedSaveFormats Toolkit
Bokeh = [SaveFormat]
bokehSupportedSaveFormats
supportedSaveFormats Toolkit
Plotsjl = [SaveFormat]
plotsjlSupportedSaveFormats
supportedSaveFormats Toolkit
PlantUML = [SaveFormat]
plantumlSupportedSaveFormats
supportedSaveFormats Toolkit
SageMath = [SaveFormat]
sagemathSupportedSaveFormats
preambleSelector :: Toolkit -> (Configuration -> Script)
preambleSelector :: Toolkit -> Configuration -> Text
preambleSelector Toolkit
Matplotlib = Configuration -> Text
matplotlibPreamble
preambleSelector Toolkit
PlotlyPython = Configuration -> Text
plotlyPythonPreamble
preambleSelector Toolkit
PlotlyR = Configuration -> Text
plotlyRPreamble
preambleSelector Toolkit
Matlab = Configuration -> Text
matlabPreamble
preambleSelector Toolkit
Mathematica = Configuration -> Text
mathematicaPreamble
preambleSelector Toolkit
Octave = Configuration -> Text
octavePreamble
preambleSelector Toolkit
GGPlot2 = Configuration -> Text
ggplot2Preamble
preambleSelector Toolkit
GNUPlot = Configuration -> Text
gnuplotPreamble
preambleSelector Toolkit
Graphviz = Configuration -> Text
graphvizPreamble
preambleSelector Toolkit
Bokeh = Configuration -> Text
bokehPreamble
preambleSelector Toolkit
Plotsjl = Configuration -> Text
plotsjlPreamble
preambleSelector Toolkit
PlantUML = Configuration -> Text
plantumlPreamble
preambleSelector Toolkit
SageMath = Configuration -> Text
sagemathPreamble
parseExtraAttrs :: Toolkit -> Map Text Text -> Map Text Text
Toolkit
Matplotlib = forall k a. (k -> a -> Bool) -> Map k a -> Map k a
M.filterWithKey (\Text
k Text
_ -> Text
k forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [ String -> Text
pack forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show InclusionKey
MatplotlibTightBBoxK
, String -> Text
pack forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show InclusionKey
MatplotlibTransparentK
])
parseExtraAttrs Toolkit
_ = forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Monoid a => a
mempty
availableToolkits :: Configuration -> IO [Toolkit]
availableToolkits :: Configuration -> IO [Toolkit]
availableToolkits Configuration
conf = forall a. Maybe Format -> Configuration -> PlotM a -> IO a
runPlotM forall a. Maybe a
Nothing Configuration
conf PlotM [Toolkit]
availableToolkitsM
unavailableToolkits :: Configuration -> IO [Toolkit]
unavailableToolkits :: Configuration -> IO [Toolkit]
unavailableToolkits Configuration
conf = forall a. Maybe Format -> Configuration -> PlotM a -> IO a
runPlotM forall a. Maybe a
Nothing Configuration
conf PlotM [Toolkit]
unavailableToolkitsM
availableToolkitsM :: PlotM [Toolkit]
availableToolkitsM :: PlotM [Toolkit]
availableToolkitsM = forall {a}.
StateT PlotState (ReaderT RuntimeEnv IO) a
-> StateT PlotState (ReaderT RuntimeEnv IO) a
asNonStrictAndSilent forall a b. (a -> b) -> a -> b
$ do
[Maybe Toolkit]
mtks <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, MonadBaseControl IO m) =>
t a -> (a -> m b) -> m (t b)
forConcurrently [Toolkit]
toolkits forall a b. (a -> b) -> a -> b
$ \Toolkit
tk -> do
Renderer
r <- Toolkit -> PlotM Renderer
renderer Toolkit
tk
Executable
exe <- Toolkit -> PlotM Executable
executable Toolkit
tk
Bool
a <- Executable -> AvailabilityCheck -> PlotM Bool
isAvailable Executable
exe (Renderer -> AvailabilityCheck
rendererAvailability Renderer
r)
if Bool
a
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just Toolkit
tk
else forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. [Maybe a] -> [a]
catMaybes [Maybe Toolkit]
mtks
where
asNonStrictAndSilent :: StateT PlotState (ReaderT RuntimeEnv IO) a
-> StateT PlotState (ReaderT RuntimeEnv IO) a
asNonStrictAndSilent = forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (\(RuntimeEnv Maybe Format
f Configuration
c Logger
l String
d MVar ()
s) -> Maybe Format
-> Configuration -> Logger -> String -> MVar () -> RuntimeEnv
RuntimeEnv Maybe Format
f (Configuration
c{strictMode :: Bool
strictMode = Bool
False}) (Logger
l{lVerbosity :: Verbosity
lVerbosity = Verbosity
Silent}) String
d MVar ()
s)
commandSuccess :: Text -> PlotM Bool
commandSuccess :: Text -> PlotM Bool
commandSuccess Text
s = do
String
cwd <- forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks RuntimeEnv -> String
envCWD
(ExitCode
ec, Text
_) <- String -> Text -> PlotM (ExitCode, Text)
runCommand String
cwd Text
s
forall (m :: * -> *). (MonadLogger m, MonadIO m) => Text -> m ()
debug forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat [Text
"Command ", Text
s, Text
" resulted in ", String -> Text
pack forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show ExitCode
ec]
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ ExitCode
ec forall a. Eq a => a -> a -> Bool
== ExitCode
ExitSuccess
isAvailable :: Executable -> AvailabilityCheck -> PlotM Bool
isAvailable :: Executable -> AvailabilityCheck -> PlotM Bool
isAvailable Executable
exe (CommandSuccess Executable -> Text
f) = Text -> PlotM Bool
commandSuccess (Executable -> Text
f Executable
exe)
isAvailable Executable
exe (AvailabilityCheck
ExecutableExists) = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ String -> IO (Maybe String)
findExecutable (Executable -> String
pathToExe Executable
exe) forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> forall a. Maybe a -> Bool
isJust
unavailableToolkitsM :: PlotM [Toolkit]
unavailableToolkitsM :: PlotM [Toolkit]
unavailableToolkitsM = forall a. Eq a => [a] -> [a] -> [a]
(\\) [Toolkit]
toolkits forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> PlotM [Toolkit]
availableToolkitsM