{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
module Text.Pandoc.Filter.Plot.Scripting
( ScriptResult (..),
runTempScript,
runScriptIfNecessary,
figurePath,
sourceCodePath,
)
where
import Data.Default (def)
import Data.Functor.Identity (Identity (..))
import Data.Hashable (hash)
import Data.Text (Text, pack, unpack)
import qualified Data.Text as T
import qualified Data.Text.IO as T
import Paths_pandoc_plot (version)
import System.Directory
( createDirectoryIfMissing,
doesFileExist,
getTemporaryDirectory,
)
import System.Exit (ExitCode (..))
import System.FilePath
( addExtension,
normalise,
replaceExtension,
takeDirectory,
(</>),
takeBaseName,
)
import Text.Pandoc.Class (runPure)
import Text.Pandoc.Definition (Block (CodeBlock), Pandoc (Pandoc))
import Text.Pandoc.Filter.Plot.Monad
import Text.Pandoc.Filter.Plot.Scripting.Template
import Text.Pandoc.Options (WriterOptions (..))
import Text.Pandoc.SelfContained (makeSelfContained)
import Text.Pandoc.Templates
import Text.Pandoc.Writers (writeHtml5String)
import Text.Printf (printf)
runScriptIfNecessary :: FigureSpec -> PlotM ScriptResult
runScriptIfNecessary :: FigureSpec -> PlotM ScriptResult
runScriptIfNecessary FigureSpec
spec = do
FilePath
target <- FigureSpec -> PlotM FilePath
figurePath FigureSpec
spec
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
$ Bool -> FilePath -> IO ()
createDirectoryIfMissing Bool
True (FilePath -> IO ()) -> (FilePath -> FilePath) -> FilePath -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath
takeDirectory (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
target
Bool
fileAlreadyExists <- 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)
-> (FilePath -> IO Bool)
-> FilePath
-> StateT PlotState (ReaderT RuntimeEnv IO) Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO Bool
doesFileExist (FilePath -> StateT PlotState (ReaderT RuntimeEnv IO) Bool)
-> FilePath -> StateT PlotState (ReaderT RuntimeEnv IO) Bool
forall a b. (a -> b) -> a -> b
$ FilePath
target
ScriptResult
result <-
if Bool
fileAlreadyExists
then ScriptResult -> PlotM ScriptResult
forall (m :: * -> *) a. Monad m => a -> m a
return ScriptResult
ScriptSuccess
else FigureSpec -> PlotM ScriptResult
runTempScript FigureSpec
spec
ScriptResult -> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall (m :: * -> *).
(MonadLogger m, MonadIO m) =>
ScriptResult -> m ()
logScriptResult ScriptResult
result
case ScriptResult
result of
ScriptResult
ScriptSuccess -> FigureSpec -> StateT PlotState (ReaderT RuntimeEnv IO) ()
writeSource FigureSpec
spec StateT PlotState (ReaderT RuntimeEnv IO) ()
-> PlotM ScriptResult -> PlotM ScriptResult
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ScriptResult -> PlotM ScriptResult
forall (m :: * -> *) a. Monad m => a -> m a
return ScriptResult
ScriptSuccess
ScriptResult
other -> ScriptResult -> PlotM ScriptResult
forall (m :: * -> *) a. Monad m => a -> m a
return ScriptResult
other
where
logScriptResult :: ScriptResult -> m ()
logScriptResult ScriptResult
ScriptSuccess = () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
logScriptResult ScriptResult
r = Text -> m ()
forall (m :: * -> *). (MonadLogger m, MonadIO m) => Text -> m ()
err (Text -> m ()) -> (ScriptResult -> Text) -> ScriptResult -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Text
pack (FilePath -> Text)
-> (ScriptResult -> FilePath) -> ScriptResult -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ScriptResult -> FilePath
forall a. Show a => a -> FilePath
show (ScriptResult -> m ()) -> ScriptResult -> m ()
forall a b. (a -> b) -> a -> b
$ ScriptResult
r
data ScriptResult
= ScriptSuccess
| ScriptChecksFailed Text
| ScriptFailure Text Int Script
instance Show ScriptResult where
show :: ScriptResult -> FilePath
show ScriptResult
ScriptSuccess = FilePath
"Script success."
show (ScriptChecksFailed Text
msg) = Text -> FilePath
unpack (Text -> FilePath) -> Text -> FilePath
forall a b. (a -> b) -> a -> b
$ Text
"Script checks failed: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
msg
show (ScriptFailure Text
cmd Int
ec Text
s) = [FilePath] -> FilePath
forall a. Monoid a => [a] -> a
mconcat [FilePath
"Command \"", Text -> FilePath
unpack Text
cmd, FilePath
"\" failed with exit code ", Int -> FilePath
forall a. Show a => a -> FilePath
show Int
ec, FilePath
". The script source was: \n\n", Text -> FilePath
unpack (Text -> FilePath) -> (Text -> Text) -> Text -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
formatScript (Text -> FilePath) -> Text -> FilePath
forall a b. (a -> b) -> a -> b
$ Text
s, FilePath
"\n"]
formatScript :: Script -> Text
formatScript :: Text -> Text
formatScript Text
s = [Text] -> Text
T.unlines ([Text] -> Text)
-> ([(Int, Text)] -> [Text]) -> [(Int, Text)] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Int, Text) -> Text) -> [(Int, Text)] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Int -> Text -> Text) -> (Int, Text) -> Text
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Int -> Text -> Text
formatLine) ([(Int, Text)] -> Text) -> [(Int, Text)] -> Text
forall a b. (a -> b) -> a -> b
$ [Int] -> [Text] -> [(Int, Text)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int]
linenos (Text -> [Text]
T.lines Text
s)
where
nlines :: Int
nlines = [Text] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (Text -> [Text]
T.lines Text
s)
linenos :: [Int]
linenos = [Int
1 .. Int
nlines]
maxdigits :: Int
maxdigits :: Int
maxdigits = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Double -> Int
forall a b. (RealFrac a, Integral b) => a -> b
floor (Double -> Double -> Double
forall a. Floating a => a -> a -> a
logBase Double
10 (Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
nlines :: Double))
formatLine :: Int -> Text -> Text
formatLine :: Int -> Text -> Text
formatLine Int
n Text
l = FilePath -> Text
pack (FilePath -> Int -> FilePath
forall r. PrintfType r => FilePath -> r
printf (FilePath
"%" FilePath -> FilePath -> FilePath
forall a. Semigroup a => a -> a -> a
<> Int -> FilePath
forall a. Show a => a -> FilePath
show Int
maxdigits FilePath -> FilePath -> FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath
"d") Int
n) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" > " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
l
runTempScript :: FigureSpec -> PlotM ScriptResult
runTempScript :: FigureSpec -> PlotM ScriptResult
runTempScript spec :: FigureSpec
spec@FigureSpec {Bool
Int
FilePath
[FilePath]
[(Text, Text)]
Attr
Text
Renderer
SaveFormat
blockAttrs :: FigureSpec -> Attr
extraAttrs :: FigureSpec -> [(Text, Text)]
dependencies :: FigureSpec -> [FilePath]
dpi :: FigureSpec -> Int
directory :: FigureSpec -> FilePath
saveFormat :: FigureSpec -> SaveFormat
script :: FigureSpec -> Text
withSource :: FigureSpec -> Bool
caption :: FigureSpec -> Text
renderer_ :: FigureSpec -> Renderer
blockAttrs :: Attr
extraAttrs :: [(Text, Text)]
dependencies :: [FilePath]
dpi :: Int
directory :: FilePath
saveFormat :: SaveFormat
script :: Text
withSource :: Bool
caption :: Text
renderer_ :: Renderer
..} = do
let checks :: [Text -> CheckResult]
checks = Renderer -> [Text -> CheckResult]
rendererChecks Renderer
renderer_
checkResult :: CheckResult
checkResult = [CheckResult] -> CheckResult
forall a. Monoid a => [a] -> a
mconcat ([CheckResult] -> CheckResult) -> [CheckResult] -> CheckResult
forall a b. (a -> b) -> a -> b
$ [Text -> CheckResult]
checks [Text -> CheckResult] -> [Text] -> [CheckResult]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [Text
script]
case CheckResult
checkResult of
CheckFailed Text
msg -> ScriptResult -> PlotM ScriptResult
forall (m :: * -> *) a. Monad m => a -> m a
return (ScriptResult -> PlotM ScriptResult)
-> ScriptResult -> PlotM ScriptResult
forall a b. (a -> b) -> a -> b
$ Text -> ScriptResult
ScriptChecksFailed Text
msg
CheckResult
CheckPassed -> do
FilePath
scriptPath <- FigureSpec -> PlotM FilePath
tempScriptPath FigureSpec
spec
FilePath
target <- FigureSpec -> PlotM FilePath
figurePath FigureSpec
spec
FilePath
cwd <- (RuntimeEnv -> FilePath) -> PlotM FilePath
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks RuntimeEnv -> FilePath
envCWD
let scriptWithCapture :: Text
scriptWithCapture = Renderer -> FigureSpec -> FilePath -> Text
rendererCapture Renderer
renderer_ FigureSpec
spec FilePath
target
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 -> Text -> IO ()
T.writeFile FilePath
scriptPath Text
scriptWithCapture
let outputSpec :: OutputSpec
outputSpec =
OutputSpec :: FigureSpec -> FilePath -> FilePath -> FilePath -> OutputSpec
OutputSpec
{ oFigureSpec :: FigureSpec
oFigureSpec = FigureSpec
spec,
oScriptPath :: FilePath
oScriptPath = FilePath
scriptPath,
oFigurePath :: FilePath
oFigurePath = FilePath
target,
oCWD :: FilePath
oCWD = FilePath
cwd
}
let command_ :: Text
command_ = Renderer -> OutputSpec -> Text
rendererCommand Renderer
renderer_ OutputSpec
outputSpec
let (Executable FilePath
exedir Text
_) = Renderer -> Executable
rendererExe Renderer
renderer_
FilePath -> PlotM ScriptResult -> PlotM ScriptResult
forall a. FilePath -> PlotM a -> PlotM a
withPrependedPath FilePath
exedir (PlotM ScriptResult -> PlotM ScriptResult)
-> PlotM ScriptResult -> PlotM ScriptResult
forall a b. (a -> b) -> a -> b
$ do
(ExitCode
ec, Text
_) <- FilePath -> Text -> PlotM (ExitCode, Text)
runCommand FilePath
cwd Text
command_
case ExitCode
ec of
ExitCode
ExitSuccess -> ScriptResult -> PlotM ScriptResult
forall (m :: * -> *) a. Monad m => a -> m a
return ScriptResult
ScriptSuccess
ExitFailure Int
code -> ScriptResult -> PlotM ScriptResult
forall (m :: * -> *) a. Monad m => a -> m a
return (ScriptResult -> PlotM ScriptResult)
-> ScriptResult -> PlotM ScriptResult
forall a b. (a -> b) -> a -> b
$ Text -> Int -> Text -> ScriptResult
ScriptFailure Text
command_ Int
code Text
script
tempScriptPath :: FigureSpec -> PlotM FilePath
tempScriptPath :: FigureSpec -> PlotM FilePath
tempScriptPath fs :: FigureSpec
fs@FigureSpec {Bool
Int
FilePath
[FilePath]
[(Text, Text)]
Attr
Text
Renderer
SaveFormat
blockAttrs :: Attr
extraAttrs :: [(Text, Text)]
dependencies :: [FilePath]
dpi :: Int
directory :: FilePath
saveFormat :: SaveFormat
script :: Text
withSource :: Bool
caption :: Text
renderer_ :: Renderer
blockAttrs :: FigureSpec -> Attr
extraAttrs :: FigureSpec -> [(Text, Text)]
dependencies :: FigureSpec -> [FilePath]
dpi :: FigureSpec -> Int
directory :: FigureSpec -> FilePath
saveFormat :: FigureSpec -> SaveFormat
script :: FigureSpec -> Text
withSource :: FigureSpec -> Bool
caption :: FigureSpec -> Text
renderer_ :: FigureSpec -> Renderer
..} = do
let ext :: FilePath
ext = Renderer -> FilePath
rendererScriptExtension Renderer
renderer_
FilePath
fp <- FigureSpec -> PlotM FilePath
figurePath FigureSpec
fs
let hashedPath :: FilePath
hashedPath = FilePath -> FilePath
takeBaseName FilePath
fp FilePath -> FilePath -> FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath
ext
IO FilePath -> PlotM FilePath
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FilePath -> PlotM FilePath) -> IO FilePath -> PlotM FilePath
forall a b. (a -> b) -> a -> b
$ (FilePath -> FilePath -> FilePath
</> FilePath
hashedPath) (FilePath -> FilePath) -> IO FilePath -> IO FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO FilePath
getTemporaryDirectory
sourceCodePath :: FigureSpec -> PlotM FilePath
sourceCodePath :: FigureSpec -> PlotM FilePath
sourceCodePath = (FilePath -> FilePath) -> PlotM FilePath -> PlotM FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (FilePath -> FilePath
normalise (FilePath -> FilePath)
-> (FilePath -> FilePath) -> FilePath -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath -> FilePath -> FilePath)
-> FilePath -> FilePath -> FilePath
forall a b c. (a -> b -> c) -> b -> a -> c
flip FilePath -> FilePath -> FilePath
replaceExtension FilePath
".src.html") (PlotM FilePath -> PlotM FilePath)
-> (FigureSpec -> PlotM FilePath) -> FigureSpec -> PlotM FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FigureSpec -> PlotM FilePath
figurePath
figureContentHash :: FigureSpec -> PlotM Word
figureContentHash :: FigureSpec -> PlotM Word
figureContentHash FigureSpec {Bool
Int
FilePath
[FilePath]
[(Text, Text)]
Attr
Text
Renderer
SaveFormat
blockAttrs :: Attr
extraAttrs :: [(Text, Text)]
dependencies :: [FilePath]
dpi :: Int
directory :: FilePath
saveFormat :: SaveFormat
script :: Text
withSource :: Bool
caption :: Text
renderer_ :: Renderer
blockAttrs :: FigureSpec -> Attr
extraAttrs :: FigureSpec -> [(Text, Text)]
dependencies :: FigureSpec -> [FilePath]
dpi :: FigureSpec -> Int
directory :: FigureSpec -> FilePath
saveFormat :: FigureSpec -> SaveFormat
script :: FigureSpec -> Text
withSource :: FigureSpec -> Bool
caption :: FigureSpec -> Text
renderer_ :: FigureSpec -> Renderer
..} = do
[Word]
dependenciesHash <- [PlotM Word] -> StateT PlotState (ReaderT RuntimeEnv IO) [Word]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence ([PlotM Word] -> StateT PlotState (ReaderT RuntimeEnv IO) [Word])
-> [PlotM Word] -> StateT PlotState (ReaderT RuntimeEnv IO) [Word]
forall a b. (a -> b) -> a -> b
$ FilePath -> PlotM Word
fileHash (FilePath -> PlotM Word) -> [FilePath] -> [PlotM Word]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [FilePath]
dependencies
Word -> PlotM Word
forall (m :: * -> *) a. Monad m => a -> m a
return (Word -> PlotM Word) -> Word -> PlotM Word
forall a b. (a -> b) -> a -> b
$
Int -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word) -> Int -> Word
forall a b. (a -> b) -> a -> b
$
((Int, Text, Int, FilePath),
(Int, [Word], [(Text, Text)], FilePath))
-> Int
forall a. Hashable a => a -> Int
hash
( ( Toolkit -> Int
forall a. Enum a => a -> Int
fromEnum (Renderer -> Toolkit
rendererToolkit Renderer
renderer_),
Text
script,
SaveFormat -> Int
forall a. Enum a => a -> Int
fromEnum SaveFormat
saveFormat,
FilePath
directory
),
( Int
dpi,
[Word]
dependenciesHash,
[(Text, Text)]
extraAttrs,
Version -> FilePath
forall a. Show a => a -> FilePath
show Version
version
)
)
figurePath :: FigureSpec -> PlotM FilePath
figurePath :: FigureSpec -> PlotM FilePath
figurePath FigureSpec
spec = do
Word
fh <- FigureSpec -> PlotM Word
figureContentHash FigureSpec
spec
let ext :: FilePath
ext = SaveFormat -> FilePath
extension (SaveFormat -> FilePath)
-> (FigureSpec -> SaveFormat) -> FigureSpec -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FigureSpec -> SaveFormat
saveFormat (FigureSpec -> FilePath) -> FigureSpec -> FilePath
forall a b. (a -> b) -> a -> b
$ FigureSpec
spec
stem :: FilePath
stem = (FilePath -> FilePath -> FilePath)
-> FilePath -> FilePath -> FilePath
forall a b c. (a -> b -> c) -> b -> a -> c
flip FilePath -> FilePath -> FilePath
addExtension FilePath
ext (FilePath -> FilePath) -> (Word -> FilePath) -> Word -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath -> FilePath
forall a. Monoid a => a -> a -> a
mappend FilePath
"pandocplot" (FilePath -> FilePath) -> (Word -> FilePath) -> Word -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word -> FilePath
forall a. Show a => a -> FilePath
show (Word -> FilePath) -> Word -> FilePath
forall a b. (a -> b) -> a -> b
$ Word
fh
FilePath -> PlotM FilePath
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath -> PlotM FilePath) -> FilePath -> PlotM FilePath
forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath
normalise (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ FigureSpec -> FilePath
directory FigureSpec
spec FilePath -> FilePath -> FilePath
</> FilePath
stem
writeSource :: FigureSpec -> PlotM ()
writeSource :: FigureSpec -> StateT PlotState (ReaderT RuntimeEnv IO) ()
writeSource FigureSpec
spec = do
let rdr :: Renderer
rdr = FigureSpec -> Renderer
renderer_ FigureSpec
spec
language :: Text
language = Renderer -> Text
rendererLanguage Renderer
rdr
FilePath
scp <- FigureSpec -> PlotM FilePath
sourceCodePath FigureSpec
spec
let doc :: Pandoc
doc = Meta -> [Block] -> Pandoc
Pandoc Meta
forall a. Monoid a => a
mempty [Attr -> Text -> Block
CodeBlock (Text
forall a. Monoid a => a
mempty, [Text
language], [(Text, Text)]
forall a. Monoid a => a
mempty) (FigureSpec -> Text
script FigureSpec
spec)]
renderSource :: Template Text -> StateT PlotState (ReaderT RuntimeEnv IO) ()
renderSource = \Template Text
template -> do
let opts :: WriterOptions
opts = WriterOptions
forall a. Default a => a
def {writerTemplate :: Maybe (Template Text)
writerTemplate = Template Text -> Maybe (Template Text)
forall a. a -> Maybe a
Just Template Text
template}
t :: Text
t = (PandocError -> Text)
-> (Text -> Text) -> Either PandocError Text -> Text
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Text -> PandocError -> Text
forall a b. a -> b -> a
const Text
forall a. Monoid a => a
mempty) Text -> Text
forall a. a -> a
id (Either PandocError Text -> Text)
-> Either PandocError Text -> Text
forall a b. (a -> b) -> a -> b
$ PandocPure Text -> Either PandocError Text
forall a. PandocPure a -> Either PandocError a
runPure (WriterOptions -> Pandoc -> PandocPure Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Pandoc -> m Text
writeHtml5String WriterOptions
opts Pandoc
doc PandocPure Text -> (Text -> PandocPure Text) -> PandocPure Text
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> PandocPure Text
forall (m :: * -> *). PandocMonad m => Text -> m Text
makeSelfContained)
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 -> Text -> IO ()
T.writeFile FilePath
scp Text
t
(FilePath -> StateT PlotState (ReaderT RuntimeEnv IO) ())
-> (Template Text -> StateT PlotState (ReaderT RuntimeEnv IO) ())
-> Either FilePath (Template Text)
-> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Text -> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall (m :: * -> *). (MonadLogger m, MonadIO m) => Text -> m ()
err (Text -> StateT PlotState (ReaderT RuntimeEnv IO) ())
-> (FilePath -> Text)
-> FilePath
-> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Text
pack) Template Text -> StateT PlotState (ReaderT RuntimeEnv IO) ()
renderSource (Either FilePath (Template Text)
-> StateT PlotState (ReaderT RuntimeEnv IO) ())
-> Either FilePath (Template Text)
-> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall a b. (a -> b) -> a -> b
$ Identity (Either FilePath (Template Text))
-> Either FilePath (Template Text)
forall a. Identity a -> a
runIdentity (Identity (Either FilePath (Template Text))
-> Either FilePath (Template Text))
-> Identity (Either FilePath (Template Text))
-> Either FilePath (Template Text)
forall a b. (a -> b) -> a -> b
$ FilePath -> Text -> Identity (Either FilePath (Template Text))
forall (m :: * -> *) a.
(TemplateMonad m, TemplateTarget a) =>
FilePath -> Text -> m (Either FilePath (Template a))
compileTemplate FilePath
forall a. Monoid a => a
mempty Text
sourceTemplate
sourceTemplate :: Text
sourceTemplate :: Text
sourceTemplate = FilePath -> Text
pack $(FilePath
FilePath -> FilePath
forall a. IsString a => FilePath -> a
sourceTemplate_)