module Sound.SC3.Plot where import qualified Graphics.Gnuplot.Simple as G {- gnuplot -} import qualified Graphics.Gnuplot.Value.Tuple as G import Sound.SC3.Plot.Histogram import Sound.SC3.UGen.Envelope {- hsc3 -} import System.Directory {- directory -} import System.FilePath {- filepath -} import System.Process {- process -} eps :: G.Attribute eps = G.EPS "/tmp/plot.eps" -- | Plot 'Envelope' data. -- -- > import Sound.SC3 -- > plotEnvelope [envPerc 0.2 1,envSine 1 0.75] plotEnvelope :: (G.C t,Ord t, Floating t, Enum t) => [Envelope t] -> IO () plotEnvelope = G.plotLists [] . map (envelope_render 256) -- | Plot 'Histogram' data. -- -- > plotHistogram [histogram 3 [0,0,1,2,2,2]] 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] -- | Plot 'Table' data, ie. /y/ values at equal /x/ increments. -- -- > plotTable [[0,2..12],[0..6],[0,4..12]] plotTable :: G.C t => [Table t] -> IO () plotTable = G.plotLists [] type Coord x = [(x,x)] {--| Plot two-dimensional coordinates. > let {t = [-pi,-pi + 0.01 .. pi] > ;f r t = (r t * cos t,r t * sin t)} > in plotCoord [zip (map cos t) (map sin t) > ,zip (map cos t) (map (sin . (* 3)) t) > ,map (f ((/ (2 * pi)) . (+ pi))) t] -} 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)] {--| Three dimensional variant of 'plotCoord'. > let {t = [-pi,-pi + 0.01 .. pi] > ;f n d = map (sin . (+) d . (*) n) t > ;(x,y,z) = (f 1 (pi/2),f 3 0,f 5 0)} > in plotPath (zip3 x y z) > let {t' = [-pi,-pi + 0.01 .. pi] > ;e' = [0,0.005 .. pi] > ;f a b r e t = ((a * t + r * sin e) * cos t > ,(a * t + r * sin e) * sin t > ,b * t + r * (1 - cos e))} > in plotPath (zipWith (f 1 1 1) e' t') -} 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 ()