{-# OPTIONS_GHC -Wall #-}
module Physics.Learn.Visual.PlotTools
( label
, postscript
, psFile
, examplePlot1
, examplePlot2
, plotXYCurve
)
where
import Graphics.Gnuplot.Simple
( Attribute(..)
, plotFunc
, plotPath
)
import Physics.Learn.Curve
( Curve(..)
)
import Physics.Learn.Position
( cartesianCoordinates
)
label :: String -> (Double,Double) -> Attribute
label name (x,y)
= Custom "label" [show name ++ " at " ++ show x ++ "," ++ show y]
postscript :: Attribute
postscript = Custom "term" ["postscript"]
psFile :: FilePath -> Attribute
psFile file = Custom "output" [show file]
examplePlot1 :: IO ()
examplePlot1 = plotFunc [Title "Cosine Wave"
,XLabel "Time (ms)"
,YLabel "Velocity"
,label "Albert Einstein" (2,0.8)
] [0,0.01..10::Double] cos
examplePlot2 :: IO ()
examplePlot2 = plotFunc [Title "Cosine Wave"
,XLabel "Time (ms)"
,YLabel "Velocity of Car"
,label "Albert Einstein" (2,0.8)
,postscript
,psFile "post1.ps"
] [0,0.01..10::Double] cos
plotXYCurve :: Curve -> IO ()
plotXYCurve (Curve f a b)
= plotPath [] [(x,y) | t <- [a,a+dt..b]
, let (x,y,_) = cartesianCoordinates (f t)]
where
dt = (b-a)/1000