pandoc-plot-1.0.2.0: A Pandoc filter to include figures generated from code blocks using your plotting toolkit of choice.
Copyright(c) Laurent P René de Cotret 2019 - 2021
LicenseGNU GPL, version 2 or above
Maintainerlaurent.decotret@outlook.com
Stabilityinternal
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Text.Pandoc.Filter.Plot.Internal

Description

This module re-exports internal pandoc-plot functionality. The external use of content from this module is discouraged.

Synopsis

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.

Constructors

OutputSpec 

Fields

data Executable Source #

Executable program and directory where it can be found.

Constructors

Executable FilePath Text 

data ScriptResult Source #

Possible result of running a script

Instances

Instances details
Show ScriptResult Source # 
Instance details

Defined in Text.Pandoc.Filter.Plot.Scripting

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 (Maybe FigureSpec) Source #

Determine inclusion specifications from Block attributes. If an environment is detected, but the save format is incompatible, an error will be thrown.

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.

Constructors

Configuration 

Fields

type PlotM a = StateT PlotState (ReaderT RuntimeEnv IO) a Source #

pandoc-plot monad

data RuntimeEnv Source #

Constructors

RuntimeEnv 

Fields

data PlotState Source #

Constructors

PlotState (MVar (Map FilePath FileHash)) (MVar (Map Toolkit (Maybe Renderer))) 

runPlotM :: Configuration -> PlotM a -> IO a Source #

Evaluate a PlotM action.

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

whenStrict :: PlotM () -> PlotM () Source #

Conditional execution of a PlotM action if pandoc-plot is run in strict mode.

throwError :: Text -> PlotM () Source #

Throw an error that halts the execution of pandoc-plot

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

data Verbosity Source #

Verbosity of the logger.

Constructors

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

Instances details
Bounded Verbosity Source # 
Instance details

Defined in Text.Pandoc.Filter.Plot.Monad.Logging

Enum Verbosity Source # 
Instance details

Defined in Text.Pandoc.Filter.Plot.Monad.Logging

Eq Verbosity Source # 
Instance details

Defined in Text.Pandoc.Filter.Plot.Monad.Logging

Ord Verbosity Source # 
Instance details

Defined in Text.Pandoc.Filter.Plot.Monad.Logging

Show Verbosity Source # 
Instance details

Defined in Text.Pandoc.Filter.Plot.Monad.Logging

IsString Verbosity Source # 
Instance details

Defined in Text.Pandoc.Filter.Plot.Monad.Logging

FromJSON Verbosity Source # 
Instance details

Defined in Text.Pandoc.Filter.Plot.Monad.Logging

data LogSink Source #

Description of the possible ways to sink log messages.

Constructors

StdErr

Standard error stream.

LogFile FilePath

Appended to file.

Instances

Instances details
Eq LogSink Source # 
Instance details

Defined in Text.Pandoc.Filter.Plot.Monad.Logging

Methods

(==) :: LogSink -> LogSink -> Bool #

(/=) :: LogSink -> LogSink -> Bool #

Show LogSink Source # 
Instance details

Defined in Text.Pandoc.Filter.Plot.Monad.Logging

err :: Text -> PlotM () Source #

Lifting and other monadic operations

liftIO :: MonadIO m => IO a -> m a #

Lift a computation from the IO monad.

ask :: MonadReader r m => m r #

Retrieves the monad environment.

asks #

Arguments

:: 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.

silence :: PlotM a -> PlotM a Source #

Modify the runtime environment to be silent.

Base types

data Toolkit Source #

Enumeration of supported toolkits

Instances

Instances details
Bounded Toolkit Source # 
Instance details

Defined in Text.Pandoc.Filter.Plot.Monad.Types

Enum Toolkit Source # 
Instance details

Defined in Text.Pandoc.Filter.Plot.Monad.Types

Eq Toolkit Source # 
Instance details

Defined in Text.Pandoc.Filter.Plot.Monad.Types

Methods

(==) :: Toolkit -> Toolkit -> Bool #

(/=) :: Toolkit -> Toolkit -> Bool #

Ord Toolkit Source # 
Instance details

Defined in Text.Pandoc.Filter.Plot.Monad.Types

Show Toolkit Source #

This instance should only be used to display toolkit names

Instance details

Defined in Text.Pandoc.Filter.Plot.Monad.Types

Generic Toolkit Source # 
Instance details

Defined in Text.Pandoc.Filter.Plot.Monad.Types

Associated Types

type Rep Toolkit :: Type -> Type #

Methods

from :: Toolkit -> Rep Toolkit x #

to :: Rep Toolkit x -> Toolkit #

type Rep Toolkit Source # 
Instance details

Defined in Text.Pandoc.Filter.Plot.Monad.Types

type Rep Toolkit = D1 ('MetaData "Toolkit" "Text.Pandoc.Filter.Plot.Monad.Types" "pandoc-plot-1.0.2.0-GgIxq71JBtyKpMstRJsx0G" 'False) (((C1 ('MetaCons "Matplotlib" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Matlab" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PlotlyPython" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PlotlyR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mathematica" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Octave" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GGPlot2" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GNUPlot" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Graphviz" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Bokeh" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Plotsjl" 'PrefixI 'False) (U1 :: Type -> Type)))))

type Script = Text Source #

Source context for plotting scripts

data InclusionKey Source #

Description of any possible inclusion key, both in documents and in configuration files.

data FigureSpec Source #

Datatype containing all parameters required to run pandoc-plot.

It is assumed that once a FigureSpec has been created, no configuration can overload it; hence, a FigureSpec completely encodes a particular figure.

Constructors

FigureSpec 

Fields

data OutputSpec Source #

Internal description of all information needed to output a figure.

Constructors

OutputSpec 

Fields

data SaveFormat Source #

Generated figure file format supported by pandoc-plot. Note that not all formats are supported by all toolkits.

Constructors

PNG

Portable network graphics

PDF

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.

Instances

Instances details
Bounded SaveFormat Source # 
Instance details

Defined in Text.Pandoc.Filter.Plot.Monad.Types

Enum SaveFormat Source # 
Instance details

Defined in Text.Pandoc.Filter.Plot.Monad.Types

Eq SaveFormat Source # 
Instance details

Defined in Text.Pandoc.Filter.Plot.Monad.Types

Show SaveFormat Source # 
Instance details

Defined in Text.Pandoc.Filter.Plot.Monad.Types

IsString SaveFormat Source # 
Instance details

Defined in Text.Pandoc.Filter.Plot.Monad.Types

Generic SaveFormat Source # 
Instance details

Defined in Text.Pandoc.Filter.Plot.Monad.Types

Associated Types

type Rep SaveFormat :: Type -> Type #

ToJSON SaveFormat Source # 
Instance details

Defined in Text.Pandoc.Filter.Plot.Monad.Types

FromJSON SaveFormat Source # 
Instance details

Defined in Text.Pandoc.Filter.Plot.Monad.Types

type Rep SaveFormat Source # 
Instance details

Defined in Text.Pandoc.Filter.Plot.Monad.Types

type Rep SaveFormat = D1 ('MetaData "SaveFormat" "Text.Pandoc.Filter.Plot.Monad.Types" "pandoc-plot-1.0.2.0-GgIxq71JBtyKpMstRJsx0G" 'False) (((C1 ('MetaCons "PNG" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PDF" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SVG" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "JPG" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "EPS" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GIF" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TIF" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "WEBP" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HTML" 'PrefixI 'False) (U1 :: Type -> Type)))))

cls :: Toolkit -> Text Source #

Class name which will trigger the filter

extension :: SaveFormat -> String Source #

Save format file extension

toolkits :: [Toolkit] Source #

List of supported toolkits.

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.

Constructors

Executable FilePath Text 

extractPlot :: Text -> Text Source #

Extract the plot-relevant content from inside of a full HTML document. Scripts contained in the head tag are extracted, as well as the entirety of the body tag.

toFigure Source #

Arguments

:: Format

text format of the caption

-> FigureSpec 
-> PlotM Block 

Convert a FigureSpec to a Pandoc figure component. Note that the script to generate figure files must still be run in another function.