{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeSynonymInstances #-}
module Text.Pandoc.Filter.Plot.Monad
( Configuration (..),
PlotM,
RuntimeEnv (..),
PlotState (..),
runPlotM,
mapConcurrentlyN,
runCommand,
withPrependedPath,
throwStrictError,
fileHash,
executable,
Verbosity (..),
LogSink (..),
debug,
err,
warning,
info,
liftIO,
ask,
asks,
asksConfig,
module Text.Pandoc.Filter.Plot.Monad.Types,
)
where
import Control.Concurrent.Async.Lifted (mapConcurrently)
import Control.Concurrent.MVar (MVar, newMVar, putMVar, takeMVar)
import Control.Concurrent.QSemN
( QSemN,
newQSemN,
signalQSemN,
waitQSemN,
)
import Control.Exception.Lifted (bracket, bracket_)
import Control.Monad.Reader
( MonadIO (liftIO),
MonadReader (ask),
ReaderT (runReaderT),
asks,
)
import Control.Monad.State.Strict
( MonadState (get, put),
StateT,
evalStateT,
)
import Data.ByteString.Lazy (toStrict)
import Data.Functor ((<&>))
import Data.Hashable (hash)
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as M
import Data.Text (Text, pack, unpack)
import qualified Data.Text as T
import Data.Text.Encoding (decodeUtf8With)
import Data.Text.Encoding.Error (lenientDecode)
import System.Directory
( doesFileExist,
findExecutable,
getCurrentDirectory,
getModificationTime,
)
import System.Environment (getEnv, setEnv)
import System.Exit (ExitCode (..), exitFailure)
import System.Process.Typed
( byteStringInput,
byteStringOutput,
nullStream,
readProcessStderr,
setStderr,
setStdin,
setStdout,
setWorkingDir,
shell,
)
import Text.Pandoc.Definition (Format (..))
import Text.Pandoc.Filter.Plot.Monad.Logging
( LogSink (..),
Logger,
MonadLogger (..),
Verbosity (..),
debug,
err,
info,
strict,
terminateLogging,
warning,
withLogger,
)
import Text.Pandoc.Filter.Plot.Monad.Types
import Prelude hiding (fst, log, snd)
type PlotM = StateT PlotState (ReaderT RuntimeEnv IO)
instance MonadLogger PlotM where
askLogger :: PlotM Logger
askLogger = (RuntimeEnv -> Logger) -> PlotM Logger
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks RuntimeEnv -> Logger
envLogger
data RuntimeEnv = RuntimeEnv
{ RuntimeEnv -> Maybe Format
envFormat :: Maybe Format,
RuntimeEnv -> Configuration
envConfig :: Configuration,
RuntimeEnv -> Logger
envLogger :: Logger,
RuntimeEnv -> FilePath
envCWD :: FilePath
}
asksConfig :: (Configuration -> a) -> PlotM a
asksConfig :: (Configuration -> a) -> PlotM a
asksConfig Configuration -> a
f = (RuntimeEnv -> a) -> PlotM a
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (Configuration -> a
f (Configuration -> a)
-> (RuntimeEnv -> Configuration) -> RuntimeEnv -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RuntimeEnv -> Configuration
envConfig)
runPlotM :: Maybe Format -> Configuration -> PlotM a -> IO a
runPlotM :: Maybe Format -> Configuration -> PlotM a -> IO a
runPlotM Maybe Format
fmt Configuration
conf PlotM a
v = do
FilePath
cwd <- IO FilePath
getCurrentDirectory
PlotState
st <-
MVar (Map FilePath FileHash)
-> MVar (Map Toolkit (Maybe Renderer)) -> PlotState
PlotState (MVar (Map FilePath FileHash)
-> MVar (Map Toolkit (Maybe Renderer)) -> PlotState)
-> IO (MVar (Map FilePath FileHash))
-> IO (MVar (Map Toolkit (Maybe Renderer)) -> PlotState)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Map FilePath FileHash -> IO (MVar (Map FilePath FileHash))
forall a. a -> IO (MVar a)
newMVar Map FilePath FileHash
forall a. Monoid a => a
mempty
IO (MVar (Map Toolkit (Maybe Renderer)) -> PlotState)
-> IO (MVar (Map Toolkit (Maybe Renderer))) -> IO PlotState
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Map Toolkit (Maybe Renderer)
-> IO (MVar (Map Toolkit (Maybe Renderer)))
forall a. a -> IO (MVar a)
newMVar Map Toolkit (Maybe Renderer)
forall a. Monoid a => a
mempty
let verbosity :: Verbosity
verbosity = Configuration -> Verbosity
logVerbosity Configuration
conf
sink :: LogSink
sink = Configuration -> LogSink
logSink Configuration
conf
Verbosity -> LogSink -> (Logger -> IO a) -> IO a
forall a. Verbosity -> LogSink -> (Logger -> IO a) -> IO a
withLogger Verbosity
verbosity LogSink
sink ((Logger -> IO a) -> IO a) -> (Logger -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$
\Logger
logger -> ReaderT RuntimeEnv IO a -> RuntimeEnv -> IO a
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT (PlotM a -> PlotState -> ReaderT RuntimeEnv IO a
forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m a
evalStateT PlotM a
v PlotState
st) (Maybe Format -> Configuration -> Logger -> FilePath -> RuntimeEnv
RuntimeEnv Maybe Format
fmt Configuration
conf Logger
logger FilePath
cwd)
mapConcurrentlyN :: Traversable t => Int -> (a -> PlotM b) -> t a -> PlotM (t b)
mapConcurrentlyN :: Int -> (a -> PlotM b) -> t a -> PlotM (t b)
mapConcurrentlyN Int
n a -> PlotM b
f t a
xs = do
QSemN
sem <- IO QSemN -> StateT PlotState (ReaderT RuntimeEnv IO) QSemN
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO QSemN -> StateT PlotState (ReaderT RuntimeEnv IO) QSemN)
-> IO QSemN -> StateT PlotState (ReaderT RuntimeEnv IO) QSemN
forall a b. (a -> b) -> a -> b
$ Int -> IO QSemN
newQSemN Int
n
(a -> PlotM b) -> t a -> PlotM (t b)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, MonadBaseControl IO m) =>
(a -> m b) -> t a -> m (t b)
mapConcurrently (QSemN -> PlotM b -> PlotM b
forall a. QSemN -> PlotM a -> PlotM a
with QSemN
sem (PlotM b -> PlotM b) -> (a -> PlotM b) -> a -> PlotM b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> PlotM b
f) t a
xs
where
with :: QSemN -> PlotM a -> PlotM a
with :: QSemN -> PlotM a -> PlotM a
with QSemN
s = StateT PlotState (ReaderT RuntimeEnv IO) ()
-> StateT PlotState (ReaderT RuntimeEnv IO) ()
-> PlotM a
-> PlotM a
forall (m :: * -> *) a b c.
MonadBaseControl IO m =>
m a -> m b -> m c -> m c
bracket_ (IO () -> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> StateT PlotState (ReaderT RuntimeEnv IO) ())
-> IO () -> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall a b. (a -> b) -> a -> b
$ QSemN -> Int -> IO ()
waitQSemN QSemN
s Int
1) (IO () -> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> StateT PlotState (ReaderT RuntimeEnv IO) ())
-> IO () -> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall a b. (a -> b) -> a -> b
$ QSemN -> Int -> IO ()
signalQSemN QSemN
s Int
1)
runCommand ::
FilePath ->
Text ->
PlotM (ExitCode, Text)
runCommand :: FilePath -> Text -> PlotM (ExitCode, Text)
runCommand FilePath
wordir Text
command = do
(ExitCode
ec, ByteString
processOutput') <-
IO (ExitCode, ByteString)
-> StateT PlotState (ReaderT RuntimeEnv IO) (ExitCode, ByteString)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (ExitCode, ByteString)
-> StateT PlotState (ReaderT RuntimeEnv IO) (ExitCode, ByteString))
-> IO (ExitCode, ByteString)
-> StateT PlotState (ReaderT RuntimeEnv IO) (ExitCode, ByteString)
forall a b. (a -> b) -> a -> b
$
ProcessConfig () () (STM ByteString) -> IO (ExitCode, ByteString)
forall (m :: * -> *) stdin stdout stderrIgnored.
MonadIO m =>
ProcessConfig stdin stdout stderrIgnored
-> m (ExitCode, ByteString)
readProcessStderr (ProcessConfig () () (STM ByteString) -> IO (ExitCode, ByteString))
-> ProcessConfig () () (STM ByteString)
-> IO (ExitCode, ByteString)
forall a b. (a -> b) -> a -> b
$
StreamSpec 'STInput ()
-> ProcessConfig () () (STM ByteString)
-> ProcessConfig () () (STM ByteString)
forall stdin stdin0 stdout stderr.
StreamSpec 'STInput stdin
-> ProcessConfig stdin0 stdout stderr
-> ProcessConfig stdin stdout stderr
setStdin (ByteString -> StreamSpec 'STInput ()
byteStringInput ByteString
"") (ProcessConfig () () (STM ByteString)
-> ProcessConfig () () (STM ByteString))
-> ProcessConfig () () (STM ByteString)
-> ProcessConfig () () (STM ByteString)
forall a b. (a -> b) -> a -> b
$
StreamSpec 'STOutput ()
-> ProcessConfig () () (STM ByteString)
-> ProcessConfig () () (STM ByteString)
forall stdout stdin stdout0 stderr.
StreamSpec 'STOutput stdout
-> ProcessConfig stdin stdout0 stderr
-> ProcessConfig stdin stdout stderr
setStdout StreamSpec 'STOutput ()
forall (anyStreamType :: StreamType). StreamSpec anyStreamType ()
nullStream (ProcessConfig () () (STM ByteString)
-> ProcessConfig () () (STM ByteString))
-> ProcessConfig () () (STM ByteString)
-> ProcessConfig () () (STM ByteString)
forall a b. (a -> b) -> a -> b
$
StreamSpec 'STOutput (STM ByteString)
-> ProcessConfig () () () -> ProcessConfig () () (STM ByteString)
forall stderr stdin stdout stderr0.
StreamSpec 'STOutput stderr
-> ProcessConfig stdin stdout stderr0
-> ProcessConfig stdin stdout stderr
setStderr StreamSpec 'STOutput (STM ByteString)
byteStringOutput (ProcessConfig () () () -> ProcessConfig () () (STM ByteString))
-> ProcessConfig () () () -> ProcessConfig () () (STM ByteString)
forall a b. (a -> b) -> a -> b
$
FilePath -> ProcessConfig () () () -> ProcessConfig () () ()
forall stdin stdout stderr.
FilePath
-> ProcessConfig stdin stdout stderr
-> ProcessConfig stdin stdout stderr
setWorkingDir FilePath
wordir (ProcessConfig () () () -> ProcessConfig () () ())
-> ProcessConfig () () () -> ProcessConfig () () ()
forall a b. (a -> b) -> a -> b
$
FilePath -> ProcessConfig () () ()
shell (Text -> FilePath
unpack Text
command)
let processOutput :: Text
processOutput = OnDecodeError -> ByteString -> Text
decodeUtf8With OnDecodeError
lenientDecode (ByteString -> Text) -> ByteString -> Text
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString
toStrict ByteString
processOutput'
logFunc :: Text -> StateT PlotState (ReaderT RuntimeEnv IO) ()
logFunc =
if ExitCode
ec ExitCode -> ExitCode -> Bool
forall a. Eq a => a -> a -> Bool
== ExitCode
ExitSuccess
then Text -> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall (m :: * -> *). (MonadLogger m, MonadIO m) => Text -> m ()
debug
else Text -> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall (m :: * -> *). (MonadLogger m, MonadIO m) => Text -> m ()
err
message :: Text
message =
[Text] -> Text
T.unlines
[ Text
"Running command",
Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
command,
Text
"ended with exit code " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> (FilePath -> Text
pack (FilePath -> Text) -> (ExitCode -> FilePath) -> ExitCode -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ExitCode -> FilePath
forall a. Show a => a -> FilePath
show (ExitCode -> Text) -> ExitCode -> Text
forall a b. (a -> b) -> a -> b
$ ExitCode
ec)
]
errorMessage :: Text
errorMessage =
if Text
processOutput Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
forall a. Monoid a => a
mempty
then Text
forall a. Monoid a => a
mempty
else
[Text] -> Text
T.unlines
[ Text
"*******",
Text
processOutput,
Text
"*******"
]
Text -> StateT PlotState (ReaderT RuntimeEnv IO) ()
logFunc (Text -> StateT PlotState (ReaderT RuntimeEnv IO) ())
-> Text -> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall a b. (a -> b) -> a -> b
$ Text
message Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
errorMessage
(ExitCode, Text) -> PlotM (ExitCode, Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (ExitCode
ec, Text
processOutput)
withPrependedPath :: FilePath -> PlotM a -> PlotM a
withPrependedPath :: FilePath -> PlotM a -> PlotM a
withPrependedPath FilePath
dir PlotM a
f = do
FilePath
pathVar <- IO FilePath -> StateT PlotState (ReaderT RuntimeEnv IO) FilePath
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FilePath -> StateT PlotState (ReaderT RuntimeEnv IO) FilePath)
-> IO FilePath -> StateT PlotState (ReaderT RuntimeEnv IO) FilePath
forall a b. (a -> b) -> a -> b
$ FilePath -> IO FilePath
getEnv FilePath
"PATH"
let pathVarPrepended :: FilePath
pathVarPrepended = [FilePath] -> FilePath
forall a. Monoid a => [a] -> a
mconcat [FilePath
dir, FilePath
";", FilePath
pathVar]
StateT PlotState (ReaderT RuntimeEnv IO) ()
-> (() -> StateT PlotState (ReaderT RuntimeEnv IO) ())
-> (() -> PlotM a)
-> PlotM a
forall (m :: * -> *) a b c.
MonadBaseControl IO m =>
m a -> (a -> m b) -> (a -> m c) -> m c
bracket
(IO () -> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> StateT PlotState (ReaderT RuntimeEnv IO) ())
-> IO () -> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath -> IO ()
setEnv FilePath
"PATH" FilePath
pathVarPrepended)
(\()
_ -> IO () -> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> StateT PlotState (ReaderT RuntimeEnv IO) ())
-> IO () -> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath -> IO ()
setEnv FilePath
"PATH" FilePath
pathVar)
(PlotM a -> () -> PlotM a
forall a b. a -> b -> a
const PlotM a
f)
throwStrictError :: Text -> PlotM ()
throwStrictError :: Text -> StateT PlotState (ReaderT RuntimeEnv IO) ()
throwStrictError Text
msg = do
Text -> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall (m :: * -> *). (MonadLogger m, MonadIO m) => Text -> m ()
strict Text
msg
Logger
logger <- PlotM Logger
forall (m :: * -> *). MonadLogger m => m Logger
askLogger
IO () -> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> StateT PlotState (ReaderT RuntimeEnv IO) ())
-> IO () -> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall a b. (a -> b) -> a -> b
$ Logger -> IO ()
terminateLogging Logger
logger IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> IO ()
forall a. IO a
exitFailure
type FileHash = Word
data PlotState
= PlotState
(MVar (Map FilePath FileHash))
(MVar (Map Toolkit (Maybe Renderer)))
fileHash :: FilePath -> PlotM FileHash
fileHash :: FilePath -> PlotM FileHash
fileHash FilePath
path = do
PlotState MVar (Map FilePath FileHash)
varHashes MVar (Map Toolkit (Maybe Renderer))
varExes <- StateT PlotState (ReaderT RuntimeEnv IO) PlotState
forall s (m :: * -> *). MonadState s m => m s
get
Map FilePath FileHash
hashes <- IO (Map FilePath FileHash)
-> StateT PlotState (ReaderT RuntimeEnv IO) (Map FilePath FileHash)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Map FilePath FileHash)
-> StateT
PlotState (ReaderT RuntimeEnv IO) (Map FilePath FileHash))
-> IO (Map FilePath FileHash)
-> StateT PlotState (ReaderT RuntimeEnv IO) (Map FilePath FileHash)
forall a b. (a -> b) -> a -> b
$ MVar (Map FilePath FileHash) -> IO (Map FilePath FileHash)
forall a. MVar a -> IO a
takeMVar MVar (Map FilePath FileHash)
varHashes
(FileHash
fh, Map FilePath FileHash
hashes') <- case FilePath -> Map FilePath FileHash -> Maybe FileHash
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup FilePath
path Map FilePath FileHash
hashes of
Maybe FileHash
Nothing -> do
Text -> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall (m :: * -> *). (MonadLogger m, MonadIO m) => Text -> m ()
debug (Text -> StateT PlotState (ReaderT RuntimeEnv IO) ())
-> Text -> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat [Text
"Calculating hash of dependency ", FilePath -> Text
pack FilePath
path]
FileHash
fh <- FilePath -> PlotM FileHash
fileHash' FilePath
path
let hashes' :: Map FilePath FileHash
hashes' = FilePath
-> FileHash -> Map FilePath FileHash -> Map FilePath FileHash
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert FilePath
path FileHash
fh Map FilePath FileHash
hashes
(FileHash, Map FilePath FileHash)
-> StateT
PlotState (ReaderT RuntimeEnv IO) (FileHash, Map FilePath FileHash)
forall (m :: * -> *) a. Monad m => a -> m a
return (FileHash
fh, Map FilePath FileHash
hashes')
Just FileHash
h -> do
Text -> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall (m :: * -> *). (MonadLogger m, MonadIO m) => Text -> m ()
debug (Text -> StateT PlotState (ReaderT RuntimeEnv IO) ())
-> Text -> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat [Text
"Hash of dependency ", FilePath -> Text
pack FilePath
path, Text
" already calculated."]
(FileHash, Map FilePath FileHash)
-> StateT
PlotState (ReaderT RuntimeEnv IO) (FileHash, Map FilePath FileHash)
forall (m :: * -> *) a. Monad m => a -> m a
return (FileHash
h, Map FilePath FileHash
hashes)
IO () -> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> StateT PlotState (ReaderT RuntimeEnv IO) ())
-> IO () -> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall a b. (a -> b) -> a -> b
$ MVar (Map FilePath FileHash) -> Map FilePath FileHash -> IO ()
forall a. MVar a -> a -> IO ()
putMVar MVar (Map FilePath FileHash)
varHashes Map FilePath FileHash
hashes'
PlotState -> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall s (m :: * -> *). MonadState s m => s -> m ()
put (PlotState -> StateT PlotState (ReaderT RuntimeEnv IO) ())
-> PlotState -> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall a b. (a -> b) -> a -> b
$ MVar (Map FilePath FileHash)
-> MVar (Map Toolkit (Maybe Renderer)) -> PlotState
PlotState MVar (Map FilePath FileHash)
varHashes MVar (Map Toolkit (Maybe Renderer))
varExes
FileHash -> PlotM FileHash
forall (m :: * -> *) a. Monad m => a -> m a
return FileHash
fh
where
fileHash' :: FilePath -> PlotM FileHash
fileHash' :: FilePath -> PlotM FileHash
fileHash' FilePath
fp = do
Bool
fileExists <- IO Bool -> StateT PlotState (ReaderT RuntimeEnv IO) Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> StateT PlotState (ReaderT RuntimeEnv IO) Bool)
-> IO Bool -> StateT PlotState (ReaderT RuntimeEnv IO) Bool
forall a b. (a -> b) -> a -> b
$ FilePath -> IO Bool
doesFileExist FilePath
fp
if Bool
fileExists
then IO FileHash -> PlotM FileHash
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FileHash -> PlotM FileHash)
-> (FilePath -> IO FileHash) -> FilePath -> PlotM FileHash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UTCTime -> FileHash) -> IO UTCTime -> IO FileHash
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int -> FileHash
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> FileHash) -> (UTCTime -> Int) -> UTCTime -> FileHash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Int
forall a. Hashable a => a -> Int
hash (FilePath -> Int) -> (UTCTime -> FilePath) -> UTCTime -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTCTime -> FilePath
forall a. Show a => a -> FilePath
show) (IO UTCTime -> IO FileHash)
-> (FilePath -> IO UTCTime) -> FilePath -> IO FileHash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO UTCTime
getModificationTime (FilePath -> PlotM FileHash) -> FilePath -> PlotM FileHash
forall a b. (a -> b) -> a -> b
$ FilePath
fp
else Text -> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall (m :: * -> *). (MonadLogger m, MonadIO m) => Text -> m ()
err ([Text] -> Text
forall a. Monoid a => [a] -> a
mconcat [Text
"Dependency ", FilePath -> Text
pack FilePath
fp, Text
" does not exist."]) StateT PlotState (ReaderT RuntimeEnv IO) ()
-> PlotM FileHash -> PlotM FileHash
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> FileHash -> PlotM FileHash
forall (m :: * -> *) a. Monad m => a -> m a
return FileHash
0
executable :: Toolkit -> PlotM (Maybe Executable)
executable :: Toolkit -> PlotM (Maybe Executable)
executable Toolkit
tk =
Toolkit -> StateT PlotState (ReaderT RuntimeEnv IO) FilePath
exeSelector Toolkit
tk
StateT PlotState (ReaderT RuntimeEnv IO) FilePath
-> (FilePath -> PlotM (Maybe Executable))
-> PlotM (Maybe Executable)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \FilePath
name ->
IO (Maybe Executable) -> PlotM (Maybe Executable)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Executable) -> PlotM (Maybe Executable))
-> IO (Maybe Executable) -> PlotM (Maybe Executable)
forall a b. (a -> b) -> a -> b
$
FilePath -> IO (Maybe FilePath)
findExecutable FilePath
name IO (Maybe FilePath)
-> (Maybe FilePath -> Maybe Executable) -> IO (Maybe Executable)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (FilePath -> Executable) -> Maybe FilePath -> Maybe Executable
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap FilePath -> Executable
exeFromPath
where
exeSelector :: Toolkit -> StateT PlotState (ReaderT RuntimeEnv IO) FilePath
exeSelector Toolkit
Matplotlib = (Configuration -> FilePath)
-> StateT PlotState (ReaderT RuntimeEnv IO) FilePath
forall a. (Configuration -> a) -> PlotM a
asksConfig Configuration -> FilePath
matplotlibExe
exeSelector Toolkit
PlotlyPython = (Configuration -> FilePath)
-> StateT PlotState (ReaderT RuntimeEnv IO) FilePath
forall a. (Configuration -> a) -> PlotM a
asksConfig Configuration -> FilePath
plotlyPythonExe
exeSelector Toolkit
PlotlyR = (Configuration -> FilePath)
-> StateT PlotState (ReaderT RuntimeEnv IO) FilePath
forall a. (Configuration -> a) -> PlotM a
asksConfig Configuration -> FilePath
plotlyRExe
exeSelector Toolkit
Matlab = (Configuration -> FilePath)
-> StateT PlotState (ReaderT RuntimeEnv IO) FilePath
forall a. (Configuration -> a) -> PlotM a
asksConfig Configuration -> FilePath
matlabExe
exeSelector Toolkit
Mathematica = (Configuration -> FilePath)
-> StateT PlotState (ReaderT RuntimeEnv IO) FilePath
forall a. (Configuration -> a) -> PlotM a
asksConfig Configuration -> FilePath
mathematicaExe
exeSelector Toolkit
Octave = (Configuration -> FilePath)
-> StateT PlotState (ReaderT RuntimeEnv IO) FilePath
forall a. (Configuration -> a) -> PlotM a
asksConfig Configuration -> FilePath
octaveExe
exeSelector Toolkit
GGPlot2 = (Configuration -> FilePath)
-> StateT PlotState (ReaderT RuntimeEnv IO) FilePath
forall a. (Configuration -> a) -> PlotM a
asksConfig Configuration -> FilePath
ggplot2Exe
exeSelector Toolkit
GNUPlot = (Configuration -> FilePath)
-> StateT PlotState (ReaderT RuntimeEnv IO) FilePath
forall a. (Configuration -> a) -> PlotM a
asksConfig Configuration -> FilePath
gnuplotExe
exeSelector Toolkit
Graphviz = (Configuration -> FilePath)
-> StateT PlotState (ReaderT RuntimeEnv IO) FilePath
forall a. (Configuration -> a) -> PlotM a
asksConfig Configuration -> FilePath
graphvizExe
exeSelector Toolkit
Bokeh = (Configuration -> FilePath)
-> StateT PlotState (ReaderT RuntimeEnv IO) FilePath
forall a. (Configuration -> a) -> PlotM a
asksConfig Configuration -> FilePath
bokehExe
exeSelector Toolkit
Plotsjl = (Configuration -> FilePath)
-> StateT PlotState (ReaderT RuntimeEnv IO) FilePath
forall a. (Configuration -> a) -> PlotM a
asksConfig Configuration -> FilePath
plotsjlExe
exeSelector Toolkit
PlantUML = (Configuration -> FilePath)
-> StateT PlotState (ReaderT RuntimeEnv IO) FilePath
forall a. (Configuration -> a) -> PlotM a
asksConfig Configuration -> FilePath
plantumlExe
exeSelector Toolkit
SageMath = (Configuration -> FilePath)
-> StateT PlotState (ReaderT RuntimeEnv IO) FilePath
forall a. (Configuration -> a) -> PlotM a
asksConfig Configuration -> FilePath
sagemathExe
data Configuration = Configuration
{
Configuration -> FilePath
defaultDirectory :: !FilePath,
Configuration -> Bool
defaultWithSource :: !Bool,
Configuration -> Int
defaultDPI :: !Int,
Configuration -> SaveFormat
defaultSaveFormat :: !SaveFormat,
Configuration -> [FilePath]
defaultDependencies :: ![FilePath],
Configuration -> Format
captionFormat :: !Format,
Configuration -> Text
sourceCodeLabel :: !Text,
Configuration -> Bool
strictMode :: !Bool,
Configuration -> Verbosity
logVerbosity :: !Verbosity,
Configuration -> LogSink
logSink :: !LogSink,
Configuration -> Text
matplotlibPreamble :: !Script,
Configuration -> Text
plotlyPythonPreamble :: !Script,
Configuration -> Text
plotlyRPreamble :: !Script,
Configuration -> Text
matlabPreamble :: !Script,
Configuration -> Text
mathematicaPreamble :: !Script,
Configuration -> Text
octavePreamble :: !Script,
Configuration -> Text
ggplot2Preamble :: !Script,
Configuration -> Text
gnuplotPreamble :: !Script,
Configuration -> Text
graphvizPreamble :: !Script,
Configuration -> Text
bokehPreamble :: !Script,
Configuration -> Text
plotsjlPreamble :: !Script,
Configuration -> Text
plantumlPreamble :: !Script,
Configuration -> Text
sagemathPreamble :: !Script,
Configuration -> FilePath
matplotlibExe :: !FilePath,
Configuration -> FilePath
matlabExe :: !FilePath,
Configuration -> FilePath
plotlyPythonExe :: !FilePath,
Configuration -> FilePath
plotlyRExe :: !FilePath,
Configuration -> FilePath
mathematicaExe :: !FilePath,
Configuration -> FilePath
octaveExe :: !FilePath,
Configuration -> FilePath
ggplot2Exe :: !FilePath,
Configuration -> FilePath
gnuplotExe :: !FilePath,
Configuration -> FilePath
graphvizExe :: !FilePath,
Configuration -> FilePath
bokehExe :: !FilePath,
Configuration -> FilePath
plotsjlExe :: !FilePath,
Configuration -> FilePath
plantumlExe :: !FilePath,
Configuration -> FilePath
sagemathExe :: !FilePath,
Configuration -> Text
matplotlibCmdArgs :: !Text,
Configuration -> Text
matlabCmdArgs :: !Text,
Configuration -> Text
plotlyPythonCmdArgs :: !Text,
Configuration -> Text
plotlyRCmdArgs :: !Text,
Configuration -> Text
mathematicaCmdArgs :: !Text,
Configuration -> Text
octaveCmdArgs :: !Text,
Configuration -> Text
ggplot2CmdArgs :: !Text,
Configuration -> Text
gnuplotCmdArgs :: !Text,
Configuration -> Text
graphvizCmdArgs :: !Text,
Configuration -> Text
bokehCmdArgs :: !Text,
Configuration -> Text
plotsjlCmdArgs :: !Text,
Configuration -> Text
plantumlCmdArgs :: !Text,
Configuration -> Text
sagemathCmdArgs :: !Text,
Configuration -> Bool
matplotlibTightBBox :: !Bool,
Configuration -> Bool
matplotlibTransparent :: !Bool
}
deriving (Configuration -> Configuration -> Bool
(Configuration -> Configuration -> Bool)
-> (Configuration -> Configuration -> Bool) -> Eq Configuration
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Configuration -> Configuration -> Bool
$c/= :: Configuration -> Configuration -> Bool
== :: Configuration -> Configuration -> Bool
$c== :: Configuration -> Configuration -> Bool
Eq, Int -> Configuration -> ShowS
[Configuration] -> ShowS
Configuration -> FilePath
(Int -> Configuration -> ShowS)
-> (Configuration -> FilePath)
-> ([Configuration] -> ShowS)
-> Show Configuration
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Configuration] -> ShowS
$cshowList :: [Configuration] -> ShowS
show :: Configuration -> FilePath
$cshow :: Configuration -> FilePath
showsPrec :: Int -> Configuration -> ShowS
$cshowsPrec :: Int -> Configuration -> ShowS
Show)