summaryrefslogtreecommitdiff
path: root/02.05.hs
blob: bad736774ed855b5ffb12c48edb441235940f039 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30

import System.Random
import Control.Monad.State
import Data.List.Split (chunksOf)

import Graphics.Rendering.Chart.Easy
import Graphics.Rendering.Chart.Backend.Cairo

import Data.Colour.Names
import Diagrams.Prelude
import Diagrams.Backend.SVG.CmdLine

randomWalk :: (RandomGen g) => Int -> Int -> State g [[Double]]
randomWalk d n = get >>= (\g -> let (g1, g2) = split g in (put g1) >> (return $ take n $ scanl (\x y -> map (uncurry (+)) $ zip x y) (replicate d 0.0)  $ chunksOf d $ randomRs (-0.5,0.5) g2))

drawWalk :: [[Double]] -> Diagram B
drawWalk w = fromVertices $ (\[x, y] -> p2 (x, y)) <$> w

main = do
  g <- newStdGen
  let (w10, g2) = runState (randomWalk 2 10) g
  let (w1000, g3) = runState (randomWalk 2 1000) g2
  let (w100000, g4) = runState (randomWalk 2 100000) g3
--  mainWith $ foldr1 Diagrams.Prelude.atop [lc red $ drawWalk w10, lc blue $ drawWalk w1000, lc green $ drawWalk w100000]
  let (e1, g5) = runState (sequence $ replicate 10000 $ randomWalk 2 2) g4
  let (e10, g6) = runState (sequence $ replicate 10000 $ randomWalk 2 11) g5
  mainWith $ foldr1 Diagrams.Prelude.atop [mconcat $ map (place (lw Diagrams.Prelude.none $ fc yellow $ ((circle 0.01) :: Diagram B))) (map (\[x, y] -> p2 (x, y)) (map last e1)), mconcat $  map (place (lw Diagrams.Prelude.none $ fc black $ circle 0.01)) (map (\[x, y] -> p2 (x, y)) (map last e10))]