{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module Text.Pandoc.Filter.Plot.Configuration
( configuration,
configurationPathMeta,
defaultConfiguration,
)
where
import Data.Text (Text, pack, unpack)
import qualified Data.Text.IO as TIO
import Data.Yaml (FromJSON (parseJSON), Value (Null, Object), (.!=), (.:?))
import Data.Yaml.Config (ignoreEnv, loadYamlSettings)
import System.FilePath (normalise)
import Text.Pandoc.Definition (Format (..), Inline (..), MetaValue (..), Pandoc (..), lookupMeta)
import Text.Pandoc.Filter.Plot.Monad
configuration :: FilePath -> IO Configuration
configuration :: FilePath -> IO Configuration
configuration FilePath
fp = [FilePath] -> [Value] -> EnvUsage -> IO ConfigPrecursor
forall settings.
FromJSON settings =>
[FilePath] -> [Value] -> EnvUsage -> IO settings
loadYamlSettings [FilePath -> FilePath
normalise FilePath
fp] [] EnvUsage
ignoreEnv IO ConfigPrecursor
-> (ConfigPrecursor -> IO Configuration) -> IO Configuration
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ConfigPrecursor -> IO Configuration
renderConfig
defaultConfiguration :: Configuration
defaultConfiguration :: Configuration
defaultConfiguration =
Configuration :: FilePath
-> Bool
-> Int
-> SaveFormat
-> [FilePath]
-> Format
-> Text
-> Bool
-> Verbosity
-> LogSink
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> FilePath
-> FilePath
-> FilePath
-> FilePath
-> FilePath
-> FilePath
-> FilePath
-> FilePath
-> FilePath
-> FilePath
-> FilePath
-> FilePath
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Bool
-> Configuration
Configuration
{ defaultDirectory :: FilePath
defaultDirectory = FilePath
"plots/",
defaultWithSource :: Bool
defaultWithSource = Bool
False,
defaultDPI :: Int
defaultDPI = Int
80,
defaultSaveFormat :: SaveFormat
defaultSaveFormat = SaveFormat
PNG,
defaultDependencies :: [FilePath]
defaultDependencies = [FilePath]
forall a. Monoid a => a
mempty,
captionFormat :: Format
captionFormat = Text -> Format
Format Text
"markdown+tex_math_dollars",
sourceCodeLabel :: Text
sourceCodeLabel = Text
"Source code",
strictMode :: Bool
strictMode = Bool
False,
logVerbosity :: Verbosity
logVerbosity = Verbosity
Warning,
logSink :: LogSink
logSink = LogSink
StdErr,
matplotlibPreamble :: Text
matplotlibPreamble = Text
forall a. Monoid a => a
mempty,
plotlyPythonPreamble :: Text
plotlyPythonPreamble = Text
forall a. Monoid a => a
mempty,
plotlyRPreamble :: Text
plotlyRPreamble = Text
forall a. Monoid a => a
mempty,
matlabPreamble :: Text
matlabPreamble = Text
forall a. Monoid a => a
mempty,
mathematicaPreamble :: Text
mathematicaPreamble = Text
forall a. Monoid a => a
mempty,
octavePreamble :: Text
octavePreamble = Text
forall a. Monoid a => a
mempty,
ggplot2Preamble :: Text
ggplot2Preamble = Text
forall a. Monoid a => a
mempty,
gnuplotPreamble :: Text
gnuplotPreamble = Text
forall a. Monoid a => a
mempty,
graphvizPreamble :: Text
graphvizPreamble = Text
forall a. Monoid a => a
mempty,
bokehPreamble :: Text
bokehPreamble = Text
forall a. Monoid a => a
mempty,
plotsjlPreamble :: Text
plotsjlPreamble = Text
forall a. Monoid a => a
mempty,
plantumlPreamble :: Text
plantumlPreamble = Text
forall a. Monoid a => a
mempty,
matplotlibExe :: FilePath
matplotlibExe = FilePath
python,
matlabExe :: FilePath
matlabExe = FilePath
"matlab",
plotlyPythonExe :: FilePath
plotlyPythonExe = FilePath
python,
plotlyRExe :: FilePath
plotlyRExe = FilePath
"Rscript",
mathematicaExe :: FilePath
mathematicaExe = FilePath
"math",
octaveExe :: FilePath
octaveExe = FilePath
"octave",
ggplot2Exe :: FilePath
ggplot2Exe = FilePath
"Rscript",
gnuplotExe :: FilePath
gnuplotExe = FilePath
"gnuplot",
graphvizExe :: FilePath
graphvizExe = FilePath
"dot",
bokehExe :: FilePath
bokehExe = FilePath
python,
plotsjlExe :: FilePath
plotsjlExe = FilePath
"julia",
plantumlExe :: FilePath
plantumlExe = FilePath
"java",
matplotlibCmdArgs :: Text
matplotlibCmdArgs = Text
forall a. Monoid a => a
mempty,
matlabCmdArgs :: Text
matlabCmdArgs = Text
forall a. Monoid a => a
mempty,
plotlyPythonCmdArgs :: Text
plotlyPythonCmdArgs = Text
forall a. Monoid a => a
mempty,
plotlyRCmdArgs :: Text
plotlyRCmdArgs = Text
forall a. Monoid a => a
mempty,
mathematicaCmdArgs :: Text
mathematicaCmdArgs = Text
forall a. Monoid a => a
mempty,
octaveCmdArgs :: Text
octaveCmdArgs = Text
forall a. Monoid a => a
mempty,
ggplot2CmdArgs :: Text
ggplot2CmdArgs = Text
forall a. Monoid a => a
mempty,
gnuplotCmdArgs :: Text
gnuplotCmdArgs = Text
forall a. Monoid a => a
mempty,
graphvizCmdArgs :: Text
graphvizCmdArgs = Text
forall a. Monoid a => a
mempty,
bokehCmdArgs :: Text
bokehCmdArgs = Text
forall a. Monoid a => a
mempty,
plotsjlCmdArgs :: Text
plotsjlCmdArgs = Text
forall a. Monoid a => a
mempty,
plantumlCmdArgs :: Text
plantumlCmdArgs = Text
"-jar plantuml.jar",
matplotlibTightBBox :: Bool
matplotlibTightBBox = Bool
False,
matplotlibTransparent :: Bool
matplotlibTransparent = Bool
False
}
where
python :: FilePath
python = if Bool
isWindows then FilePath
"python" else FilePath
"python3"
configurationPathMeta :: Pandoc -> Maybe FilePath
configurationPathMeta :: Pandoc -> Maybe FilePath
configurationPathMeta (Pandoc Meta
meta [Block]
_) =
Text -> Meta -> Maybe MetaValue
lookupMeta Text
"plot-configuration" Meta
meta Maybe MetaValue -> (MetaValue -> Maybe FilePath) -> Maybe FilePath
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= MetaValue -> Maybe FilePath
getPath
where
getPath :: MetaValue -> Maybe FilePath
getPath (MetaString Text
t) = FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just (Text -> FilePath
unpack Text
t)
getPath (MetaInlines [Str Text
s]) = FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just (Text -> FilePath
unpack Text
s)
getPath MetaValue
_ = Maybe FilePath
forall a. Maybe a
Nothing
data ConfigPrecursor = ConfigPrecursor
{ ConfigPrecursor -> FilePath
_defaultDirectory :: !FilePath,
ConfigPrecursor -> Bool
_defaultWithSource :: !Bool,
ConfigPrecursor -> Int
_defaultDPI :: !Int,
ConfigPrecursor -> SaveFormat
_defaultSaveFormat :: !SaveFormat,
ConfigPrecursor -> [FilePath]
_defaultDependencies :: ![FilePath],
ConfigPrecursor -> Format
_captionFormat :: !Format,
ConfigPrecursor -> Text
_sourceCodeLabel :: !Text,
ConfigPrecursor -> Bool
_strictMode :: !Bool,
ConfigPrecursor -> LoggingPrecursor
_logPrec :: !LoggingPrecursor,
ConfigPrecursor -> MatplotlibPrecursor
_matplotlibPrec :: !MatplotlibPrecursor,
ConfigPrecursor -> MatlabPrecursor
_matlabPrec :: !MatlabPrecursor,
ConfigPrecursor -> PlotlyPythonPrecursor
_plotlyPythonPrec :: !PlotlyPythonPrecursor,
ConfigPrecursor -> PlotlyRPrecursor
_plotlyRPrec :: !PlotlyRPrecursor,
ConfigPrecursor -> MathematicaPrecursor
_mathematicaPrec :: !MathematicaPrecursor,
ConfigPrecursor -> OctavePrecursor
_octavePrec :: !OctavePrecursor,
ConfigPrecursor -> GGPlot2Precursor
_ggplot2Prec :: !GGPlot2Precursor,
ConfigPrecursor -> GNUPlotPrecursor
_gnuplotPrec :: !GNUPlotPrecursor,
ConfigPrecursor -> GraphvizPrecursor
_graphvizPrec :: !GraphvizPrecursor,
ConfigPrecursor -> BokehPrecursor
_bokehPrec :: !BokehPrecursor,
ConfigPrecursor -> PlotsjlPrecursor
_plotsjlPrec :: !PlotsjlPrecursor,
ConfigPrecursor -> PlantUMLPrecursor
_plantumlPrec :: !PlantUMLPrecursor
}
defaultConfigPrecursor :: ConfigPrecursor
defaultConfigPrecursor :: ConfigPrecursor
defaultConfigPrecursor =
ConfigPrecursor :: FilePath
-> Bool
-> Int
-> SaveFormat
-> [FilePath]
-> Format
-> Text
-> Bool
-> LoggingPrecursor
-> MatplotlibPrecursor
-> MatlabPrecursor
-> PlotlyPythonPrecursor
-> PlotlyRPrecursor
-> MathematicaPrecursor
-> OctavePrecursor
-> GGPlot2Precursor
-> GNUPlotPrecursor
-> GraphvizPrecursor
-> BokehPrecursor
-> PlotsjlPrecursor
-> PlantUMLPrecursor
-> ConfigPrecursor
ConfigPrecursor
{ _defaultDirectory :: FilePath
_defaultDirectory = Configuration -> FilePath
defaultDirectory Configuration
defaultConfiguration,
_defaultWithSource :: Bool
_defaultWithSource = Configuration -> Bool
defaultWithSource Configuration
defaultConfiguration,
_defaultDPI :: Int
_defaultDPI = Configuration -> Int
defaultDPI Configuration
defaultConfiguration,
_defaultSaveFormat :: SaveFormat
_defaultSaveFormat = Configuration -> SaveFormat
defaultSaveFormat Configuration
defaultConfiguration,
_defaultDependencies :: [FilePath]
_defaultDependencies = Configuration -> [FilePath]
defaultDependencies Configuration
defaultConfiguration,
_captionFormat :: Format
_captionFormat = Configuration -> Format
captionFormat Configuration
defaultConfiguration,
_sourceCodeLabel :: Text
_sourceCodeLabel = Configuration -> Text
sourceCodeLabel Configuration
defaultConfiguration,
_strictMode :: Bool
_strictMode = Configuration -> Bool
strictMode Configuration
defaultConfiguration,
_logPrec :: LoggingPrecursor
_logPrec = Verbosity -> Maybe FilePath -> LoggingPrecursor
LoggingPrecursor (Configuration -> Verbosity
logVerbosity Configuration
defaultConfiguration) Maybe FilePath
forall a. Maybe a
Nothing,
_matplotlibPrec :: MatplotlibPrecursor
_matplotlibPrec = Maybe FilePath
-> Bool -> Bool -> FilePath -> Text -> MatplotlibPrecursor
MatplotlibPrecursor Maybe FilePath
forall a. Maybe a
Nothing (Configuration -> Bool
matplotlibTightBBox Configuration
defaultConfiguration) (Configuration -> Bool
matplotlibTransparent Configuration
defaultConfiguration) (Configuration -> FilePath
matplotlibExe Configuration
defaultConfiguration) (Configuration -> Text
matplotlibCmdArgs Configuration
defaultConfiguration),
_matlabPrec :: MatlabPrecursor
_matlabPrec = Maybe FilePath -> FilePath -> Text -> MatlabPrecursor
MatlabPrecursor Maybe FilePath
forall a. Maybe a
Nothing (Configuration -> FilePath
matlabExe Configuration
defaultConfiguration) (Configuration -> Text
matlabCmdArgs Configuration
defaultConfiguration),
_plotlyPythonPrec :: PlotlyPythonPrecursor
_plotlyPythonPrec = Maybe FilePath -> FilePath -> Text -> PlotlyPythonPrecursor
PlotlyPythonPrecursor Maybe FilePath
forall a. Maybe a
Nothing (Configuration -> FilePath
plotlyPythonExe Configuration
defaultConfiguration) (Configuration -> Text
plotlyPythonCmdArgs Configuration
defaultConfiguration),
_plotlyRPrec :: PlotlyRPrecursor
_plotlyRPrec = Maybe FilePath -> FilePath -> Text -> PlotlyRPrecursor
PlotlyRPrecursor Maybe FilePath
forall a. Maybe a
Nothing (Configuration -> FilePath
plotlyRExe Configuration
defaultConfiguration) (Configuration -> Text
plotlyRCmdArgs Configuration
defaultConfiguration),
_mathematicaPrec :: MathematicaPrecursor
_mathematicaPrec = Maybe FilePath -> FilePath -> Text -> MathematicaPrecursor
MathematicaPrecursor Maybe FilePath
forall a. Maybe a
Nothing (Configuration -> FilePath
mathematicaExe Configuration
defaultConfiguration) (Configuration -> Text
mathematicaCmdArgs Configuration
defaultConfiguration),
_octavePrec :: OctavePrecursor
_octavePrec = Maybe FilePath -> FilePath -> Text -> OctavePrecursor
OctavePrecursor Maybe FilePath
forall a. Maybe a
Nothing (Configuration -> FilePath
octaveExe Configuration
defaultConfiguration) (Configuration -> Text
octaveCmdArgs Configuration
defaultConfiguration),
_ggplot2Prec :: GGPlot2Precursor
_ggplot2Prec = Maybe FilePath -> FilePath -> Text -> GGPlot2Precursor
GGPlot2Precursor Maybe FilePath
forall a. Maybe a
Nothing (Configuration -> FilePath
ggplot2Exe Configuration
defaultConfiguration) (Configuration -> Text
ggplot2CmdArgs Configuration
defaultConfiguration),
_gnuplotPrec :: GNUPlotPrecursor
_gnuplotPrec = Maybe FilePath -> FilePath -> Text -> GNUPlotPrecursor
GNUPlotPrecursor Maybe FilePath
forall a. Maybe a
Nothing (Configuration -> FilePath
gnuplotExe Configuration
defaultConfiguration) (Configuration -> Text
gnuplotCmdArgs Configuration
defaultConfiguration),
_graphvizPrec :: GraphvizPrecursor
_graphvizPrec = Maybe FilePath -> FilePath -> Text -> GraphvizPrecursor
GraphvizPrecursor Maybe FilePath
forall a. Maybe a
Nothing (Configuration -> FilePath
graphvizExe Configuration
defaultConfiguration) (Configuration -> Text
graphvizCmdArgs Configuration
defaultConfiguration),
_bokehPrec :: BokehPrecursor
_bokehPrec = Maybe FilePath -> FilePath -> Text -> BokehPrecursor
BokehPrecursor Maybe FilePath
forall a. Maybe a
Nothing (Configuration -> FilePath
bokehExe Configuration
defaultConfiguration) (Configuration -> Text
bokehCmdArgs Configuration
defaultConfiguration),
_plotsjlPrec :: PlotsjlPrecursor
_plotsjlPrec = Maybe FilePath -> FilePath -> Text -> PlotsjlPrecursor
PlotsjlPrecursor Maybe FilePath
forall a. Maybe a
Nothing (Configuration -> FilePath
plotsjlExe Configuration
defaultConfiguration) (Configuration -> Text
plotsjlCmdArgs Configuration
defaultConfiguration),
_plantumlPrec :: PlantUMLPrecursor
_plantumlPrec = Maybe FilePath -> FilePath -> Text -> PlantUMLPrecursor
PlantUMLPrecursor Maybe FilePath
forall a. Maybe a
Nothing (Configuration -> FilePath
plantumlExe Configuration
defaultConfiguration) (Configuration -> Text
plantumlCmdArgs Configuration
defaultConfiguration)
}
data LoggingPrecursor = LoggingPrecursor
{ LoggingPrecursor -> Verbosity
_logVerbosity :: !Verbosity,
LoggingPrecursor -> Maybe FilePath
_logFilePath :: !(Maybe FilePath)
}
data MatplotlibPrecursor = MatplotlibPrecursor
{ MatplotlibPrecursor -> Maybe FilePath
_matplotlibPreamble :: !(Maybe FilePath),
MatplotlibPrecursor -> Bool
_matplotlibTightBBox :: !Bool,
MatplotlibPrecursor -> Bool
_matplotlibTransparent :: !Bool,
MatplotlibPrecursor -> FilePath
_matplotlibExe :: !FilePath,
MatplotlibPrecursor -> Text
_matplotlibCmdArgs :: !Text
}
data MatlabPrecursor = MatlabPrecursor {MatlabPrecursor -> Maybe FilePath
_matlabPreamble :: !(Maybe FilePath), MatlabPrecursor -> FilePath
_matlabExe :: !FilePath, MatlabPrecursor -> Text
_matlabCmdArgs :: !Text}
data PlotlyPythonPrecursor = PlotlyPythonPrecursor {PlotlyPythonPrecursor -> Maybe FilePath
_plotlyPythonPreamble :: !(Maybe FilePath), PlotlyPythonPrecursor -> FilePath
_plotlyPythonExe :: !FilePath, PlotlyPythonPrecursor -> Text
_plotlyPythonCmdArgs :: !Text}
data PlotlyRPrecursor = PlotlyRPrecursor {PlotlyRPrecursor -> Maybe FilePath
_plotlyRPreamble :: !(Maybe FilePath), PlotlyRPrecursor -> FilePath
_plotlyRExe :: !FilePath, PlotlyRPrecursor -> Text
_plotlyRCmdArgs :: !Text}
data MathematicaPrecursor = MathematicaPrecursor {MathematicaPrecursor -> Maybe FilePath
_mathematicaPreamble :: !(Maybe FilePath), MathematicaPrecursor -> FilePath
_mathematicaExe :: !FilePath, MathematicaPrecursor -> Text
_mathematicaCmdArgs :: !Text}
data OctavePrecursor = OctavePrecursor {OctavePrecursor -> Maybe FilePath
_octavePreamble :: !(Maybe FilePath), OctavePrecursor -> FilePath
_octaveExe :: !FilePath, OctavePrecursor -> Text
_octaveCmdArgs :: !Text}
data GGPlot2Precursor = GGPlot2Precursor {GGPlot2Precursor -> Maybe FilePath
_ggplot2Preamble :: !(Maybe FilePath), GGPlot2Precursor -> FilePath
_ggplot2Exe :: !FilePath, GGPlot2Precursor -> Text
_ggplot2CmdArgs :: !Text}
data GNUPlotPrecursor = GNUPlotPrecursor {GNUPlotPrecursor -> Maybe FilePath
_gnuplotPreamble :: !(Maybe FilePath), GNUPlotPrecursor -> FilePath
_gnuplotExe :: !FilePath, GNUPlotPrecursor -> Text
_gnuplotCmdArgs :: !Text}
data GraphvizPrecursor = GraphvizPrecursor {GraphvizPrecursor -> Maybe FilePath
_graphvizPreamble :: !(Maybe FilePath), GraphvizPrecursor -> FilePath
_graphvizExe :: !FilePath, GraphvizPrecursor -> Text
_graphvizCmdArgs :: !Text}
data BokehPrecursor = BokehPrecursor {BokehPrecursor -> Maybe FilePath
_bokehPreamble :: !(Maybe FilePath), BokehPrecursor -> FilePath
_bokehExe :: !FilePath, BokehPrecursor -> Text
_bokehCmdArgs :: !Text}
data PlotsjlPrecursor = PlotsjlPrecursor {PlotsjlPrecursor -> Maybe FilePath
_plotsjlPreamble :: !(Maybe FilePath), PlotsjlPrecursor -> FilePath
_plotsjlExe :: !FilePath, PlotsjlPrecursor -> Text
_plotsjlCmdArgs :: !Text}
data PlantUMLPrecursor = PlantUMLPrecursor {PlantUMLPrecursor -> Maybe FilePath
_plantumlPreamble :: !(Maybe FilePath), PlantUMLPrecursor -> FilePath
_plantumlExe :: !FilePath, PlantUMLPrecursor -> Text
_plantumlCmdArgs :: !Text}
instance FromJSON LoggingPrecursor where
parseJSON :: Value -> Parser LoggingPrecursor
parseJSON (Object Object
v) =
Verbosity -> Maybe FilePath -> LoggingPrecursor
LoggingPrecursor (Verbosity -> Maybe FilePath -> LoggingPrecursor)
-> Parser Verbosity -> Parser (Maybe FilePath -> LoggingPrecursor)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser (Maybe Verbosity)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"verbosity" Parser (Maybe Verbosity) -> Verbosity -> Parser Verbosity
forall a. Parser (Maybe a) -> a -> Parser a
.!= Configuration -> Verbosity
logVerbosity Configuration
defaultConfiguration
Parser (Maybe FilePath -> LoggingPrecursor)
-> Parser (Maybe FilePath) -> Parser LoggingPrecursor
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"filepath"
parseJSON Value
_ = FilePath -> Parser LoggingPrecursor
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail (FilePath -> Parser LoggingPrecursor)
-> FilePath -> Parser LoggingPrecursor
forall a b. (a -> b) -> a -> b
$ [FilePath] -> FilePath
forall a. Monoid a => [a] -> a
mconcat [FilePath
"Could not parse logging configuration. "]
instance FromJSON MatplotlibPrecursor where
parseJSON :: Value -> Parser MatplotlibPrecursor
parseJSON (Object Object
v) =
Maybe FilePath
-> Bool -> Bool -> FilePath -> Text -> MatplotlibPrecursor
MatplotlibPrecursor
(Maybe FilePath
-> Bool -> Bool -> FilePath -> Text -> MatplotlibPrecursor)
-> Parser (Maybe FilePath)
-> Parser (Bool -> Bool -> FilePath -> Text -> MatplotlibPrecursor)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
PreambleK
Parser (Bool -> Bool -> FilePath -> Text -> MatplotlibPrecursor)
-> Parser Bool
-> Parser (Bool -> FilePath -> Text -> MatplotlibPrecursor)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
MatplotlibTightBBoxK Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Configuration -> Bool
matplotlibTightBBox Configuration
defaultConfiguration
Parser (Bool -> FilePath -> Text -> MatplotlibPrecursor)
-> Parser Bool -> Parser (FilePath -> Text -> MatplotlibPrecursor)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
MatplotlibTransparentK Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Configuration -> Bool
matplotlibTransparent Configuration
defaultConfiguration
Parser (FilePath -> Text -> MatplotlibPrecursor)
-> Parser FilePath -> Parser (Text -> MatplotlibPrecursor)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
ExecutableK Parser (Maybe FilePath) -> FilePath -> Parser FilePath
forall a. Parser (Maybe a) -> a -> Parser a
.!= Configuration -> FilePath
matplotlibExe Configuration
defaultConfiguration
Parser (Text -> MatplotlibPrecursor)
-> Parser Text -> Parser MatplotlibPrecursor
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
CommandLineArgsK Parser (Maybe Text) -> Text -> Parser Text
forall a. Parser (Maybe a) -> a -> Parser a
.!= Configuration -> Text
matplotlibCmdArgs Configuration
defaultConfiguration
parseJSON Value
_ = FilePath -> Parser MatplotlibPrecursor
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail (FilePath -> Parser MatplotlibPrecursor)
-> FilePath -> Parser MatplotlibPrecursor
forall a b. (a -> b) -> a -> b
$ [FilePath] -> FilePath
forall a. Monoid a => [a] -> a
mconcat [FilePath
"Could not parse ", Toolkit -> FilePath
forall a. Show a => a -> FilePath
show Toolkit
Matplotlib, FilePath
" configuration."]
instance FromJSON MatlabPrecursor where
parseJSON :: Value -> Parser MatlabPrecursor
parseJSON (Object Object
v) = Maybe FilePath -> FilePath -> Text -> MatlabPrecursor
MatlabPrecursor (Maybe FilePath -> FilePath -> Text -> MatlabPrecursor)
-> Parser (Maybe FilePath)
-> Parser (FilePath -> Text -> MatlabPrecursor)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
PreambleK Parser (FilePath -> Text -> MatlabPrecursor)
-> Parser FilePath -> Parser (Text -> MatlabPrecursor)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
ExecutableK Parser (Maybe FilePath) -> FilePath -> Parser FilePath
forall a. Parser (Maybe a) -> a -> Parser a
.!= Configuration -> FilePath
matlabExe Configuration
defaultConfiguration Parser (Text -> MatlabPrecursor)
-> Parser Text -> Parser MatlabPrecursor
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
CommandLineArgsK Parser (Maybe Text) -> Text -> Parser Text
forall a. Parser (Maybe a) -> a -> Parser a
.!= Configuration -> Text
matlabCmdArgs Configuration
defaultConfiguration
parseJSON Value
_ = FilePath -> Parser MatlabPrecursor
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail (FilePath -> Parser MatlabPrecursor)
-> FilePath -> Parser MatlabPrecursor
forall a b. (a -> b) -> a -> b
$ [FilePath] -> FilePath
forall a. Monoid a => [a] -> a
mconcat [FilePath
"Could not parse ", Toolkit -> FilePath
forall a. Show a => a -> FilePath
show Toolkit
Matlab, FilePath
" configuration."]
instance FromJSON PlotlyPythonPrecursor where
parseJSON :: Value -> Parser PlotlyPythonPrecursor
parseJSON (Object Object
v) = Maybe FilePath -> FilePath -> Text -> PlotlyPythonPrecursor
PlotlyPythonPrecursor (Maybe FilePath -> FilePath -> Text -> PlotlyPythonPrecursor)
-> Parser (Maybe FilePath)
-> Parser (FilePath -> Text -> PlotlyPythonPrecursor)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
PreambleK Parser (FilePath -> Text -> PlotlyPythonPrecursor)
-> Parser FilePath -> Parser (Text -> PlotlyPythonPrecursor)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
ExecutableK Parser (Maybe FilePath) -> FilePath -> Parser FilePath
forall a. Parser (Maybe a) -> a -> Parser a
.!= Configuration -> FilePath
plotlyPythonExe Configuration
defaultConfiguration Parser (Text -> PlotlyPythonPrecursor)
-> Parser Text -> Parser PlotlyPythonPrecursor
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
CommandLineArgsK Parser (Maybe Text) -> Text -> Parser Text
forall a. Parser (Maybe a) -> a -> Parser a
.!= Configuration -> Text
plotlyPythonCmdArgs Configuration
defaultConfiguration
parseJSON Value
_ = FilePath -> Parser PlotlyPythonPrecursor
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail (FilePath -> Parser PlotlyPythonPrecursor)
-> FilePath -> Parser PlotlyPythonPrecursor
forall a b. (a -> b) -> a -> b
$ [FilePath] -> FilePath
forall a. Monoid a => [a] -> a
mconcat [FilePath
"Could not parse ", Toolkit -> FilePath
forall a. Show a => a -> FilePath
show Toolkit
PlotlyPython, FilePath
" configuration."]
instance FromJSON PlotlyRPrecursor where
parseJSON :: Value -> Parser PlotlyRPrecursor
parseJSON (Object Object
v) = Maybe FilePath -> FilePath -> Text -> PlotlyRPrecursor
PlotlyRPrecursor (Maybe FilePath -> FilePath -> Text -> PlotlyRPrecursor)
-> Parser (Maybe FilePath)
-> Parser (FilePath -> Text -> PlotlyRPrecursor)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
PreambleK Parser (FilePath -> Text -> PlotlyRPrecursor)
-> Parser FilePath -> Parser (Text -> PlotlyRPrecursor)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
ExecutableK Parser (Maybe FilePath) -> FilePath -> Parser FilePath
forall a. Parser (Maybe a) -> a -> Parser a
.!= Configuration -> FilePath
plotlyRExe Configuration
defaultConfiguration Parser (Text -> PlotlyRPrecursor)
-> Parser Text -> Parser PlotlyRPrecursor
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
CommandLineArgsK Parser (Maybe Text) -> Text -> Parser Text
forall a. Parser (Maybe a) -> a -> Parser a
.!= Configuration -> Text
plotlyRCmdArgs Configuration
defaultConfiguration
parseJSON Value
_ = FilePath -> Parser PlotlyRPrecursor
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail (FilePath -> Parser PlotlyRPrecursor)
-> FilePath -> Parser PlotlyRPrecursor
forall a b. (a -> b) -> a -> b
$ [FilePath] -> FilePath
forall a. Monoid a => [a] -> a
mconcat [FilePath
"Could not parse ", Toolkit -> FilePath
forall a. Show a => a -> FilePath
show Toolkit
PlotlyR, FilePath
" configuration."]
instance FromJSON MathematicaPrecursor where
parseJSON :: Value -> Parser MathematicaPrecursor
parseJSON (Object Object
v) = Maybe FilePath -> FilePath -> Text -> MathematicaPrecursor
MathematicaPrecursor (Maybe FilePath -> FilePath -> Text -> MathematicaPrecursor)
-> Parser (Maybe FilePath)
-> Parser (FilePath -> Text -> MathematicaPrecursor)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
PreambleK Parser (FilePath -> Text -> MathematicaPrecursor)
-> Parser FilePath -> Parser (Text -> MathematicaPrecursor)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
ExecutableK Parser (Maybe FilePath) -> FilePath -> Parser FilePath
forall a. Parser (Maybe a) -> a -> Parser a
.!= Configuration -> FilePath
mathematicaExe Configuration
defaultConfiguration Parser (Text -> MathematicaPrecursor)
-> Parser Text -> Parser MathematicaPrecursor
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
CommandLineArgsK Parser (Maybe Text) -> Text -> Parser Text
forall a. Parser (Maybe a) -> a -> Parser a
.!= Configuration -> Text
mathematicaCmdArgs Configuration
defaultConfiguration
parseJSON Value
_ = FilePath -> Parser MathematicaPrecursor
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail (FilePath -> Parser MathematicaPrecursor)
-> FilePath -> Parser MathematicaPrecursor
forall a b. (a -> b) -> a -> b
$ [FilePath] -> FilePath
forall a. Monoid a => [a] -> a
mconcat [FilePath
"Could not parse ", Toolkit -> FilePath
forall a. Show a => a -> FilePath
show Toolkit
Mathematica, FilePath
" configuration."]
instance FromJSON OctavePrecursor where
parseJSON :: Value -> Parser OctavePrecursor
parseJSON (Object Object
v) = Maybe FilePath -> FilePath -> Text -> OctavePrecursor
OctavePrecursor (Maybe FilePath -> FilePath -> Text -> OctavePrecursor)
-> Parser (Maybe FilePath)
-> Parser (FilePath -> Text -> OctavePrecursor)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
PreambleK Parser (FilePath -> Text -> OctavePrecursor)
-> Parser FilePath -> Parser (Text -> OctavePrecursor)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
ExecutableK Parser (Maybe FilePath) -> FilePath -> Parser FilePath
forall a. Parser (Maybe a) -> a -> Parser a
.!= Configuration -> FilePath
octaveExe Configuration
defaultConfiguration Parser (Text -> OctavePrecursor)
-> Parser Text -> Parser OctavePrecursor
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
CommandLineArgsK Parser (Maybe Text) -> Text -> Parser Text
forall a. Parser (Maybe a) -> a -> Parser a
.!= Configuration -> Text
octaveCmdArgs Configuration
defaultConfiguration
parseJSON Value
_ = FilePath -> Parser OctavePrecursor
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail (FilePath -> Parser OctavePrecursor)
-> FilePath -> Parser OctavePrecursor
forall a b. (a -> b) -> a -> b
$ [FilePath] -> FilePath
forall a. Monoid a => [a] -> a
mconcat [FilePath
"Could not parse ", Toolkit -> FilePath
forall a. Show a => a -> FilePath
show Toolkit
Octave, FilePath
" configuration."]
instance FromJSON GGPlot2Precursor where
parseJSON :: Value -> Parser GGPlot2Precursor
parseJSON (Object Object
v) = Maybe FilePath -> FilePath -> Text -> GGPlot2Precursor
GGPlot2Precursor (Maybe FilePath -> FilePath -> Text -> GGPlot2Precursor)
-> Parser (Maybe FilePath)
-> Parser (FilePath -> Text -> GGPlot2Precursor)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
PreambleK Parser (FilePath -> Text -> GGPlot2Precursor)
-> Parser FilePath -> Parser (Text -> GGPlot2Precursor)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
ExecutableK Parser (Maybe FilePath) -> FilePath -> Parser FilePath
forall a. Parser (Maybe a) -> a -> Parser a
.!= Configuration -> FilePath
ggplot2Exe Configuration
defaultConfiguration Parser (Text -> GGPlot2Precursor)
-> Parser Text -> Parser GGPlot2Precursor
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
CommandLineArgsK Parser (Maybe Text) -> Text -> Parser Text
forall a. Parser (Maybe a) -> a -> Parser a
.!= Configuration -> Text
ggplot2CmdArgs Configuration
defaultConfiguration
parseJSON Value
_ = FilePath -> Parser GGPlot2Precursor
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail (FilePath -> Parser GGPlot2Precursor)
-> FilePath -> Parser GGPlot2Precursor
forall a b. (a -> b) -> a -> b
$ [FilePath] -> FilePath
forall a. Monoid a => [a] -> a
mconcat [FilePath
"Could not parse ", Toolkit -> FilePath
forall a. Show a => a -> FilePath
show Toolkit
GGPlot2, FilePath
" configuration."]
instance FromJSON GNUPlotPrecursor where
parseJSON :: Value -> Parser GNUPlotPrecursor
parseJSON (Object Object
v) = Maybe FilePath -> FilePath -> Text -> GNUPlotPrecursor
GNUPlotPrecursor (Maybe FilePath -> FilePath -> Text -> GNUPlotPrecursor)
-> Parser (Maybe FilePath)
-> Parser (FilePath -> Text -> GNUPlotPrecursor)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
PreambleK Parser (FilePath -> Text -> GNUPlotPrecursor)
-> Parser FilePath -> Parser (Text -> GNUPlotPrecursor)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
ExecutableK Parser (Maybe FilePath) -> FilePath -> Parser FilePath
forall a. Parser (Maybe a) -> a -> Parser a
.!= Configuration -> FilePath
gnuplotExe Configuration
defaultConfiguration Parser (Text -> GNUPlotPrecursor)
-> Parser Text -> Parser GNUPlotPrecursor
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
CommandLineArgsK Parser (Maybe Text) -> Text -> Parser Text
forall a. Parser (Maybe a) -> a -> Parser a
.!= Configuration -> Text
gnuplotCmdArgs Configuration
defaultConfiguration
parseJSON Value
_ = FilePath -> Parser GNUPlotPrecursor
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail (FilePath -> Parser GNUPlotPrecursor)
-> FilePath -> Parser GNUPlotPrecursor
forall a b. (a -> b) -> a -> b
$ [FilePath] -> FilePath
forall a. Monoid a => [a] -> a
mconcat [FilePath
"Could not parse ", Toolkit -> FilePath
forall a. Show a => a -> FilePath
show Toolkit
GNUPlot, FilePath
" configuration."]
instance FromJSON GraphvizPrecursor where
parseJSON :: Value -> Parser GraphvizPrecursor
parseJSON (Object Object
v) = Maybe FilePath -> FilePath -> Text -> GraphvizPrecursor
GraphvizPrecursor (Maybe FilePath -> FilePath -> Text -> GraphvizPrecursor)
-> Parser (Maybe FilePath)
-> Parser (FilePath -> Text -> GraphvizPrecursor)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
PreambleK Parser (FilePath -> Text -> GraphvizPrecursor)
-> Parser FilePath -> Parser (Text -> GraphvizPrecursor)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
ExecutableK Parser (Maybe FilePath) -> FilePath -> Parser FilePath
forall a. Parser (Maybe a) -> a -> Parser a
.!= Configuration -> FilePath
graphvizExe Configuration
defaultConfiguration Parser (Text -> GraphvizPrecursor)
-> Parser Text -> Parser GraphvizPrecursor
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
CommandLineArgsK Parser (Maybe Text) -> Text -> Parser Text
forall a. Parser (Maybe a) -> a -> Parser a
.!= Configuration -> Text
graphvizCmdArgs Configuration
defaultConfiguration
parseJSON Value
_ = FilePath -> Parser GraphvizPrecursor
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail (FilePath -> Parser GraphvizPrecursor)
-> FilePath -> Parser GraphvizPrecursor
forall a b. (a -> b) -> a -> b
$ [FilePath] -> FilePath
forall a. Monoid a => [a] -> a
mconcat [FilePath
"Could not parse ", Toolkit -> FilePath
forall a. Show a => a -> FilePath
show Toolkit
Graphviz, FilePath
" configuration."]
instance FromJSON BokehPrecursor where
parseJSON :: Value -> Parser BokehPrecursor
parseJSON (Object Object
v) = Maybe FilePath -> FilePath -> Text -> BokehPrecursor
BokehPrecursor (Maybe FilePath -> FilePath -> Text -> BokehPrecursor)
-> Parser (Maybe FilePath)
-> Parser (FilePath -> Text -> BokehPrecursor)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
PreambleK Parser (FilePath -> Text -> BokehPrecursor)
-> Parser FilePath -> Parser (Text -> BokehPrecursor)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
ExecutableK Parser (Maybe FilePath) -> FilePath -> Parser FilePath
forall a. Parser (Maybe a) -> a -> Parser a
.!= Configuration -> FilePath
bokehExe Configuration
defaultConfiguration Parser (Text -> BokehPrecursor)
-> Parser Text -> Parser BokehPrecursor
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
CommandLineArgsK Parser (Maybe Text) -> Text -> Parser Text
forall a. Parser (Maybe a) -> a -> Parser a
.!= Configuration -> Text
bokehCmdArgs Configuration
defaultConfiguration
parseJSON Value
_ = FilePath -> Parser BokehPrecursor
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail (FilePath -> Parser BokehPrecursor)
-> FilePath -> Parser BokehPrecursor
forall a b. (a -> b) -> a -> b
$ [FilePath] -> FilePath
forall a. Monoid a => [a] -> a
mconcat [FilePath
"Could not parse ", Toolkit -> FilePath
forall a. Show a => a -> FilePath
show Toolkit
Bokeh, FilePath
" configuration."]
instance FromJSON PlotsjlPrecursor where
parseJSON :: Value -> Parser PlotsjlPrecursor
parseJSON (Object Object
v) = Maybe FilePath -> FilePath -> Text -> PlotsjlPrecursor
PlotsjlPrecursor (Maybe FilePath -> FilePath -> Text -> PlotsjlPrecursor)
-> Parser (Maybe FilePath)
-> Parser (FilePath -> Text -> PlotsjlPrecursor)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
PreambleK Parser (FilePath -> Text -> PlotsjlPrecursor)
-> Parser FilePath -> Parser (Text -> PlotsjlPrecursor)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
ExecutableK Parser (Maybe FilePath) -> FilePath -> Parser FilePath
forall a. Parser (Maybe a) -> a -> Parser a
.!= Configuration -> FilePath
plotsjlExe Configuration
defaultConfiguration Parser (Text -> PlotsjlPrecursor)
-> Parser Text -> Parser PlotsjlPrecursor
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
CommandLineArgsK Parser (Maybe Text) -> Text -> Parser Text
forall a. Parser (Maybe a) -> a -> Parser a
.!= Configuration -> Text
plotsjlCmdArgs Configuration
defaultConfiguration
parseJSON Value
_ = FilePath -> Parser PlotsjlPrecursor
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail (FilePath -> Parser PlotsjlPrecursor)
-> FilePath -> Parser PlotsjlPrecursor
forall a b. (a -> b) -> a -> b
$ [FilePath] -> FilePath
forall a. Monoid a => [a] -> a
mconcat [FilePath
"Could not parse ", Toolkit -> FilePath
forall a. Show a => a -> FilePath
show Toolkit
Plotsjl, FilePath
" configuration."]
instance FromJSON PlantUMLPrecursor where
parseJSON :: Value -> Parser PlantUMLPrecursor
parseJSON (Object Object
v) = Maybe FilePath -> FilePath -> Text -> PlantUMLPrecursor
PlantUMLPrecursor (Maybe FilePath -> FilePath -> Text -> PlantUMLPrecursor)
-> Parser (Maybe FilePath)
-> Parser (FilePath -> Text -> PlantUMLPrecursor)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
PreambleK Parser (FilePath -> Text -> PlantUMLPrecursor)
-> Parser FilePath -> Parser (Text -> PlantUMLPrecursor)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
ExecutableK Parser (Maybe FilePath) -> FilePath -> Parser FilePath
forall a. Parser (Maybe a) -> a -> Parser a
.!= Configuration -> FilePath
plantumlExe Configuration
defaultConfiguration Parser (Text -> PlantUMLPrecursor)
-> Parser Text -> Parser PlantUMLPrecursor
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
CommandLineArgsK Parser (Maybe Text) -> Text -> Parser Text
forall a. Parser (Maybe a) -> a -> Parser a
.!= Configuration -> Text
plantumlCmdArgs Configuration
defaultConfiguration
parseJSON Value
_ = FilePath -> Parser PlantUMLPrecursor
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail (FilePath -> Parser PlantUMLPrecursor)
-> FilePath -> Parser PlantUMLPrecursor
forall a b. (a -> b) -> a -> b
$ [FilePath] -> FilePath
forall a. Monoid a => [a] -> a
mconcat [FilePath
"Could not parse ", Toolkit -> FilePath
forall a. Show a => a -> FilePath
show Toolkit
PlantUML, FilePath
" configuration."]
instance FromJSON ConfigPrecursor where
parseJSON :: Value -> Parser ConfigPrecursor
parseJSON Value
Null = ConfigPrecursor -> Parser ConfigPrecursor
forall (m :: * -> *) a. Monad m => a -> m a
return ConfigPrecursor
defaultConfigPrecursor
parseJSON (Object Object
v) = do
FilePath
_defaultDirectory <- Object
v Object -> Text -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
DirectoryK Parser (Maybe FilePath) -> FilePath -> Parser FilePath
forall a. Parser (Maybe a) -> a -> Parser a
.!= ConfigPrecursor -> FilePath
_defaultDirectory ConfigPrecursor
defaultConfigPrecursor
Bool
_defaultWithSource <- Object
v Object -> Text -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
WithSourceK Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= ConfigPrecursor -> Bool
_defaultWithSource ConfigPrecursor
defaultConfigPrecursor
Int
_defaultDPI <- Object
v Object -> Text -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
DpiK Parser (Maybe Int) -> Int -> Parser Int
forall a. Parser (Maybe a) -> a -> Parser a
.!= ConfigPrecursor -> Int
_defaultDPI ConfigPrecursor
defaultConfigPrecursor
SaveFormat
_defaultSaveFormat <- Object
v Object -> Text -> Parser (Maybe SaveFormat)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
SaveFormatK Parser (Maybe SaveFormat) -> SaveFormat -> Parser SaveFormat
forall a. Parser (Maybe a) -> a -> Parser a
.!= ConfigPrecursor -> SaveFormat
_defaultSaveFormat ConfigPrecursor
defaultConfigPrecursor
[FilePath]
_defaultDependencies <- Object
v Object -> Text -> Parser (Maybe [FilePath])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
DependenciesK Parser (Maybe [FilePath]) -> [FilePath] -> Parser [FilePath]
forall a. Parser (Maybe a) -> a -> Parser a
.!= ConfigPrecursor -> [FilePath]
_defaultDependencies ConfigPrecursor
defaultConfigPrecursor
Format
_captionFormat <- Object
v Object -> Text -> Parser (Maybe Format)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
CaptionFormatK Parser (Maybe Format) -> Format -> Parser Format
forall a. Parser (Maybe a) -> a -> Parser a
.!= ConfigPrecursor -> Format
_captionFormat ConfigPrecursor
defaultConfigPrecursor
Text
_sourceCodeLabel <- Object
v Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
SourceCodeLabelK Parser (Maybe Text) -> Text -> Parser Text
forall a. Parser (Maybe a) -> a -> Parser a
.!= ConfigPrecursor -> Text
_sourceCodeLabel ConfigPrecursor
defaultConfigPrecursor
Bool
_strictMode <- Object
v Object -> Text -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
StrictModeK Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= ConfigPrecursor -> Bool
_strictMode ConfigPrecursor
defaultConfigPrecursor
LoggingPrecursor
_logPrec <- Object
v Object -> Text -> Parser (Maybe LoggingPrecursor)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"logging" Parser (Maybe LoggingPrecursor)
-> LoggingPrecursor -> Parser LoggingPrecursor
forall a. Parser (Maybe a) -> a -> Parser a
.!= ConfigPrecursor -> LoggingPrecursor
_logPrec ConfigPrecursor
defaultConfigPrecursor
MatplotlibPrecursor
_matplotlibPrec <- Object
v Object -> Text -> Parser (Maybe MatplotlibPrecursor)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Toolkit -> Text
cls Toolkit
Matplotlib Parser (Maybe MatplotlibPrecursor)
-> MatplotlibPrecursor -> Parser MatplotlibPrecursor
forall a. Parser (Maybe a) -> a -> Parser a
.!= ConfigPrecursor -> MatplotlibPrecursor
_matplotlibPrec ConfigPrecursor
defaultConfigPrecursor
MatlabPrecursor
_matlabPrec <- Object
v Object -> Text -> Parser (Maybe MatlabPrecursor)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Toolkit -> Text
cls Toolkit
Matlab Parser (Maybe MatlabPrecursor)
-> MatlabPrecursor -> Parser MatlabPrecursor
forall a. Parser (Maybe a) -> a -> Parser a
.!= ConfigPrecursor -> MatlabPrecursor
_matlabPrec ConfigPrecursor
defaultConfigPrecursor
PlotlyPythonPrecursor
_plotlyPythonPrec <- Object
v Object -> Text -> Parser (Maybe PlotlyPythonPrecursor)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Toolkit -> Text
cls Toolkit
PlotlyPython Parser (Maybe PlotlyPythonPrecursor)
-> PlotlyPythonPrecursor -> Parser PlotlyPythonPrecursor
forall a. Parser (Maybe a) -> a -> Parser a
.!= ConfigPrecursor -> PlotlyPythonPrecursor
_plotlyPythonPrec ConfigPrecursor
defaultConfigPrecursor
PlotlyRPrecursor
_plotlyRPrec <- Object
v Object -> Text -> Parser (Maybe PlotlyRPrecursor)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Toolkit -> Text
cls Toolkit
PlotlyR Parser (Maybe PlotlyRPrecursor)
-> PlotlyRPrecursor -> Parser PlotlyRPrecursor
forall a. Parser (Maybe a) -> a -> Parser a
.!= ConfigPrecursor -> PlotlyRPrecursor
_plotlyRPrec ConfigPrecursor
defaultConfigPrecursor
MathematicaPrecursor
_mathematicaPrec <- Object
v Object -> Text -> Parser (Maybe MathematicaPrecursor)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Toolkit -> Text
cls Toolkit
Mathematica Parser (Maybe MathematicaPrecursor)
-> MathematicaPrecursor -> Parser MathematicaPrecursor
forall a. Parser (Maybe a) -> a -> Parser a
.!= ConfigPrecursor -> MathematicaPrecursor
_mathematicaPrec ConfigPrecursor
defaultConfigPrecursor
OctavePrecursor
_octavePrec <- Object
v Object -> Text -> Parser (Maybe OctavePrecursor)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Toolkit -> Text
cls Toolkit
Octave Parser (Maybe OctavePrecursor)
-> OctavePrecursor -> Parser OctavePrecursor
forall a. Parser (Maybe a) -> a -> Parser a
.!= ConfigPrecursor -> OctavePrecursor
_octavePrec ConfigPrecursor
defaultConfigPrecursor
GGPlot2Precursor
_ggplot2Prec <- Object
v Object -> Text -> Parser (Maybe GGPlot2Precursor)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Toolkit -> Text
cls Toolkit
GGPlot2 Parser (Maybe GGPlot2Precursor)
-> GGPlot2Precursor -> Parser GGPlot2Precursor
forall a. Parser (Maybe a) -> a -> Parser a
.!= ConfigPrecursor -> GGPlot2Precursor
_ggplot2Prec ConfigPrecursor
defaultConfigPrecursor
GNUPlotPrecursor
_gnuplotPrec <- Object
v Object -> Text -> Parser (Maybe GNUPlotPrecursor)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Toolkit -> Text
cls Toolkit
GNUPlot Parser (Maybe GNUPlotPrecursor)
-> GNUPlotPrecursor -> Parser GNUPlotPrecursor
forall a. Parser (Maybe a) -> a -> Parser a
.!= ConfigPrecursor -> GNUPlotPrecursor
_gnuplotPrec ConfigPrecursor
defaultConfigPrecursor
GraphvizPrecursor
_graphvizPrec <- Object
v Object -> Text -> Parser (Maybe GraphvizPrecursor)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Toolkit -> Text
cls Toolkit
Graphviz Parser (Maybe GraphvizPrecursor)
-> GraphvizPrecursor -> Parser GraphvizPrecursor
forall a. Parser (Maybe a) -> a -> Parser a
.!= ConfigPrecursor -> GraphvizPrecursor
_graphvizPrec ConfigPrecursor
defaultConfigPrecursor
BokehPrecursor
_bokehPrec <- Object
v Object -> Text -> Parser (Maybe BokehPrecursor)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Toolkit -> Text
cls Toolkit
Bokeh Parser (Maybe BokehPrecursor)
-> BokehPrecursor -> Parser BokehPrecursor
forall a. Parser (Maybe a) -> a -> Parser a
.!= ConfigPrecursor -> BokehPrecursor
_bokehPrec ConfigPrecursor
defaultConfigPrecursor
PlotsjlPrecursor
_plotsjlPrec <- Object
v Object -> Text -> Parser (Maybe PlotsjlPrecursor)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Toolkit -> Text
cls Toolkit
Plotsjl Parser (Maybe PlotsjlPrecursor)
-> PlotsjlPrecursor -> Parser PlotsjlPrecursor
forall a. Parser (Maybe a) -> a -> Parser a
.!= ConfigPrecursor -> PlotsjlPrecursor
_plotsjlPrec ConfigPrecursor
defaultConfigPrecursor
PlantUMLPrecursor
_plantumlPrec <- Object
v Object -> Text -> Parser (Maybe PlantUMLPrecursor)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Toolkit -> Text
cls Toolkit
PlantUML Parser (Maybe PlantUMLPrecursor)
-> PlantUMLPrecursor -> Parser PlantUMLPrecursor
forall a. Parser (Maybe a) -> a -> Parser a
.!= ConfigPrecursor -> PlantUMLPrecursor
_plantumlPrec ConfigPrecursor
defaultConfigPrecursor
ConfigPrecursor -> Parser ConfigPrecursor
forall (m :: * -> *) a. Monad m => a -> m a
return (ConfigPrecursor -> Parser ConfigPrecursor)
-> ConfigPrecursor -> Parser ConfigPrecursor
forall a b. (a -> b) -> a -> b
$ ConfigPrecursor :: FilePath
-> Bool
-> Int
-> SaveFormat
-> [FilePath]
-> Format
-> Text
-> Bool
-> LoggingPrecursor
-> MatplotlibPrecursor
-> MatlabPrecursor
-> PlotlyPythonPrecursor
-> PlotlyRPrecursor
-> MathematicaPrecursor
-> OctavePrecursor
-> GGPlot2Precursor
-> GNUPlotPrecursor
-> GraphvizPrecursor
-> BokehPrecursor
-> PlotsjlPrecursor
-> PlantUMLPrecursor
-> ConfigPrecursor
ConfigPrecursor {Bool
Int
FilePath
[FilePath]
Text
Format
SaveFormat
PlantUMLPrecursor
PlotsjlPrecursor
BokehPrecursor
GraphvizPrecursor
GNUPlotPrecursor
GGPlot2Precursor
OctavePrecursor
MathematicaPrecursor
PlotlyRPrecursor
PlotlyPythonPrecursor
MatlabPrecursor
MatplotlibPrecursor
LoggingPrecursor
_plantumlPrec :: PlantUMLPrecursor
_plotsjlPrec :: PlotsjlPrecursor
_bokehPrec :: BokehPrecursor
_graphvizPrec :: GraphvizPrecursor
_gnuplotPrec :: GNUPlotPrecursor
_ggplot2Prec :: GGPlot2Precursor
_octavePrec :: OctavePrecursor
_mathematicaPrec :: MathematicaPrecursor
_plotlyRPrec :: PlotlyRPrecursor
_plotlyPythonPrec :: PlotlyPythonPrecursor
_matlabPrec :: MatlabPrecursor
_matplotlibPrec :: MatplotlibPrecursor
_logPrec :: LoggingPrecursor
_strictMode :: Bool
_sourceCodeLabel :: Text
_captionFormat :: Format
_defaultDependencies :: [FilePath]
_defaultSaveFormat :: SaveFormat
_defaultDPI :: Int
_defaultWithSource :: Bool
_defaultDirectory :: FilePath
_plantumlPrec :: PlantUMLPrecursor
_plotsjlPrec :: PlotsjlPrecursor
_bokehPrec :: BokehPrecursor
_graphvizPrec :: GraphvizPrecursor
_gnuplotPrec :: GNUPlotPrecursor
_ggplot2Prec :: GGPlot2Precursor
_octavePrec :: OctavePrecursor
_mathematicaPrec :: MathematicaPrecursor
_plotlyRPrec :: PlotlyRPrecursor
_plotlyPythonPrec :: PlotlyPythonPrecursor
_matlabPrec :: MatlabPrecursor
_matplotlibPrec :: MatplotlibPrecursor
_logPrec :: LoggingPrecursor
_strictMode :: Bool
_sourceCodeLabel :: Text
_captionFormat :: Format
_defaultDependencies :: [FilePath]
_defaultSaveFormat :: SaveFormat
_defaultDPI :: Int
_defaultWithSource :: Bool
_defaultDirectory :: FilePath
..}
parseJSON Value
_ = FilePath -> Parser ConfigPrecursor
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail FilePath
"Could not parse configuration."
renderConfig :: ConfigPrecursor -> IO Configuration
renderConfig :: ConfigPrecursor -> IO Configuration
renderConfig ConfigPrecursor {Bool
Int
FilePath
[FilePath]
Text
Format
SaveFormat
PlantUMLPrecursor
PlotsjlPrecursor
BokehPrecursor
GraphvizPrecursor
GNUPlotPrecursor
GGPlot2Precursor
OctavePrecursor
MathematicaPrecursor
PlotlyRPrecursor
PlotlyPythonPrecursor
MatlabPrecursor
MatplotlibPrecursor
LoggingPrecursor
_plantumlPrec :: PlantUMLPrecursor
_plotsjlPrec :: PlotsjlPrecursor
_bokehPrec :: BokehPrecursor
_graphvizPrec :: GraphvizPrecursor
_gnuplotPrec :: GNUPlotPrecursor
_ggplot2Prec :: GGPlot2Precursor
_octavePrec :: OctavePrecursor
_mathematicaPrec :: MathematicaPrecursor
_plotlyRPrec :: PlotlyRPrecursor
_plotlyPythonPrec :: PlotlyPythonPrecursor
_matlabPrec :: MatlabPrecursor
_matplotlibPrec :: MatplotlibPrecursor
_logPrec :: LoggingPrecursor
_strictMode :: Bool
_sourceCodeLabel :: Text
_captionFormat :: Format
_defaultDependencies :: [FilePath]
_defaultSaveFormat :: SaveFormat
_defaultDPI :: Int
_defaultWithSource :: Bool
_defaultDirectory :: FilePath
_plantumlPrec :: ConfigPrecursor -> PlantUMLPrecursor
_plotsjlPrec :: ConfigPrecursor -> PlotsjlPrecursor
_bokehPrec :: ConfigPrecursor -> BokehPrecursor
_graphvizPrec :: ConfigPrecursor -> GraphvizPrecursor
_gnuplotPrec :: ConfigPrecursor -> GNUPlotPrecursor
_ggplot2Prec :: ConfigPrecursor -> GGPlot2Precursor
_octavePrec :: ConfigPrecursor -> OctavePrecursor
_mathematicaPrec :: ConfigPrecursor -> MathematicaPrecursor
_plotlyRPrec :: ConfigPrecursor -> PlotlyRPrecursor
_plotlyPythonPrec :: ConfigPrecursor -> PlotlyPythonPrecursor
_matlabPrec :: ConfigPrecursor -> MatlabPrecursor
_matplotlibPrec :: ConfigPrecursor -> MatplotlibPrecursor
_logPrec :: ConfigPrecursor -> LoggingPrecursor
_strictMode :: ConfigPrecursor -> Bool
_sourceCodeLabel :: ConfigPrecursor -> Text
_captionFormat :: ConfigPrecursor -> Format
_defaultDependencies :: ConfigPrecursor -> [FilePath]
_defaultSaveFormat :: ConfigPrecursor -> SaveFormat
_defaultDPI :: ConfigPrecursor -> Int
_defaultWithSource :: ConfigPrecursor -> Bool
_defaultDirectory :: ConfigPrecursor -> FilePath
..} = do
let defaultDirectory :: FilePath
defaultDirectory = FilePath
_defaultDirectory
defaultWithSource :: Bool
defaultWithSource = Bool
_defaultWithSource
defaultDPI :: Int
defaultDPI = Int
_defaultDPI
defaultSaveFormat :: SaveFormat
defaultSaveFormat = SaveFormat
_defaultSaveFormat
defaultDependencies :: [FilePath]
defaultDependencies = [FilePath]
_defaultDependencies
captionFormat :: Format
captionFormat = Format
_captionFormat
sourceCodeLabel :: Text
sourceCodeLabel = Text
_sourceCodeLabel
strictMode :: Bool
strictMode = Bool
_strictMode
logVerbosity :: Verbosity
logVerbosity = LoggingPrecursor -> Verbosity
_logVerbosity LoggingPrecursor
_logPrec
logSink :: LogSink
logSink = LogSink -> (FilePath -> LogSink) -> Maybe FilePath -> LogSink
forall b a. b -> (a -> b) -> Maybe a -> b
maybe LogSink
StdErr FilePath -> LogSink
LogFile (LoggingPrecursor -> Maybe FilePath
_logFilePath LoggingPrecursor
_logPrec)
matplotlibTightBBox :: Bool
matplotlibTightBBox = MatplotlibPrecursor -> Bool
_matplotlibTightBBox MatplotlibPrecursor
_matplotlibPrec
matplotlibTransparent :: Bool
matplotlibTransparent = MatplotlibPrecursor -> Bool
_matplotlibTransparent MatplotlibPrecursor
_matplotlibPrec
matplotlibExe :: FilePath
matplotlibExe = MatplotlibPrecursor -> FilePath
_matplotlibExe MatplotlibPrecursor
_matplotlibPrec
matlabExe :: FilePath
matlabExe = MatlabPrecursor -> FilePath
_matlabExe MatlabPrecursor
_matlabPrec
plotlyPythonExe :: FilePath
plotlyPythonExe = PlotlyPythonPrecursor -> FilePath
_plotlyPythonExe PlotlyPythonPrecursor
_plotlyPythonPrec
plotlyRExe :: FilePath
plotlyRExe = PlotlyRPrecursor -> FilePath
_plotlyRExe PlotlyRPrecursor
_plotlyRPrec
mathematicaExe :: FilePath
mathematicaExe = MathematicaPrecursor -> FilePath
_mathematicaExe MathematicaPrecursor
_mathematicaPrec
octaveExe :: FilePath
octaveExe = OctavePrecursor -> FilePath
_octaveExe OctavePrecursor
_octavePrec
ggplot2Exe :: FilePath
ggplot2Exe = GGPlot2Precursor -> FilePath
_ggplot2Exe GGPlot2Precursor
_ggplot2Prec
gnuplotExe :: FilePath
gnuplotExe = GNUPlotPrecursor -> FilePath
_gnuplotExe GNUPlotPrecursor
_gnuplotPrec
graphvizExe :: FilePath
graphvizExe = GraphvizPrecursor -> FilePath
_graphvizExe GraphvizPrecursor
_graphvizPrec
bokehExe :: FilePath
bokehExe = BokehPrecursor -> FilePath
_bokehExe BokehPrecursor
_bokehPrec
plotsjlExe :: FilePath
plotsjlExe = PlotsjlPrecursor -> FilePath
_plotsjlExe PlotsjlPrecursor
_plotsjlPrec
plantumlExe :: FilePath
plantumlExe = PlantUMLPrecursor -> FilePath
_plantumlExe PlantUMLPrecursor
_plantumlPrec
matplotlibCmdArgs :: Text
matplotlibCmdArgs = MatplotlibPrecursor -> Text
_matplotlibCmdArgs MatplotlibPrecursor
_matplotlibPrec
matlabCmdArgs :: Text
matlabCmdArgs = MatlabPrecursor -> Text
_matlabCmdArgs MatlabPrecursor
_matlabPrec
plotlyPythonCmdArgs :: Text
plotlyPythonCmdArgs = PlotlyPythonPrecursor -> Text
_plotlyPythonCmdArgs PlotlyPythonPrecursor
_plotlyPythonPrec
plotlyRCmdArgs :: Text
plotlyRCmdArgs = PlotlyRPrecursor -> Text
_plotlyRCmdArgs PlotlyRPrecursor
_plotlyRPrec
mathematicaCmdArgs :: Text
mathematicaCmdArgs = MathematicaPrecursor -> Text
_mathematicaCmdArgs MathematicaPrecursor
_mathematicaPrec
octaveCmdArgs :: Text
octaveCmdArgs = OctavePrecursor -> Text
_octaveCmdArgs OctavePrecursor
_octavePrec
ggplot2CmdArgs :: Text
ggplot2CmdArgs = GGPlot2Precursor -> Text
_ggplot2CmdArgs GGPlot2Precursor
_ggplot2Prec
gnuplotCmdArgs :: Text
gnuplotCmdArgs = GNUPlotPrecursor -> Text
_gnuplotCmdArgs GNUPlotPrecursor
_gnuplotPrec
graphvizCmdArgs :: Text
graphvizCmdArgs = GraphvizPrecursor -> Text
_graphvizCmdArgs GraphvizPrecursor
_graphvizPrec
bokehCmdArgs :: Text
bokehCmdArgs = BokehPrecursor -> Text
_bokehCmdArgs BokehPrecursor
_bokehPrec
plotsjlCmdArgs :: Text
plotsjlCmdArgs = PlotsjlPrecursor -> Text
_plotsjlCmdArgs PlotsjlPrecursor
_plotsjlPrec
plantumlCmdArgs :: Text
plantumlCmdArgs = PlantUMLPrecursor -> Text
_plantumlCmdArgs PlantUMLPrecursor
_plantumlPrec
Text
matplotlibPreamble <- Maybe FilePath -> IO Text
readPreamble (MatplotlibPrecursor -> Maybe FilePath
_matplotlibPreamble MatplotlibPrecursor
_matplotlibPrec)
Text
matlabPreamble <- Maybe FilePath -> IO Text
readPreamble (MatlabPrecursor -> Maybe FilePath
_matlabPreamble MatlabPrecursor
_matlabPrec)
Text
plotlyPythonPreamble <- Maybe FilePath -> IO Text
readPreamble (PlotlyPythonPrecursor -> Maybe FilePath
_plotlyPythonPreamble PlotlyPythonPrecursor
_plotlyPythonPrec)
Text
plotlyRPreamble <- Maybe FilePath -> IO Text
readPreamble (PlotlyRPrecursor -> Maybe FilePath
_plotlyRPreamble PlotlyRPrecursor
_plotlyRPrec)
Text
mathematicaPreamble <- Maybe FilePath -> IO Text
readPreamble (MathematicaPrecursor -> Maybe FilePath
_mathematicaPreamble MathematicaPrecursor
_mathematicaPrec)
Text
octavePreamble <- Maybe FilePath -> IO Text
readPreamble (OctavePrecursor -> Maybe FilePath
_octavePreamble OctavePrecursor
_octavePrec)
Text
ggplot2Preamble <- Maybe FilePath -> IO Text
readPreamble (GGPlot2Precursor -> Maybe FilePath
_ggplot2Preamble GGPlot2Precursor
_ggplot2Prec)
Text
gnuplotPreamble <- Maybe FilePath -> IO Text
readPreamble (GNUPlotPrecursor -> Maybe FilePath
_gnuplotPreamble GNUPlotPrecursor
_gnuplotPrec)
Text
graphvizPreamble <- Maybe FilePath -> IO Text
readPreamble (GraphvizPrecursor -> Maybe FilePath
_graphvizPreamble GraphvizPrecursor
_graphvizPrec)
Text
bokehPreamble <- Maybe FilePath -> IO Text
readPreamble (BokehPrecursor -> Maybe FilePath
_bokehPreamble BokehPrecursor
_bokehPrec)
Text
plotsjlPreamble <- Maybe FilePath -> IO Text
readPreamble (PlotsjlPrecursor -> Maybe FilePath
_plotsjlPreamble PlotsjlPrecursor
_plotsjlPrec)
Text
plantumlPreamble <- Maybe FilePath -> IO Text
readPreamble (PlantUMLPrecursor -> Maybe FilePath
_plantumlPreamble PlantUMLPrecursor
_plantumlPrec)
Configuration -> IO Configuration
forall (m :: * -> *) a. Monad m => a -> m a
return Configuration :: FilePath
-> Bool
-> Int
-> SaveFormat
-> [FilePath]
-> Format
-> Text
-> Bool
-> Verbosity
-> LogSink
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> FilePath
-> FilePath
-> FilePath
-> FilePath
-> FilePath
-> FilePath
-> FilePath
-> FilePath
-> FilePath
-> FilePath
-> FilePath
-> FilePath
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Bool
-> Configuration
Configuration {Bool
Int
FilePath
[FilePath]
Text
Format
LogSink
Verbosity
SaveFormat
plantumlPreamble :: Text
plotsjlPreamble :: Text
bokehPreamble :: Text
graphvizPreamble :: Text
gnuplotPreamble :: Text
ggplot2Preamble :: Text
octavePreamble :: Text
mathematicaPreamble :: Text
plotlyRPreamble :: Text
plotlyPythonPreamble :: Text
matlabPreamble :: Text
matplotlibPreamble :: Text
plantumlCmdArgs :: Text
plotsjlCmdArgs :: Text
bokehCmdArgs :: Text
graphvizCmdArgs :: Text
gnuplotCmdArgs :: Text
ggplot2CmdArgs :: Text
octaveCmdArgs :: Text
mathematicaCmdArgs :: Text
plotlyRCmdArgs :: Text
plotlyPythonCmdArgs :: Text
matlabCmdArgs :: Text
matplotlibCmdArgs :: Text
plantumlExe :: FilePath
plotsjlExe :: FilePath
bokehExe :: FilePath
graphvizExe :: FilePath
gnuplotExe :: FilePath
ggplot2Exe :: FilePath
octaveExe :: FilePath
mathematicaExe :: FilePath
plotlyRExe :: FilePath
plotlyPythonExe :: FilePath
matlabExe :: FilePath
matplotlibExe :: FilePath
matplotlibTransparent :: Bool
matplotlibTightBBox :: Bool
logSink :: LogSink
logVerbosity :: Verbosity
strictMode :: Bool
sourceCodeLabel :: Text
captionFormat :: Format
defaultDependencies :: [FilePath]
defaultSaveFormat :: SaveFormat
defaultDPI :: Int
defaultWithSource :: Bool
defaultDirectory :: FilePath
matplotlibTransparent :: Bool
matplotlibTightBBox :: Bool
plantumlCmdArgs :: Text
plotsjlCmdArgs :: Text
bokehCmdArgs :: Text
graphvizCmdArgs :: Text
gnuplotCmdArgs :: Text
ggplot2CmdArgs :: Text
octaveCmdArgs :: Text
mathematicaCmdArgs :: Text
plotlyRCmdArgs :: Text
plotlyPythonCmdArgs :: Text
matlabCmdArgs :: Text
matplotlibCmdArgs :: Text
plantumlExe :: FilePath
plotsjlExe :: FilePath
bokehExe :: FilePath
graphvizExe :: FilePath
gnuplotExe :: FilePath
ggplot2Exe :: FilePath
octaveExe :: FilePath
mathematicaExe :: FilePath
plotlyRExe :: FilePath
plotlyPythonExe :: FilePath
matlabExe :: FilePath
matplotlibExe :: FilePath
plantumlPreamble :: Text
plotsjlPreamble :: Text
bokehPreamble :: Text
graphvizPreamble :: Text
gnuplotPreamble :: Text
ggplot2Preamble :: Text
octavePreamble :: Text
mathematicaPreamble :: Text
matlabPreamble :: Text
plotlyRPreamble :: Text
plotlyPythonPreamble :: Text
matplotlibPreamble :: Text
logSink :: LogSink
logVerbosity :: Verbosity
strictMode :: Bool
sourceCodeLabel :: Text
captionFormat :: Format
defaultDependencies :: [FilePath]
defaultSaveFormat :: SaveFormat
defaultDPI :: Int
defaultWithSource :: Bool
defaultDirectory :: FilePath
..}
where
readPreamble :: Maybe FilePath -> IO Text
readPreamble Maybe FilePath
fp = IO Text -> (FilePath -> IO Text) -> Maybe FilePath -> IO Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe IO Text
forall a. Monoid a => a
mempty FilePath -> IO Text
TIO.readFile Maybe FilePath
fp
tshow :: Show a => a -> Text
tshow :: a -> Text
tshow = FilePath -> Text
pack (FilePath -> Text) -> (a -> FilePath) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> FilePath
forall a. Show a => a -> FilePath
show