module Graphics.Gnuplot.Advanced (
plot,
plotDefault,
plotSync,
plotAsync,
fileContents,
) where
import qualified Graphics.Gnuplot.Private.FrameOptionSet as OptionSet
import qualified Graphics.Gnuplot.Private.Display as Display
import qualified Graphics.Gnuplot.Private.Terminal as Terminal
import qualified Graphics.Gnuplot.Terminal.Default as DefaultTerm
import qualified Graphics.Gnuplot.File as File
import qualified Graphics.Gnuplot.Private.Command as Cmd
import Control.Concurrent (ThreadId, forkIO, )
import System.Exit (ExitCode, )
import qualified Control.Monad.Trans.Reader as MR
import qualified Control.Monad.Trans.State as MS
import Data.Monoid (Monoid, mempty, )
import Control.Functor.HT (void, )
import Data.Tuple.HT (mapFst, )
plot ::
(Terminal.C terminal, Display.C gfx) =>
terminal -> gfx -> IO ExitCode
plot :: terminal -> gfx -> IO ExitCode
plot terminal
term gfx
gfx =
case terminal -> T
forall terminal. C terminal => terminal -> T
Terminal.canonical terminal
term of
T
cterm ->
Bool -> IO ExitCode -> IO ExitCode
Cmd.asyncIfInteractive
(T -> Bool
Terminal.interactive T
cterm)
(T -> gfx -> IO ExitCode
forall gfx. C gfx => T -> gfx -> IO ExitCode
plotCore T
cterm gfx
gfx)
plotAsync ::
(Terminal.C terminal, Display.C gfx) =>
terminal -> gfx -> IO ThreadId
plotAsync :: terminal -> gfx -> IO ThreadId
plotAsync terminal
term gfx
gfx = IO () -> IO ThreadId
forkIO (IO () -> IO ThreadId) -> IO () -> IO ThreadId
forall a b. (a -> b) -> a -> b
$ IO ExitCode -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO ExitCode -> IO ()) -> IO ExitCode -> IO ()
forall a b. (a -> b) -> a -> b
$ terminal -> gfx -> IO ExitCode
forall terminal gfx.
(C terminal, C gfx) =>
terminal -> gfx -> IO ExitCode
plotSync terminal
term gfx
gfx
plotSync ::
(Terminal.C terminal, Display.C gfx) =>
terminal -> gfx -> IO ExitCode
plotSync :: terminal -> gfx -> IO ExitCode
plotSync = T -> gfx -> IO ExitCode
forall gfx. C gfx => T -> gfx -> IO ExitCode
plotCore (T -> gfx -> IO ExitCode)
-> (terminal -> T) -> terminal -> gfx -> IO ExitCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. terminal -> T
forall terminal. C terminal => terminal -> T
Terminal.canonical
plotCore ::
(Display.C gfx) =>
Terminal.T -> gfx -> IO ExitCode
plotCore :: T -> gfx -> IO ExitCode
plotCore T
term gfx
gfx =
(FilePath -> ([FilePath], [T])) -> IO ExitCode
forall file.
C file =>
(FilePath -> ([FilePath], [file])) -> IO ExitCode
Cmd.run ((FilePath -> ([FilePath], [T])) -> IO ExitCode)
-> (FilePath -> ([FilePath], [T])) -> IO ExitCode
forall a b. (a -> b) -> a -> b
$ T -> gfx -> FilePath -> ([FilePath], [T])
forall gfx. C gfx => T -> gfx -> FilePath -> ([FilePath], [T])
render T
term gfx
gfx
fileContents ::
(Terminal.C terminal, Display.C gfx) =>
FilePath -> terminal -> gfx -> (String, [File.T])
fileContents :: FilePath -> terminal -> gfx -> (FilePath, [T])
fileContents FilePath
dir terminal
term gfx
gfx =
([FilePath] -> FilePath) -> ([FilePath], [T]) -> (FilePath, [T])
forall a c b. (a -> c) -> (a, b) -> (c, b)
mapFst [FilePath] -> FilePath
unlines (([FilePath], [T]) -> (FilePath, [T]))
-> ([FilePath], [T]) -> (FilePath, [T])
forall a b. (a -> b) -> a -> b
$ T -> gfx -> FilePath -> ([FilePath], [T])
forall gfx. C gfx => T -> gfx -> FilePath -> ([FilePath], [T])
render (terminal -> T
forall terminal. C terminal => terminal -> T
Terminal.canonical terminal
term) gfx
gfx FilePath
dir
render ::
Display.C gfx =>
Terminal.T -> gfx -> FilePath -> ([String], [File.T])
render :: T -> gfx -> FilePath -> ([FilePath], [T])
render T
term gfx
gfx FilePath
dir =
let body :: Body
body =
(Reader FilePath Body -> FilePath -> Body)
-> FilePath -> Reader FilePath Body -> Body
forall a b c. (a -> b -> c) -> b -> a -> c
flip Reader FilePath Body -> FilePath -> Body
forall r a. Reader r a -> r -> a
MR.runReader FilePath
dir (Reader FilePath Body -> Body) -> Reader FilePath Body -> Body
forall a b. (a -> b) -> a -> b
$
(StateT (Int, Plain) (Reader FilePath) Body
-> (Int, Plain) -> Reader FilePath Body)
-> (Int, Plain)
-> StateT (Int, Plain) (Reader FilePath) Body
-> Reader FilePath Body
forall a b c. (a -> b -> c) -> b -> a -> c
flip StateT (Int, Plain) (Reader FilePath) Body
-> (Int, Plain) -> Reader FilePath Body
forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m a
MS.evalStateT (Int
0, Plain
OptionSet.initial) (StateT (Int, Plain) (Reader FilePath) Body
-> Reader FilePath Body)
-> StateT (Int, Plain) (Reader FilePath) Body
-> Reader FilePath Body
forall a b. (a -> b) -> a -> b
$
Script -> StateT (Int, Plain) (Reader FilePath) Body
Display.runScript (Script -> StateT (Int, Plain) (Reader FilePath) Body)
-> Script -> StateT (Int, Plain) (Reader FilePath) Body
forall a b. (a -> b) -> a -> b
$
gfx -> Script
forall gfx. C gfx => gfx -> Script
Display.toScript gfx
gfx
in (T -> [FilePath]
Terminal.format T
term [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ Body -> [FilePath]
Display.commands Body
body,
Body -> [T]
Display.files Body
body)
plotDefault ::
(Display.C gfx) =>
gfx -> IO ExitCode
plotDefault :: gfx -> IO ExitCode
plotDefault =
T -> gfx -> IO ExitCode
forall terminal gfx.
(C terminal, C gfx) =>
terminal -> gfx -> IO ExitCode
plot T
DefaultTerm.cons
_haddockDummy :: Monoid a => a
_haddockDummy :: a
_haddockDummy = a
forall a. Monoid a => a
mempty