{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}

-- |
-- Module      : $header$
-- Description : Pandoc filter to create figures from code blocks using your plotting toolkit of choice
-- Copyright   : (c) Laurent P René de Cotret, 2019 - present
-- License     : GNU GPL, version 2 or above
-- Maintainer  : laurent.decotret@outlook.com
-- Stability   : unstable
-- Portability : portable
--
-- This module defines a Pandoc filter @plotFilter@ and related functions
-- that can be used to walk over a Pandoc document and generate figures from
-- code blocks, using a multitude of plotting toolkits.
--
-- The syntax for code blocks is simple. Code blocks with the appropriate class
-- attribute will trigger the filter, e.g. @matplotlib@ for matplotlib-based Python plots.
--
-- Here is an example, in Markdown, for a plot in MATLAB:
--
-- @
-- This is a paragraph.
-- 
-- ```{.matlabplot}
-- figure()
-- plot([1,2,3,4,5], [1,2,3,4,5], '-k')
-- ```
-- @
--
-- or a using GNUPlot:
--
-- @
-- ```{.gnuplot format=png caption="Sinusoidal function" source=true}
-- sin(x)
-- 
-- set xlabel "x"
-- set ylabel "y"
-- ```
-- @
--
-- The code block will be reworked into a script and the output figure will be captured. Optionally, the source code
--  used to generate the figure will be linked in the caption.
--
-- Here are /some/ of the possible attributes what pandoc-plot understands for ALL toolkits:
--
--     * @directory=...@ : Directory where to save the figure. This path should be specified with
--       respect to the current working directory, and not with respect to the document.
--     * @source=true|false@ : Whether or not to link the source code of this figure in the caption.
--       Ideal for web pages, for example. Default is false.
--     * @format=...@: Format of the generated figure. This can be an extension or an acronym,
--       e.g. @format=PNG@.
--     * @caption="..."@: Specify a plot caption (or alternate text). Format
--       for captions is specified in the documentation for the @Configuration@ type.
--     * @dpi=...@: Specify a value for figure resolution, or dots-per-inch. Certain toolkits ignore this.
--     * @dependencies=[...]@: Specify files/directories on which a figure depends, e.g. data file.
--       Figures will be re-rendered if one of those file/directory changes. These paths should
--       be specified with respect to the current working directory, and not with respect to the document.
--     * @preamble=...@: Path to a file to include before the code block. Ideal to avoid repetition over
--       many figures.
--     * @file=...@: Path to a file from which to read the content of the figure. The content of the
--       code block will be ignored. This path should be specified with respect to the current working
--       directory, and not with respect to the document.
--
-- All attributes are described in the online documentation, linked on the home page. 

module Text.Pandoc.Filter.Plot
  ( -- * Operating on whole Pandoc documents
    plotFilter,
    plotTransform,

    -- * Cleaning output directories
    cleanOutputDirs,

    -- * Runtime configuration
    configuration,
    defaultConfiguration,
    Configuration (..),
    Verbosity (..),
    LogSink (..),
    SaveFormat (..),
    Script,

    -- * Determining available plotting toolkits
    Toolkit (..),
    availableToolkits,
    unavailableToolkits,
    toolkits,
    supportedSaveFormats,

    -- * Version information
    pandocPlotVersion,

    -- * For embedding, testing and internal purposes ONLY. Might change without notice.
    make,
    makeEither,
    PandocPlotError (..),
  )
where

import Control.Concurrent (getNumCapabilities)
import Control.Monad.Reader (when)
import Data.Functor ((<&>))
import Data.Map (singleton)
import Data.Text (Text, pack, unpack)
import Data.Version (Version)
import Paths_pandoc_plot (version)
import Text.Pandoc.Definition (Block, Meta (..), Format, MetaValue (..), Pandoc (..))
import Text.Pandoc.Filter.Plot.Internal
  ( Configuration (..),
    FigureSpec,
    LogSink (..),
    ParseFigureResult (..),
    PlotM,
    RuntimeEnv (envConfig),
    SaveFormat (..),
    Script,
    ScriptResult (..),
    Toolkit (..),
    Verbosity (..),
    asks,
    asksConfig,
    availableToolkits,
    cleanOutputDirs,
    configuration,
    debug,
    defaultConfiguration,
    mapConcurrentlyN,
    parseFigureSpec,
    runPlotM,
    runScriptIfNecessary,
    supportedSaveFormats,
    throwStrictError,
    toFigure,
    toolkits,
    unavailableToolkits,
  )
import Text.Pandoc.Walk (walkM)

-- | Walk over an entire Pandoc document, transforming appropriate code blocks
-- into figures. This function will operate on blocks in parallel if possible.
--
-- If the target conversion format is known, then this function can provide better
-- defaults and error messages. For example, hyperlinks to source code will only be created
-- if the final target format supports it (e.g. HTML).
--
-- Failing to render a figure does not stop the filter, so that you may run the filter
-- on documents without having all necessary toolkits installed. In this case, error
-- messages are printed to stderr, and blocks are left unchanged.
--
-- @since 1.3.0
plotFilter ::
  -- | Configuration for default values
  Configuration ->
  -- | Final converted format, if known
  Maybe Format ->
  -- | Input document
  Pandoc ->
  IO Pandoc
plotFilter :: Configuration -> Maybe Format -> Pandoc -> IO Pandoc
plotFilter Configuration
conf Maybe Format
mfmt (Pandoc Meta
meta [Block]
blocks) = do
  Int
maxproc <- IO Int
getNumCapabilities
  forall a. Maybe Format -> Configuration -> PlotM a -> IO a
runPlotM Maybe Format
mfmt Configuration
conf forall a b. (a -> b) -> a -> b
$ do
    forall (m :: * -> *). (MonadLogger m, MonadIO m) => Text -> m ()
debug forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat [Text
"Starting a new run, utilizing at most ", String -> Text
pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show forall a b. (a -> b) -> a -> b
$ Int
maxproc, Text
" processes."]
    forall (t :: * -> *) a b.
Traversable t =>
Int -> (a -> PlotM b) -> t a -> PlotM (t b)
mapConcurrentlyN Int
maxproc Block -> PlotM Block
make [Block]
blocks forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> Meta -> [Block] -> Pandoc
Pandoc Meta
newMeta
  where
    -- This variable is needed for pandoc's default LaTeX template,
    -- so that graphicx gets used.
    newMeta :: Meta
newMeta = Meta
meta forall a. Semigroup a => a -> a -> a
<> Map Text MetaValue -> Meta
Meta (forall k a. k -> a -> Map k a
singleton Text
"graphics" forall a b. (a -> b) -> a -> b
$ Bool -> MetaValue
MetaBool Bool
True)

-- | Walk over an entire Pandoc document, transforming appropriate code blocks
-- into figures. This function will operate on blocks in parallel if possible.
--
-- Failing to render a figure does not stop the filter, so that you may run the filter
-- on documents without having all necessary toolkits installed. In this case, error
-- messages are printed to stderr, and blocks are left unchanged.
--
-- __Note that this function is DEPRECATED in favour of @plotFilter@. It will be 
-- removed in the next major update (v2+).__
plotTransform ::
  -- | Configuration for default values
  Configuration ->
  -- | Input document
  Pandoc ->
  IO Pandoc
{-# DEPRECATED plotTransform
  [ "plotTransform has been deprecated in favour of plotFilter, which is aware of conversion format."
  , "plotTransform will be removed in an upcoming major update."
  ] 
#-}
plotTransform :: Configuration -> Pandoc -> IO Pandoc
plotTransform Configuration
conf = Configuration -> Maybe Format -> Pandoc -> IO Pandoc
plotFilter Configuration
conf forall a. Maybe a
Nothing

-- | The version of the pandoc-plot package.
--
-- @since 0.8.0.0
pandocPlotVersion :: Version
pandocPlotVersion :: Version
pandocPlotVersion = Version
version

-- | Try to process the block with `pandoc-plot`. If a failure happens (or the block)
-- was not meant to become a figure, return the block as-is unless running in strict mode. 
-- In strict mode, any failure (for example, due to a missing plotting toolkit) will halt execution.
--
-- New in version 1.2.0: this function will detect nested code blocks, for example in @Div@ blocks.
make :: Block -> PlotM Block
make :: Block -> PlotM Block
make = forall a b (m :: * -> *).
(Walkable a b, Monad m, Applicative m, Functor m) =>
(a -> m a) -> b -> m b
walkM forall a b. (a -> b) -> a -> b
$ \Block
blk -> forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Block -> PandocPlotError -> PlotM Block
onError Block
blk) forall (m :: * -> *) a. Monad m => a -> m a
return forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Block -> PlotM (Either PandocPlotError Block)
makeEither Block
blk
  where
    onError :: Block -> PandocPlotError -> PlotM Block
    onError :: Block -> PandocPlotError -> PlotM Block
onError Block
b PandocPlotError
e = do
      StateT PlotState (ReaderT RuntimeEnv IO) ()
-> StateT PlotState (ReaderT RuntimeEnv IO) ()
whenStrict forall a b. (a -> b) -> a -> b
$ Text -> StateT PlotState (ReaderT RuntimeEnv IO) ()
throwStrictError (String -> Text
pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show forall a b. (a -> b) -> a -> b
$ PandocPlotError
e)
      forall (m :: * -> *) a. Monad m => a -> m a
return Block
b
    
    whenStrict :: StateT PlotState (ReaderT RuntimeEnv IO) ()
-> StateT PlotState (ReaderT RuntimeEnv IO) ()
whenStrict StateT PlotState (ReaderT RuntimeEnv IO) ()
f = forall a. (Configuration -> a) -> PlotM a
asksConfig Configuration -> Bool
strictMode forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
s -> forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
s StateT PlotState (ReaderT RuntimeEnv IO) ()
f

-- | Try to process the block with `pandoc-plot`, documenting the error.
-- This function does not transform code blocks nested in
-- other blocks (e.g. @Divs@)
makeEither :: Block -> PlotM (Either PandocPlotError Block)
makeEither :: Block -> PlotM (Either PandocPlotError Block)
makeEither Block
block =
  Block -> PlotM ParseFigureResult
parseFigureSpec Block
block
    forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
      ParseFigureResult
NotAFigure -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. b -> Either a b
Right Block
block
      PFigure FigureSpec
fs -> FigureSpec -> PlotM ScriptResult
runScriptIfNecessary FigureSpec
fs forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FigureSpec -> ScriptResult -> PlotM (Either PandocPlotError Block)
handleResult FigureSpec
fs
      MissingToolkit Toolkit
tk -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ Toolkit -> PandocPlotError
ToolkitNotInstalledError Toolkit
tk
      UnsupportedSaveFormat Toolkit
tk SaveFormat
sv -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ SaveFormat -> Toolkit -> PandocPlotError
IncompatibleSaveFormatError SaveFormat
sv Toolkit
tk
  where
    -- Logging of errors has been taken care of in @runScriptIfNecessary@
    handleResult :: FigureSpec -> ScriptResult -> PlotM (Either PandocPlotError Block)
    handleResult :: FigureSpec -> ScriptResult -> PlotM (Either PandocPlotError Block)
handleResult FigureSpec
_ (ScriptFailure Text
cmd Int
code Text
_) = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left (Text -> Int -> PandocPlotError
ScriptRuntimeError Text
cmd Int
code)
    handleResult FigureSpec
_ (ScriptChecksFailed Text
msg) = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left (Text -> PandocPlotError
ScriptChecksFailedError Text
msg)
    handleResult FigureSpec
spec ScriptResult
ScriptSuccess = forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks RuntimeEnv -> Configuration
envConfig forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Configuration
c -> forall a b. b -> Either a b
Right forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Format -> FigureSpec -> PlotM Block
toFigure (Configuration -> Format
captionFormat Configuration
c) FigureSpec
spec

data PandocPlotError
  = ScriptRuntimeError Text Int
  | ScriptChecksFailedError Text
  | ToolkitNotInstalledError Toolkit
  | IncompatibleSaveFormatError SaveFormat Toolkit

instance Show PandocPlotError where
  show :: PandocPlotError -> String
show (ScriptRuntimeError Text
_ Int
exitcode) = String
"ERROR (pandoc-plot) The script failed with exit code " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show Int
exitcode forall a. Semigroup a => a -> a -> a
<> String
"."
  show (ScriptChecksFailedError Text
msg) = String
"ERROR (pandoc-plot) A script check failed with message: " forall a. Semigroup a => a -> a -> a
<> Text -> String
unpack Text
msg forall a. Semigroup a => a -> a -> a
<> String
"."
  show (ToolkitNotInstalledError Toolkit
tk) = String
"ERROR (pandoc-plot) The " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show Toolkit
tk forall a. Semigroup a => a -> a -> a
<> String
" toolkit is required but not installed."
  show (IncompatibleSaveFormatError SaveFormat
tk Toolkit
sv) = String
"ERROR (pandoc-plot) Save format " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show Toolkit
sv forall a. Semigroup a => a -> a -> a
<> String
" not supported by the " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show SaveFormat
tk forall a. Semigroup a => a -> a -> a
<> String
" toolkit."