module Sound.SC3.Plot where
import qualified Graphics.Gnuplot.Simple as G
import qualified Graphics.Gnuplot.Value.Tuple as G
import Sound.SC3.Plot.Histogram
import Sound.SC3.UGen.Envelope
import System.Directory
import System.FilePath
import System.Process
eps :: G.Attribute
eps = G.EPS "/tmp/plot.eps"
plotEnvelope :: (G.C t,Ord t, Floating t, Enum t) => [Envelope t] -> IO ()
plotEnvelope = G.plotLists [] . map (envelope_render 256)
plotHistogram :: G.C t => [Histogram t] -> IO ()
plotHistogram =
let f (Histogram x y) = zip x y
in G.plotLists [] . map f
type Table x = [x]
plotTable :: G.C t => [Table t] -> IO ()
plotTable = G.plotLists []
type Coord x = [(x,x)]
plotCoord :: G.C t => [Coord t] -> IO ()
plotCoord =
let s = G.defaultStyle {G.plotType = G.LinesPoints}
in G.plotPathsStyle [] . zip (repeat s)
type Path x = [(x,x,x)]
plotPath :: (Num t,Show t) => Path t -> IO ()
plotPath p = do
tmp <- getTemporaryDirectory
let nm = tmp </> "plotPath.data"
cm = "splot '" ++ nm ++ "' with l"
f (x,y,z) = unwords (map show [x,y,z])
_ <- writeFile nm (unlines (map f p))
_ <- rawSystem "gnuplot" ["-p","-e",cm]
return ()