a one dimensional cellular automata, using comonads
25개 이상의 토픽을 선택하실 수 없습니다. Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.

213 lines
5.5KB

  1. module Main where
  2. --import System.Random
  3. import Control.Monad
  4. import System.Process
  5. import System.Random
  6. import System.Console.GetOpt
  7. import System.Environment(getArgs, getProgName)
  8. import Data.Maybe (fromMaybe)
  9. -------------------
  10. -- comonad class --
  11. -------------------
  12. class Functor w => Comonad w
  13. where
  14. (=>>) :: w a -> (w a -> b) -> w b
  15. extract :: w a -> a
  16. duplicate :: w a -> w (w a)
  17. x =>> f = fmap f (duplicate x)
  18. ------------
  19. -- spaces --
  20. ------------
  21. -- a locally focussed space
  22. data Space t = Space [t] t [t]
  23. -- spaces are also functors
  24. instance Functor Space where
  25. fmap f (Space l c r) = Space (map f l) (f c) (map f r)
  26. -- our space is a comonad
  27. instance Comonad Space where
  28. -- duplicate will create a new space where
  29. -- the focussed element is our original space
  30. -- and each side is increasingly shifted copies
  31. -- in that direction
  32. duplicate w =
  33. Space (tail $ iterate left w)
  34. w
  35. (tail $ iterate right w)
  36. -- extract simply returns the focussed element
  37. extract (Space _ c _) = c
  38. -- functions for moving the point
  39. -- of locality.
  40. -- todo: question the empty list cases
  41. -- most spaces should be infinite
  42. right :: Space t -> Space t
  43. right s@(Space l c []) = s
  44. right (Space l c (r:rs)) = Space (c:l) r rs
  45. left :: Space t -> Space t
  46. left s@(Space [] c r) = s
  47. left (Space (l:ls) c r) = Space ls l (c:r)
  48. -- bound will take an infinite space
  49. -- and bound it by i and j on each side
  50. -- (not including the focus) and
  51. -- turn it into a list for printing
  52. bound :: Int -> Int -> Space t -> [t]
  53. bound i j (Space l c r) = (reverse (take i l)) ++ (c:(take j r))
  54. -- boundw works as above, but the
  55. -- entire list will be the size
  56. -- given
  57. boundw :: Int -> Space t -> [t]
  58. boundw n = bound (x-m) x
  59. where
  60. o = if odd n then 1 else 0
  61. m = if even n then 1 else 0
  62. x = (n - o) `div` 2
  63. -----------------------
  64. -- cellular automata --
  65. -----------------------
  66. -- the states our cells can be in
  67. -- may need to provide an ordering
  68. -- may need to generalise the number
  69. -- of states
  70. data CellState = Alive | Dead
  71. deriving Eq
  72. -- how the states are displayed on screen
  73. -- this should probably be input to a function
  74. -- rather than hardcoded
  75. instance Show CellState
  76. where
  77. show Alive = "█"
  78. show Dead = " "
  79. -- a rule stating how a cell is determined
  80. rule :: Space CellState -> CellState
  81. rule (Space (l:_) _ (r:_))
  82. | l == r = Dead
  83. | otherwise = Alive
  84. -- a second rule for example
  85. rule2 :: Space CellState -> CellState
  86. rule2 (Space (l1:l2:_) m (r1:r2:_))
  87. | m == Alive && numAlive == 1 = Dead
  88. | m == Alive && numAlive == 4 = Dead
  89. | m == Dead && numAlive == 3 = Alive
  90. | otherwise = m
  91. where
  92. ns = [l1, l2, r1, r2]
  93. numAlive = length $ filter (== Alive) ns
  94. rule3 :: Space CellState -> CellState
  95. rule3 (Space (l:_) m (r:_))
  96. | l == r = m
  97. | otherwise = if m == Alive then Dead else Alive
  98. -- take a space and a rule and
  99. -- return the next space
  100. step :: (Space t -> t) -> Space t -> Space t
  101. step f w = w =>> f
  102. ---------------
  103. -- rng stuff --
  104. ---------------
  105. -- takes a generator and returns
  106. -- an infinite list of bools
  107. ilobs :: StdGen -> [Bool]
  108. ilobs rng = b : (ilobs r)
  109. where
  110. (b,r) = random rng
  111. -----------------
  112. -- gross io bs --
  113. -----------------
  114. -- everything below this line deals with
  115. -- input/output, and is therefore gross
  116. -- i will clean this up one day, but it
  117. -- hurts my soul.
  118. ------------------------
  119. -- command line flags --
  120. ------------------------
  121. -- structure containing the programs options
  122. data Options = Options
  123. { optWidth :: Int
  124. , optGenerations :: Int
  125. } deriving Show
  126. -- the default options for the program
  127. -- the width and generations are injected
  128. -- and intended to be gotten at runtime
  129. -- to match the window dimensions
  130. defaultOptions :: Int -> Int -> Options
  131. defaultOptions w h = Options
  132. { optWidth = w
  133. , optGenerations = h
  134. }
  135. -- the avaliable options
  136. options :: [OptDescr (Options -> Options)]
  137. options =
  138. [ Option ['w'] ["width"]
  139. (ReqArg (\w opts -> opts { optWidth = (read w) }) "WIDTH")
  140. "term width"
  141. , Option ['g'] ["generations"]
  142. (ReqArg (\t opts -> opts { optGenerations = (read t) }) "GENERATIONS")
  143. "time steps to simulate"
  144. ]
  145. -- parse the options into the structure
  146. -- erroring if encountering a flag not known to us
  147. parseArgs :: IO Options
  148. parseArgs = do
  149. argv <- getArgs
  150. progName <- getProgName
  151. tw <- readProcess "tput" [ "cols" ] ""
  152. th <- readProcess "tput" [ "lines" ] ""
  153. case getOpt RequireOrder options argv of
  154. (opts, [], []) -> return (foldl (flip id) (defaultOptions (read tw) (read th)) opts)
  155. (_, _, errs) -> ioError (userError (concat errs ++ helpMessage))
  156. where
  157. header = "Usage: " ++ progName ++ " [OPTION...]"
  158. helpMessage = usageInfo header options
  159. ---------------
  160. -- main loop --
  161. ---------------
  162. -- simply print the current space, then recurse to the next
  163. runAutomata :: Space CellState -> Int -> Int -> IO ()
  164. runAutomata s 0 w = putStrLn $ concat $ map show $ boundw w s
  165. runAutomata s n w = do
  166. putStrLn $ concat $ map show $ boundw w s
  167. runAutomata (step rule3 s) (n - 1) w
  168. main :: IO ()
  169. main = do
  170. options <- parseArgs
  171. rng <- getStdGen
  172. let cs = map (\x -> if x then Alive else Dead) $ ilobs rng
  173. let w = (optWidth options)
  174. let h = (optGenerations options)
  175. let wh = (w + 1) `div` 2
  176. let m = head cs
  177. let l = take wh $ drop 1 cs
  178. let r = take wh $ drop wh $ drop 1 cs
  179. let s = Space (l ++ (repeat Dead)) m (r ++ (repeat Dead))
  180. -- non-random starting position for rule3 (the serpinski triangle)
  181. --let s = Space (repeat Dead) Alive (repeat Dead)
  182. runAutomata s h w