module Graphics.Gnuplot.Private.Display where
import qualified Graphics.Gnuplot.Private.FrameOption as Option
import qualified Graphics.Gnuplot.File as File
import qualified Data.Map as Map
import qualified Control.Monad.Trans.Reader as MR
import qualified Control.Monad.Trans.State as MS
import Control.Monad (liftM2, return, )
import Data.Monoid (Monoid, mempty, mappend, )
import Data.Semigroup (Semigroup, (<>), )
import Prelude (FilePath, String, Int, ($), (.), )
newtype Script =
Script {
Script -> StateT (Int, OptionSet) (Reader FilePath) Body
runScript :: MS.StateT (Int, OptionSet) (MR.Reader FilePath) Body
}
pure :: Body -> Script
pure :: Body -> Script
pure = StateT (Int, OptionSet) (Reader FilePath) Body -> Script
Script (StateT (Int, OptionSet) (Reader FilePath) Body -> Script)
-> (Body -> StateT (Int, OptionSet) (Reader FilePath) Body)
-> Body
-> Script
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Body -> StateT (Int, OptionSet) (Reader FilePath) Body
forall (m :: * -> *) a. Monad m => a -> m a
return
data Body =
Body {
Body -> [T]
files :: [File.T],
Body -> [FilePath]
commands :: [String]
}
type OptionSet = Map.Map Option.T [String]
instance Semigroup Script where
Script StateT (Int, OptionSet) (Reader FilePath) Body
b0 <> :: Script -> Script -> Script
<> Script StateT (Int, OptionSet) (Reader FilePath) Body
b1 = StateT (Int, OptionSet) (Reader FilePath) Body -> Script
Script ((Body -> Body -> Body)
-> StateT (Int, OptionSet) (Reader FilePath) Body
-> StateT (Int, OptionSet) (Reader FilePath) Body
-> StateT (Int, OptionSet) (Reader FilePath) Body
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 Body -> Body -> Body
forall a. Semigroup a => a -> a -> a
(<>) StateT (Int, OptionSet) (Reader FilePath) Body
b0 StateT (Int, OptionSet) (Reader FilePath) Body
b1)
instance Monoid Script where
mempty :: Script
mempty = StateT (Int, OptionSet) (Reader FilePath) Body -> Script
Script (StateT (Int, OptionSet) (Reader FilePath) Body -> Script)
-> StateT (Int, OptionSet) (Reader FilePath) Body -> Script
forall a b. (a -> b) -> a -> b
$ Body -> StateT (Int, OptionSet) (Reader FilePath) Body
forall (m :: * -> *) a. Monad m => a -> m a
return Body
forall a. Monoid a => a
mempty
mappend :: Script -> Script -> Script
mappend = Script -> Script -> Script
forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup Body where
Body [T]
f0 [FilePath]
c0 <> :: Body -> Body -> Body
<> Body [T]
f1 [FilePath]
c1 = [T] -> [FilePath] -> Body
Body ([T]
f0 [T] -> [T] -> [T]
forall a. Semigroup a => a -> a -> a
<> [T]
f1) ([FilePath]
c0 [FilePath] -> [FilePath] -> [FilePath]
forall a. Semigroup a => a -> a -> a
<> [FilePath]
c1)
instance Monoid Body where
mempty :: Body
mempty = [T] -> [FilePath] -> Body
Body [T]
forall a. Monoid a => a
mempty [FilePath]
forall a. Monoid a => a
mempty
mappend :: Body -> Body -> Body
mappend = Body -> Body -> Body
forall a. Semigroup a => a -> a -> a
(<>)
class C gfx where
toScript :: gfx -> Script