{-# LANGUAGE OverloadedStrings #-}
module Text.Pandoc.Filter.Plot.Renderers.Prelude
  ( module Prelude,
    module Text.Pandoc.Filter.Plot.Monad,
    Text,
    st,
    unpack,
    findExecutable,
    appendCapture,
    toRPath,
  )
where
import Data.Text (Text, unpack)
import System.Directory (findExecutable)
import System.FilePath (isPathSeparator)
import Text.Pandoc.Filter.Plot.Monad
import Text.Shakespeare.Text (st)
appendCapture ::
  (FigureSpec -> FilePath -> Script) ->
  FigureSpec ->
  FilePath ->
  Script
appendCapture :: (FigureSpec -> FilePath -> Script)
-> FigureSpec -> FilePath -> Script
appendCapture FigureSpec -> FilePath -> Script
f FigureSpec
s FilePath
fp = [Script] -> Script
forall a. Monoid a => [a] -> a
mconcat [FigureSpec -> Script
script FigureSpec
s, Script
"\n", FigureSpec -> FilePath -> Script
f FigureSpec
s FilePath
fp]
toRPath :: FilePath -> FilePath
toRPath :: FilePath -> FilePath
toRPath = (Char -> Char) -> FilePath -> FilePath
forall a b. (a -> b) -> [a] -> [b]
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)