Copyright | (c) Laurent P René de Cotret 2019 - 2021 |
---|---|
License | GNU GPL, version 2 or above |
Maintainer | laurent.decotret@outlook.com |
Stability | internal |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
This module re-exports internal pandoc-plot functionality. The external use of content from this module is discouraged.
Synopsis
- renderer :: Toolkit -> PlotM (Maybe Renderer)
- preambleSelector :: Toolkit -> Configuration -> Script
- parseExtraAttrs :: Toolkit -> Map Text Text -> Map Text Text
- executable :: Toolkit -> PlotM (Maybe Executable)
- availableToolkits :: Configuration -> IO [Toolkit]
- availableToolkitsM :: PlotM [Toolkit]
- unavailableToolkits :: Configuration -> IO [Toolkit]
- unavailableToolkitsM :: PlotM [Toolkit]
- supportedSaveFormats :: Toolkit -> [SaveFormat]
- data OutputSpec = OutputSpec {}
- data Executable = Executable FilePath Text
- data Renderer = Renderer {
- rendererToolkit :: Toolkit
- rendererExe :: Executable
- rendererCapture :: FigureSpec -> FilePath -> Script
- rendererCommand :: OutputSpec -> Text
- rendererSupportedSaveFormats :: [SaveFormat]
- rendererChecks :: [Script -> CheckResult]
- rendererLanguage :: Text
- rendererComment :: Text -> Text
- rendererScriptExtension :: String
- data ScriptResult
- runTempScript :: FigureSpec -> PlotM ScriptResult
- runScriptIfNecessary :: FigureSpec -> PlotM ScriptResult
- figurePath :: FigureSpec -> PlotM FilePath
- sourceCodePath :: FigureSpec -> PlotM FilePath
- plotToolkit :: Block -> Maybe Toolkit
- parseFigureSpec :: Block -> PlotM ParseFigureResult
- data ParseFigureResult
- captionReader :: Format -> Text -> Maybe [Inline]
- configuration :: FilePath -> IO Configuration
- configurationPathMeta :: Pandoc -> Maybe FilePath
- defaultConfiguration :: Configuration
- cleanOutputDirs :: Walkable Block b => Configuration -> b -> IO [FilePath]
- outputDirs :: Walkable Block b => b -> PlotM [FilePath]
- readDoc :: FilePath -> IO Pandoc
- data Configuration = Configuration {
- defaultDirectory :: !FilePath
- defaultWithSource :: !Bool
- defaultDPI :: !Int
- defaultSaveFormat :: !SaveFormat
- defaultDependencies :: ![FilePath]
- captionFormat :: !Format
- sourceCodeLabel :: !Text
- strictMode :: !Bool
- logVerbosity :: !Verbosity
- logSink :: !LogSink
- matplotlibPreamble :: !Script
- plotlyPythonPreamble :: !Script
- plotlyRPreamble :: !Script
- matlabPreamble :: !Script
- mathematicaPreamble :: !Script
- octavePreamble :: !Script
- ggplot2Preamble :: !Script
- gnuplotPreamble :: !Script
- graphvizPreamble :: !Script
- bokehPreamble :: !Script
- plotsjlPreamble :: !Script
- plantumlPreamble :: !Script
- matplotlibExe :: !FilePath
- matlabExe :: !FilePath
- plotlyPythonExe :: !FilePath
- plotlyRExe :: !FilePath
- mathematicaExe :: !FilePath
- octaveExe :: !FilePath
- ggplot2Exe :: !FilePath
- gnuplotExe :: !FilePath
- graphvizExe :: !FilePath
- bokehExe :: !FilePath
- plotsjlExe :: !FilePath
- plantumlExe :: !FilePath
- matplotlibCmdArgs :: !Text
- matlabCmdArgs :: !Text
- plotlyPythonCmdArgs :: !Text
- plotlyRCmdArgs :: !Text
- mathematicaCmdArgs :: !Text
- octaveCmdArgs :: !Text
- ggplot2CmdArgs :: !Text
- gnuplotCmdArgs :: !Text
- graphvizCmdArgs :: !Text
- bokehCmdArgs :: !Text
- plotsjlCmdArgs :: !Text
- plantumlCmdArgs :: !Text
- matplotlibTightBBox :: !Bool
- matplotlibTransparent :: !Bool
- type PlotM = StateT PlotState (ReaderT RuntimeEnv IO)
- data RuntimeEnv = RuntimeEnv {}
- data PlotState = PlotState (MVar (Map FilePath FileHash)) (MVar (Map Toolkit (Maybe Renderer)))
- runPlotM :: Maybe Format -> Configuration -> PlotM a -> IO a
- mapConcurrentlyN :: Traversable t => Int -> (a -> PlotM b) -> t a -> PlotM (t b)
- runCommand :: FilePath -> Text -> PlotM (ExitCode, Text)
- withPrependedPath :: FilePath -> PlotM a -> PlotM a
- throwStrictError :: Text -> PlotM ()
- fileHash :: FilePath -> PlotM FileHash
- executable :: Toolkit -> PlotM (Maybe Executable)
- data Verbosity
- data LogSink
- debug :: (MonadLogger m, MonadIO m) => Text -> m ()
- err :: (MonadLogger m, MonadIO m) => Text -> m ()
- warning :: (MonadLogger m, MonadIO m) => Text -> m ()
- info :: (MonadLogger m, MonadIO m) => Text -> m ()
- liftIO :: MonadIO m => IO a -> m a
- ask :: MonadReader r m => m r
- asks :: MonadReader r m => (r -> a) -> m a
- asksConfig :: (Configuration -> a) -> PlotM a
- data Toolkit
- = Matplotlib
- | Matlab
- | PlotlyPython
- | PlotlyR
- | Mathematica
- | Octave
- | GGPlot2
- | GNUPlot
- | Graphviz
- | Bokeh
- | Plotsjl
- | PlantUML
- data Renderer = Renderer {
- rendererToolkit :: Toolkit
- rendererExe :: Executable
- rendererCapture :: FigureSpec -> FilePath -> Script
- rendererCommand :: OutputSpec -> Text
- rendererSupportedSaveFormats :: [SaveFormat]
- rendererChecks :: [Script -> CheckResult]
- rendererLanguage :: Text
- rendererComment :: Text -> Text
- rendererScriptExtension :: String
- type Script = Text
- data CheckResult
- data InclusionKey
- data FigureSpec = FigureSpec {
- renderer_ :: !Renderer
- caption :: !Text
- withSource :: !Bool
- script :: !Script
- saveFormat :: !SaveFormat
- directory :: !FilePath
- dpi :: !Int
- dependencies :: ![FilePath]
- extraAttrs :: ![(Text, Text)]
- blockAttrs :: !Attr
- data OutputSpec = OutputSpec {}
- data SaveFormat
- cls :: Toolkit -> Text
- extension :: SaveFormat -> String
- toolkits :: [Toolkit]
- inclusionKeys :: [InclusionKey]
- data Executable = Executable FilePath Text
- exeFromPath :: FilePath -> Executable
- isWindows :: Bool
- extractPlot :: Text -> Text
- toFigure :: Format -> FigureSpec -> PlotM Block
Documentation
renderer :: Toolkit -> PlotM (Maybe Renderer) Source #
Get the renderer associated with a toolkit. If the renderer has not been used before, initialize it and store where it is. It will be re-used.
preambleSelector :: Toolkit -> Configuration -> Script Source #
The function that maps from configuration to the preamble.
parseExtraAttrs :: Toolkit -> Map Text Text -> Map Text Text Source #
Parse code block headers for extra attributes that are specific to this renderer. By default, no extra attributes are parsed.
executable :: Toolkit -> PlotM (Maybe Executable) Source #
Find an executable.
availableToolkits :: Configuration -> IO [Toolkit] Source #
List of toolkits available on this machine. The executables to look for are taken from the configuration.
availableToolkitsM :: PlotM [Toolkit] Source #
Monadic version of availableToolkits
.
Note that logging is disabled
unavailableToolkits :: Configuration -> IO [Toolkit] Source #
List of toolkits not available on this machine. The executables to look for are taken from the configur
unavailableToolkitsM :: PlotM [Toolkit] Source #
Monadic version of unavailableToolkits
supportedSaveFormats :: Toolkit -> [SaveFormat] Source #
Save formats supported by this renderer.
data OutputSpec Source #
Internal description of all information needed to output a figure.
OutputSpec | |
|
data Executable Source #
Executable program and directory where it can be found.
Renderer | |
|
data ScriptResult Source #
Possible result of running a script
Instances
Show ScriptResult Source # | |
Defined in Text.Pandoc.Filter.Plot.Scripting showsPrec :: Int -> ScriptResult -> ShowS # show :: ScriptResult -> String # showList :: [ScriptResult] -> ShowS # |
figurePath :: FigureSpec -> PlotM FilePath Source #
Determine the path a figure should have.
The path for this file is unique to the content of the figure,
so that figurePath
can be used to determine whether a figure should
be rendered again or not.
sourceCodePath :: FigureSpec -> PlotM FilePath Source #
Determine the path to the source code that generated the figure. To ensure that the source code path is distinguished from HTML figures, we use the extension .src.html.
plotToolkit :: Block -> Maybe Toolkit Source #
Determine which toolkit should be used to render the plot from a code block, if any.
parseFigureSpec :: Block -> PlotM ParseFigureResult Source #
Determine inclusion specifications from Block
attributes.
If an environment is detected, but the save format is incompatible,
an error will be thrown.
data ParseFigureResult Source #
NotAFigure | The block is not meant to become a figure |
Figure FigureSpec | The block is meant to become a figure |
MissingToolkit Toolkit | The block is meant to become a figure, but the plotting toolkit is missing |
UnsupportedSaveFormat Toolkit SaveFormat | The block is meant to become a figure, but the figure format is incompatible with the plotting toolkit |
captionReader :: Format -> Text -> Maybe [Inline] Source #
Reader a caption, based on input document format
configuration :: FilePath -> IO Configuration Source #
Read configuration from a YAML file. The keys are exactly the same as for code blocks.
If a key is not present, its value will be set to the default value. Parsing errors result in thrown exceptions.
configurationPathMeta :: Pandoc -> Maybe FilePath Source #
Extact path to configuration from the metadata in a Pandoc document.
The path to the configuration file should be under the plot-configuration
key.
In case there is no such metadata, return the default configuration.
For example, at the top of a markdown file:
--- title: My document author: John Doe plot-configuration: pathto/file.yml ---
The same can be specified via the command line using Pandoc's -M
flag:
pandoc --filter pandoc-plot -M plot-configuration="path/to/file.yml" ...
Since: 0.6.0.0
defaultConfiguration :: Configuration Source #
Default configuration values.
Since: 0.5.0.0
cleanOutputDirs :: Walkable Block b => Configuration -> b -> IO [FilePath] Source #
Clean all output related to pandoc-plot. This includes output directories specified in the configuration and in the document/block, as well as log files. Note that *all* files in pandoc-plot output directories will be removed.
The cleaned directories are returned.
outputDirs :: Walkable Block b => b -> PlotM [FilePath] Source #
Analyze a document to determine where would the pandoc-plot output directories be.
readDoc :: FilePath -> IO Pandoc Source #
Read a document, guessing what extensions and reader options are appropriate. If the file cannot be read for any reason, an error is thrown.
data Configuration Source #
The Configuration
type holds the default values to use
when running pandoc-plot. These values can be overridden in code blocks.
You can create an instance of the Configuration
type from file using the configuration
function.
You can store the path to a configuration file in metadata under the key plot-configuration
. For example, in Markdown:
--- title: My document author: John Doe plot-configuration: pathtofile.yml ---
The same can be specified via the command line using Pandoc's -M
flag:
pandoc --filter pandoc-plot -M plot-configuration="path/to/file.yml" ...
In this case, use configurationPathMeta
to extact the path from Pandoc
documents.
Configuration | |
|
Instances
Eq Configuration Source # | |
Defined in Text.Pandoc.Filter.Plot.Monad (==) :: Configuration -> Configuration -> Bool # (/=) :: Configuration -> Configuration -> Bool # | |
Show Configuration Source # | |
Defined in Text.Pandoc.Filter.Plot.Monad showsPrec :: Int -> Configuration -> ShowS # show :: Configuration -> String # showList :: [Configuration] -> ShowS # |
data RuntimeEnv Source #
Concurrent execution
mapConcurrentlyN :: Traversable t => Int -> (a -> PlotM b) -> t a -> PlotM (t b) Source #
maps a function, performing at most N
actions concurrently.
Running external commands
runCommand :: FilePath -> Text -> PlotM (ExitCode, Text) Source #
Run a command within the PlotM
monad. Stderr stream
is read and decoded, while Stdout is ignored.
Logging happens at the debug level if the command succeeds, or at
the error level if it does not succeed.
withPrependedPath :: FilePath -> PlotM a -> PlotM a Source #
Prepend a directory to the PATH environment variable for the duration of a computation.
This function is exception-safe; even if an exception happens during the computation, the PATH environment variable will be reverted back to its initial value.
Halting pandoc-plot
throwStrictError :: Text -> PlotM () Source #
Throw an error that halts the execution of pandoc-plot due to a strict-mode.
Getting file hashes
fileHash :: FilePath -> PlotM FileHash Source #
Get a filehash. If the file hash has been computed before, it is reused. Otherwise, the filehash is calculated and stored.
Getting executables
executable :: Toolkit -> PlotM (Maybe Executable) Source #
Find an executable.
Logging
Verbosity of the logger.
Debug | Log all messages, including debug messages. |
Info | Log information, warning, and error messages. |
Warning | Log warning and error messages. |
Error | Only log errors. |
Silent | Don't log anything. |
Instances
Bounded Verbosity Source # | |
Enum Verbosity Source # | |
Defined in Text.Pandoc.Filter.Plot.Monad.Logging succ :: Verbosity -> Verbosity # pred :: Verbosity -> Verbosity # fromEnum :: Verbosity -> Int # enumFrom :: Verbosity -> [Verbosity] # enumFromThen :: Verbosity -> Verbosity -> [Verbosity] # enumFromTo :: Verbosity -> Verbosity -> [Verbosity] # enumFromThenTo :: Verbosity -> Verbosity -> Verbosity -> [Verbosity] # | |
Eq Verbosity Source # | |
Ord Verbosity Source # | |
Defined in Text.Pandoc.Filter.Plot.Monad.Logging | |
Show Verbosity Source # | |
IsString Verbosity Source # | |
Defined in Text.Pandoc.Filter.Plot.Monad.Logging fromString :: String -> Verbosity # | |
FromJSON Verbosity Source # | |
Description of the possible ways to sink log messages.
Lifting and other monadic operations
ask :: MonadReader r m => m r #
Retrieves the monad environment.
:: MonadReader r m | |
=> (r -> a) | The selector function to apply to the environment. |
-> m a |
Retrieves a function of the current environment.
asksConfig :: (Configuration -> a) -> PlotM a Source #
Get access to configuration within the PlotM
monad.
Base types
Enumeration of supported toolkits
Matplotlib | |
Matlab | |
PlotlyPython | |
PlotlyR | |
Mathematica | |
Octave | |
GGPlot2 | |
GNUPlot | |
Graphviz | |
Bokeh | |
Plotsjl | |
PlantUML |
Instances
Renderer | |
|
data CheckResult Source #
Result of checking scripts for problems
Instances
Eq CheckResult Source # | |
Defined in Text.Pandoc.Filter.Plot.Monad.Types (==) :: CheckResult -> CheckResult -> Bool # (/=) :: CheckResult -> CheckResult -> Bool # | |
Semigroup CheckResult Source # | |
Defined in Text.Pandoc.Filter.Plot.Monad.Types (<>) :: CheckResult -> CheckResult -> CheckResult # sconcat :: NonEmpty CheckResult -> CheckResult # stimes :: Integral b => b -> CheckResult -> CheckResult # | |
Monoid CheckResult Source # | |
Defined in Text.Pandoc.Filter.Plot.Monad.Types mempty :: CheckResult # mappend :: CheckResult -> CheckResult -> CheckResult # mconcat :: [CheckResult] -> CheckResult # |
data InclusionKey Source #
Description of any possible inclusion key, both in documents and in configuration files.
DirectoryK | |
CaptionK | |
SaveFormatK | |
WithSourceK | |
CaptionFormatK | |
PreambleK | |
DpiK | |
SourceCodeLabelK | |
StrictModeK | |
ExecutableK | |
CommandLineArgsK | |
DependenciesK | |
FileK | |
MatplotlibTightBBoxK | |
MatplotlibTransparentK |
Instances
Bounded InclusionKey Source # | |
Defined in Text.Pandoc.Filter.Plot.Monad.Types | |
Enum InclusionKey Source # | |
Defined in Text.Pandoc.Filter.Plot.Monad.Types succ :: InclusionKey -> InclusionKey # pred :: InclusionKey -> InclusionKey # toEnum :: Int -> InclusionKey # fromEnum :: InclusionKey -> Int # enumFrom :: InclusionKey -> [InclusionKey] # enumFromThen :: InclusionKey -> InclusionKey -> [InclusionKey] # enumFromTo :: InclusionKey -> InclusionKey -> [InclusionKey] # enumFromThenTo :: InclusionKey -> InclusionKey -> InclusionKey -> [InclusionKey] # | |
Eq InclusionKey Source # | |
Defined in Text.Pandoc.Filter.Plot.Monad.Types (==) :: InclusionKey -> InclusionKey -> Bool # (/=) :: InclusionKey -> InclusionKey -> Bool # | |
Show InclusionKey Source # | Keys that pandoc-plot will look for in code blocks. These are only exported for testing purposes. |
Defined in Text.Pandoc.Filter.Plot.Monad.Types showsPrec :: Int -> InclusionKey -> ShowS # show :: InclusionKey -> String # showList :: [InclusionKey] -> ShowS # |
data FigureSpec Source #
Datatype containing all parameters required to specify a figure.
It is assumed that once a FigureSpec
has been created, no configuration
can overload it; hence, a FigureSpec
completely encodes a particular figure.
FigureSpec | |
|
data OutputSpec Source #
Internal description of all information needed to output a figure.
OutputSpec | |
|
data SaveFormat Source #
Generated figure file format supported by pandoc-plot. Note that not all formats are supported by all toolkits.
PNG | Portable network graphics |
Portable document format | |
SVG | Scalable vector graphics |
JPG | JPEG/JPG compressed image |
EPS | Encapsulated postscript |
GIF | GIF format |
TIF | Tagged image format |
WEBP | WebP image format |
HTML | HTML for interactive plots. |
LaTeX | LaTeX text and pdf graphics |
Instances
extension :: SaveFormat -> String Source #
Save format file extension
inclusionKeys :: [InclusionKey] Source #
List of all keys related to pandoc-plot that can be specified in source material.
data Executable Source #
Executable program and directory where it can be found.
exeFromPath :: FilePath -> Executable Source #
extractPlot :: Text -> Text Source #