[haskell-gnuplot] gnuplot - 3d curve
haskell at henning-thielemann.de
haskell at henning-thielemann.de
Mon Jan 14 09:52:50 GMT 2013
Hi Rohan,
On Mon, 14 Jan 2013, Rohan Drape wrote:
> i'm trying to write a 3d equivalent to the 2d 'plotCoord' function below:
>
> type Coord x = [(x,x)]
>
> -- > plotCoord [[(0,0),(0.15,0.35),(0.75,0.25),(0.35,0.15)]]
> plotCoord :: G.C t => [Coord t] -> IO ()
> plotCoord =
> let s = G.defaultStyle {G.plotType = G.LinesPoints}
> in G.plotPathsStyle [] . zip (repeat s)
>
> i got so far as the below, but i'm not sure of the plot type to use
> (ie. neither impulses, vectors or pm3d seems correct).
>
> type Path x = [(x,x,x)]
>
> -- > plotPath [(0,0,0),(0.5,1,0),(0,1,1),(0.25,0.5,0.75)]
> plotPath :: Path Double -> IO ()
> plotPath p =
> let i = Graphics.Gnuplot.Graph.ThreeDimensional.?
> t = Graphics.Gnuplot.Terminal.X11.cons
> o = Graphics.Gnuplot.Frame.OptionSet.deflt
> g = Graphics.Gnuplot.Plot.ThreeDimensional.cloud i p
> f = Graphics.Gnuplot.Frame.cons o g
> in G.plot t f >> return ()
>
> the function below indicates what i'm after...
>
> -- > let {t = [-pi,-pi + 0.01 .. pi]
> -- > ;f n = map (sin . (*) n) t
> -- > ;(x,y,z) = (f 3,f 4,f 9)}
> -- > in plotPath (zip3 x y z)
> plotPath :: (Num t,Show t) => Path t -> IO ()
> plotPath p = do
> 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 ()
The module src/Demo.hs contains a 3d plot. Does this help?
More information about the Gnuplot
mailing list