{-# LANGUAGE Arrows #-} --- Imports --- -- Goal -- import Goal.Core import Goal.Geometry import Goal.Simulation import Goal.Probability --- Main --- main :: IO () main = do let sz = 5 nstps = 20 ts = [1..] :: [Int] x0 = 1 xs = [1..sz] smtx = fromList (markovTensor xs) . concat . replicate sz $ replicate sz (1/fromIntegral sz) chn <- runWithSystemRandom $ markovChain smtx x0 let chainToRenderable ln = toRenderable . execEC $ do layout_y_axis . laxis_generate .= scaledIntAxis defaultIntAxis (0,sz + 1) plot . liftEC $ do plot_lines_style .= solidLine 3 (opaque red) plot_lines_title .= "Markov Chain" plot_lines_values .= [ln] let mly = proc t -> do x <- chn -< () stps <- chainWindow nstps -< (t,x) returnA -< chainToRenderable stps initGUI apst <- newAnimationPost 2 (Just 10) forkIO $ streamM_ mly (postRenderable apst) ts mainGUI