module Graphics.Gnuplot.Private.Plot where
import qualified Graphics.Gnuplot.Private.Display as Display
import qualified Graphics.Gnuplot.Private.FrameOptionSet as OptionSet
import qualified Graphics.Gnuplot.Private.Graph as Graph
import qualified Graphics.Gnuplot.Private.File as FileClass
import qualified Graphics.Gnuplot.File as File
import Graphics.Gnuplot.Utility (quote, commaConcat, )
import qualified Control.Monad.Trans.Reader as MR
import qualified Control.Monad.Trans.State as MS
import qualified Control.Monad.Trans.Class as MT
import qualified Data.Accessor.Monad.Trans.State as AccState
import qualified Data.Accessor.Tuple as AccTuple
import qualified Data.Foldable as Fold
import Control.Monad (liftM2, return, )
import Data.Monoid (Monoid, mempty, mappend, )
import Data.Semigroup (Semigroup, (<>), )
import Data.Maybe (Maybe(Just, Nothing), mapMaybe, )
import Data.List (concatMap, map, (++), )
import Data.Function (($), (.), )
import qualified System.FilePath as Path
import System.FilePath (FilePath, (</>), )
import Prelude (Functor, fmap, String, show, Int, succ, writeFile, )
newtype T graph = Cons (MS.StateT Int (MR.Reader FilePath) [File graph])
pure :: [File graph] -> T graph
pure :: [File graph] -> T graph
pure = StateT Int (Reader FilePath) [File graph] -> T graph
forall graph. StateT Int (Reader FilePath) [File graph] -> T graph
Cons (StateT Int (Reader FilePath) [File graph] -> T graph)
-> ([File graph] -> StateT Int (Reader FilePath) [File graph])
-> [File graph]
-> T graph
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [File graph] -> StateT Int (Reader FilePath) [File graph]
forall (m :: * -> *) a. Monad m => a -> m a
return
instance Semigroup (T graph) where
Cons StateT Int (Reader FilePath) [File graph]
s0 <> :: T graph -> T graph -> T graph
<> Cons StateT Int (Reader FilePath) [File graph]
s1 = StateT Int (Reader FilePath) [File graph] -> T graph
forall graph. StateT Int (Reader FilePath) [File graph] -> T graph
Cons (([File graph] -> [File graph] -> [File graph])
-> StateT Int (Reader FilePath) [File graph]
-> StateT Int (Reader FilePath) [File graph]
-> StateT Int (Reader FilePath) [File graph]
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 [File graph] -> [File graph] -> [File graph]
forall a. Semigroup a => a -> a -> a
(<>) StateT Int (Reader FilePath) [File graph]
s0 StateT Int (Reader FilePath) [File graph]
s1)
instance Monoid (T graph) where
mempty :: T graph
mempty = StateT Int (Reader FilePath) [File graph] -> T graph
forall graph. StateT Int (Reader FilePath) [File graph] -> T graph
Cons (StateT Int (Reader FilePath) [File graph] -> T graph)
-> StateT Int (Reader FilePath) [File graph] -> T graph
forall a b. (a -> b) -> a -> b
$ [File graph] -> StateT Int (Reader FilePath) [File graph]
forall (m :: * -> *) a. Monad m => a -> m a
return [File graph]
forall a. Monoid a => a
mempty
mappend :: T graph -> T graph -> T graph
mappend = T graph -> T graph -> T graph
forall a. Semigroup a => a -> a -> a
(<>)
withUniqueFile :: String -> [graph] -> T graph
withUniqueFile :: FilePath -> [graph] -> T graph
withUniqueFile FilePath
content [graph]
graphs = StateT Int (Reader FilePath) [File graph] -> T graph
forall graph. StateT Int (Reader FilePath) [File graph] -> T graph
Cons (StateT Int (Reader FilePath) [File graph] -> T graph)
-> StateT Int (Reader FilePath) [File graph] -> T graph
forall a b. (a -> b) -> a -> b
$ do
Int
n <- StateT Int (Reader FilePath) Int
forall (m :: * -> *) s. Monad m => StateT s m s
MS.get
FilePath
dir <- ReaderT FilePath Identity FilePath
-> StateT Int (Reader FilePath) FilePath
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
MT.lift ReaderT FilePath Identity FilePath
forall (m :: * -> *) r. Monad m => ReaderT r m r
MR.ask
Int -> StateT Int (Reader FilePath) ()
forall (m :: * -> *) s. Monad m => s -> StateT s m ()
MS.put (Int -> StateT Int (Reader FilePath) ())
-> Int -> StateT Int (Reader FilePath) ()
forall a b. (a -> b) -> a -> b
$ Int -> Int
forall a. Enum a => a -> a
succ Int
n
[File graph] -> StateT Int (Reader FilePath) [File graph]
forall (m :: * -> *) a. Monad m => a -> m a
return ([File graph] -> StateT Int (Reader FilePath) [File graph])
-> [File graph] -> StateT Int (Reader FilePath) [File graph]
forall a b. (a -> b) -> a -> b
$
[FilePath -> Maybe FilePath -> [graph] -> File graph
forall graph. FilePath -> Maybe FilePath -> [graph] -> File graph
File
(FilePath
dir FilePath -> FilePath -> FilePath
</> FilePath -> FilePath -> FilePath
Path.addExtension (FilePath
tmpFileStem FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Int -> FilePath
forall a. Show a => a -> FilePath
show Int
n) FilePath
"csv")
(FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just FilePath
content) [graph]
graphs]
fromGraphs :: FilePath -> [graph] -> T graph
fromGraphs :: FilePath -> [graph] -> T graph
fromGraphs FilePath
name [graph]
gs =
[File graph] -> T graph
forall graph. [File graph] -> T graph
pure [FilePath -> Maybe FilePath -> [graph] -> File graph
forall graph. FilePath -> Maybe FilePath -> [graph] -> File graph
File FilePath
name Maybe FilePath
forall a. Maybe a
Nothing [graph]
gs]
data File graph =
File {
File graph -> FilePath
filename_ :: FilePath,
File graph -> Maybe FilePath
content_ :: Maybe String,
File graph -> [graph]
graphs_ :: [graph]
}
instance FileClass.C (File graph) where
write :: File graph -> IO ()
write (File FilePath
fn Maybe FilePath
cont [graph]
_) =
(FilePath -> IO ()) -> Maybe FilePath -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
Fold.mapM_ (FilePath -> FilePath -> IO ()
writeFile FilePath
fn) Maybe FilePath
cont
tmpFileStem :: FilePath
tmpFileStem :: FilePath
tmpFileStem = FilePath
"curve"
instance Functor T where
fmap :: (a -> b) -> T a -> T b
fmap a -> b
f (Cons StateT Int (Reader FilePath) [File a]
mp) =
StateT Int (Reader FilePath) [File b] -> T b
forall graph. StateT Int (Reader FilePath) [File graph] -> T graph
Cons (StateT Int (Reader FilePath) [File b] -> T b)
-> StateT Int (Reader FilePath) [File b] -> T b
forall a b. (a -> b) -> a -> b
$
([File a] -> [File b])
-> StateT Int (Reader FilePath) [File a]
-> StateT Int (Reader FilePath) [File b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((File a -> File b) -> [File a] -> [File b]
forall a b. (a -> b) -> [a] -> [b]
map (\File a
file -> File a
file{graphs_ :: [b]
graphs_ = (a -> b) -> [a] -> [b]
forall a b. (a -> b) -> [a] -> [b]
map a -> b
f ([a] -> [b]) -> [a] -> [b]
forall a b. (a -> b) -> a -> b
$ File a -> [a]
forall graph. File graph -> [graph]
graphs_ File a
file}))
StateT Int (Reader FilePath) [File a]
mp
toScript :: Graph.C graph => T graph -> Display.Script
toScript :: T graph -> Script
toScript p :: T graph
p@(Cons StateT Int (Reader FilePath) [File graph]
mp) =
StateT (Int, OptionSet) (Reader FilePath) Body -> Script
Display.Script (StateT (Int, OptionSet) (Reader FilePath) Body -> Script)
-> StateT (Int, OptionSet) (Reader FilePath) Body -> Script
forall a b. (a -> b) -> a -> b
$ do
[File graph]
blocks <- T (Int, OptionSet) Int
-> StateT Int (Reader FilePath) [File graph]
-> StateT (Int, OptionSet) (Reader FilePath) [File graph]
forall (m :: * -> *) r s a.
Monad m =>
T r s -> StateT s m a -> StateT r m a
AccState.liftT T (Int, OptionSet) Int
forall a b. T (a, b) a
AccTuple.first StateT Int (Reader FilePath) [File graph]
mp
let files :: [T]
files =
(File graph -> Maybe T) -> [File graph] -> [T]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe
(\File graph
blk -> (FilePath -> T) -> Maybe FilePath -> Maybe T
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (FilePath -> FilePath -> T
File.Cons (File graph -> FilePath
forall graph. File graph -> FilePath
filename_ File graph
blk)) (File graph -> Maybe FilePath
forall graph. File graph -> Maybe FilePath
content_ File graph
blk))
[File graph]
blocks
graphs :: [FilePath]
graphs =
(File graph -> [FilePath]) -> [File graph] -> [FilePath]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap
(\File graph
blk ->
(graph -> FilePath) -> [graph] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map
(\graph
gr ->
FilePath -> FilePath
quote (File graph -> FilePath
forall graph. File graph -> FilePath
filename_ File graph
blk) FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++
graph -> FilePath
forall graph. C graph => graph -> FilePath
Graph.toString graph
gr) ([graph] -> [FilePath]) -> [graph] -> [FilePath]
forall a b. (a -> b) -> a -> b
$ File graph -> [graph]
forall graph. File graph -> [graph]
graphs_ File graph
blk) ([File graph] -> [FilePath]) -> [File graph] -> [FilePath]
forall a b. (a -> b) -> a -> b
$
[File graph]
blocks
Body -> StateT (Int, OptionSet) (Reader FilePath) Body
forall (m :: * -> *) a. Monad m => a -> m a
return (Body -> StateT (Int, OptionSet) (Reader FilePath) Body)
-> Body -> StateT (Int, OptionSet) (Reader FilePath) Body
forall a b. (a -> b) -> a -> b
$
[T] -> [FilePath] -> Body
Display.Body [T]
files
[Command graph -> FilePath
forall graph. Command graph -> FilePath
Graph.commandString (T graph -> Command graph
forall graph. C graph => T graph -> Command graph
plotCmd T graph
p) FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ [FilePath] -> FilePath
commaConcat [FilePath]
graphs]
optionsToScript :: Graph.C graph => OptionSet.T graph -> Display.Script
optionsToScript :: T graph -> Script
optionsToScript T graph
opts =
StateT (Int, OptionSet) (Reader FilePath) Body -> Script
Display.Script (StateT (Int, OptionSet) (Reader FilePath) Body -> Script)
-> StateT (Int, OptionSet) (Reader FilePath) Body -> Script
forall a b. (a -> b) -> a -> b
$
T (Int, OptionSet) OptionSet
-> StateT OptionSet (Reader FilePath) Body
-> StateT (Int, OptionSet) (Reader FilePath) Body
forall (m :: * -> *) r s a.
Monad m =>
T r s -> StateT s m a -> StateT r m a
AccState.liftT T (Int, OptionSet) OptionSet
forall a b. T (a, b) b
AccTuple.second (StateT OptionSet (Reader FilePath) Body
-> StateT (Int, OptionSet) (Reader FilePath) Body)
-> StateT OptionSet (Reader FilePath) Body
-> StateT (Int, OptionSet) (Reader FilePath) Body
forall a b. (a -> b) -> a -> b
$ do
OptionSet
opts0 <- StateT OptionSet (Reader FilePath) OptionSet
forall (m :: * -> *) s. Monad m => StateT s m s
MS.get
let opts1 :: OptionSet
opts1 = T graph -> OptionSet
forall graph. T graph -> OptionSet
OptionSet.decons T graph
opts
OptionSet -> StateT OptionSet (Reader FilePath) ()
forall (m :: * -> *) s. Monad m => s -> StateT s m ()
MS.put OptionSet
opts1
Body -> StateT OptionSet (Reader FilePath) Body
forall (m :: * -> *) a. Monad m => a -> m a
return (Body -> StateT OptionSet (Reader FilePath) Body)
-> Body -> StateT OptionSet (Reader FilePath) Body
forall a b. (a -> b) -> a -> b
$
[T] -> [FilePath] -> Body
Display.Body [] ([FilePath] -> Body) -> [FilePath] -> Body
forall a b. (a -> b) -> a -> b
$
OptionSet -> OptionSet -> [FilePath]
OptionSet.diffToString OptionSet
opts0 OptionSet
opts1
defltOpts :: Graph.C graph => T graph -> OptionSet.T graph
defltOpts :: T graph -> T graph
defltOpts T graph
_ = T graph
forall graph. C graph => T graph
Graph.defltOptions
instance Graph.C graph => Display.C (T graph) where
toScript :: T graph -> Script
toScript T graph
plot =
T graph -> Script
forall graph. C graph => T graph -> Script
optionsToScript (T graph -> T graph
forall graph. C graph => T graph -> T graph
defltOpts T graph
plot) Script -> Script -> Script
forall a. Monoid a => a -> a -> a
`mappend` T graph -> Script
forall graph. C graph => T graph -> Script
toScript T graph
plot
plotCmd :: Graph.C graph => T graph -> Graph.Command graph
plotCmd :: T graph -> Command graph
plotCmd T graph
_plot = Command graph
forall graph. C graph => Command graph
Graph.command