{-# LANGUAGE OverloadedStrings #-}
module Text.Pandoc.Filter.Plot.Renderers.Prelude
( module Prelude,
module Text.Pandoc.Filter.Plot.Monad,
Text,
st,
unpack,
commandSuccess,
existsOnPath,
appendCapture,
toRPath,
)
where
import Data.Functor ((<&>))
import Data.Maybe (isJust)
import Data.Text (Text, unpack)
import System.Directory (findExecutable)
import System.Exit (ExitCode (..))
import System.FilePath (isPathSeparator)
import Text.Pandoc.Filter.Plot.Monad
import Text.Shakespeare.Text (st)
commandSuccess ::
FilePath ->
Text ->
PlotM Bool
commandSuccess :: FilePath -> Text -> PlotM Bool
commandSuccess FilePath
fp Text
s = do
(ExitCode
ec, Text
_) <- FilePath -> Text -> PlotM (ExitCode, Text)
runCommand FilePath
fp Text
s
Bool -> PlotM Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> PlotM Bool) -> Bool -> PlotM Bool
forall a b. (a -> b) -> a -> b
$ ExitCode
ec ExitCode -> ExitCode -> Bool
forall a. Eq a => a -> a -> Bool
== ExitCode
ExitSuccess
existsOnPath :: FilePath -> IO Bool
existsOnPath :: FilePath -> IO Bool
existsOnPath FilePath
fp = FilePath -> IO (Maybe FilePath)
findExecutable FilePath
fp IO (Maybe FilePath) -> (Maybe FilePath -> Bool) -> IO Bool
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> Maybe FilePath -> Bool
forall a. Maybe a -> Bool
isJust
appendCapture ::
(FigureSpec -> FilePath -> Script) ->
FigureSpec ->
FilePath ->
Script
appendCapture :: (FigureSpec -> FilePath -> Text) -> FigureSpec -> FilePath -> Text
appendCapture FigureSpec -> FilePath -> Text
f FigureSpec
s FilePath
fp = [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat [FigureSpec -> Text
script FigureSpec
s, Text
"\n", FigureSpec -> FilePath -> Text
f FigureSpec
s FilePath
fp]
toRPath :: FilePath -> FilePath
toRPath :: FilePath -> FilePath
toRPath = (Char -> Char) -> FilePath -> FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Char
c -> if Char -> Bool
isPathSeparator Char
c then Char
'/' else Char
c)