{-# LANGUAGE Arrows #-} --- Imports --- -- Goal -- import Goal.Core import Goal.Simulation import Goal.Geometry import Goal.Probability import qualified Data.Vector.Storable as C import qualified Numeric.LinearAlgebra.HMatrix as M --- Main --- main :: IO () main = do let dt = 0.01 fps = round $ recip dt tivl = 2 t0 = 0 ts = [t0,t0 + dt..] x0 = euclideanPoint [0] trj <- runWithSystemRandom $ itoProcess (\t _ -> C.fromList [cos t]) (\t _ -> M.fromLists [[1 + cos (2*t)]]) t0 x0 let trajectoryToRenderable ln = toRenderable . execEC $ do layout_y_axis . laxis_generate .= scaledAxis def (-6,6) plot . liftEC $ do plot_lines_title .= "Ito Process" plot_lines_style .= solidLine 3 (opaque red) plot_lines_values .= [ln] let mly = proc t -> do x <- trj -< t pth <- trajectoryWindow tivl -< (t,coordinate 0 x) returnA -< trajectoryToRenderable pth --- Gtk --- initGUI apst <- newAnimationPost 2 (Just fps) forkIO $ streamM_ mly (postRenderable apst) ts mainGUI