a one dimensional cellular automata, using comonads
You can not select more than 25 topics Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.

169 lines
4.4KB

  1. {-# LANGUAGE OverloadedStrings #-}
  2. module Main where
  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. import Comonad
  10. import Spaces
  11. import Automata
  12. import Brick
  13. import Brick.BChan (newBChan, writeBChan)
  14. import qualified Brick.Widgets.Border as B
  15. import qualified Brick.Widgets.Border.Style as BS
  16. import qualified Brick.Widgets.Center as C
  17. import qualified Graphics.Vty as V
  18. import Control.Applicative
  19. import Control.Monad.IO.Class
  20. import Control.Concurrent
  21. import Control.DeepSeq
  22. -----------------
  23. -- brick stuff --
  24. -----------------
  25. data Tick = Tick
  26. type Name = ()
  27. -- App definition
  28. app :: Int -> Int -> App (Space2 CellState) Tick Name
  29. app h w = App { appDraw = drawUI h w
  30. , appChooseCursor = neverShowCursor
  31. , appHandleEvent = handleEvent
  32. , appStartEvent = return
  33. , appAttrMap = const theMap
  34. }
  35. -- Handling events
  36. theMap :: AttrMap
  37. theMap = attrMap V.defAttr
  38. [ (rockAttr, V.red `on` V.blue)
  39. , (scissorsAttr, V.green `on` V.red)
  40. , (paperAttr, V.blue `on` V.green)
  41. ]
  42. ---------------
  43. -- rng stuff --
  44. ---------------
  45. -- takes a generator and returns
  46. -- an infinite list of bools
  47. ilobs :: StdGen -> [Bool]
  48. ilobs rng = b : (ilobs r)
  49. where
  50. (b,r) = random rng
  51. -----------------
  52. -- gross io bs --
  53. -----------------
  54. -- everything below this line deals with
  55. -- input/output, and is therefore gross
  56. -- i will clean this up one day, but it
  57. -- hurts my soul.
  58. ------------------------
  59. -- command line flags --
  60. ------------------------
  61. -- structure containing the programs options
  62. data Options = Options
  63. { optWidth :: Int
  64. , optGenerations :: Int
  65. , optHeight :: Int
  66. } deriving Show
  67. -- the default options for the program
  68. -- the width and generations are injected
  69. -- and intended to be gotten at runtime
  70. -- to match the window dimensions
  71. defaultOptions :: Int -> Int -> Options
  72. defaultOptions w h = Options
  73. { optWidth = w
  74. , optGenerations = 40
  75. , optHeight = h
  76. }
  77. -- the avaliable options
  78. options :: [OptDescr (Options -> Options)]
  79. options =
  80. [ Option ['w'] ["width"]
  81. (ReqArg (\w opts -> opts { optWidth = (read w) }) "WIDTH")
  82. "term width"
  83. , Option ['g'] ["generations"]
  84. (ReqArg (\t opts -> opts { optGenerations = (read t) }) "GENERATIONS")
  85. "time steps to simulate"
  86. , Option ['h'] ["height"]
  87. (ReqArg (\t opts -> opts { optHeight = (read t) }) "HEIGHT")
  88. "term height"
  89. ]
  90. -- parse the options into the structure
  91. -- erroring if encountering a flag not known to us
  92. parseArgs :: IO Options
  93. parseArgs = do
  94. argv <- getArgs
  95. progName <- getProgName
  96. tw <- readProcess "tput" [ "cols" ] ""
  97. th <- readProcess "tput" [ "lines" ] ""
  98. case getOpt RequireOrder options argv of
  99. (opts, [], []) -> return (foldl (flip id) (defaultOptions (read tw) (read th)) opts)
  100. (_, _, errs) -> ioError (userError (concat errs ++ helpMessage))
  101. where
  102. header = "Usage: " ++ progName ++ " [OPTION...]"
  103. helpMessage = usageInfo header options
  104. initGame :: IO (Space2 CellState)
  105. initGame = do
  106. rng <- getStdGen
  107. return $ createRandSpace2 rng
  108. ---------------
  109. -- main loop --
  110. ---------------
  111. main :: IO ()
  112. main = do
  113. options <- parseArgs
  114. let w = (optWidth options)
  115. let h = (optHeight options)
  116. chan <- newBChan 1
  117. forkIO $ forever $ do
  118. writeBChan chan Tick
  119. threadDelay 100000
  120. g <- initGame
  121. let buildVty = V.mkVty V.defaultConfig
  122. initialVty <- buildVty
  123. void $ customMain initialVty buildVty (Just chan) (app h w) (clamp2cw w h g)
  124. handleEvent :: (Space2 CellState) -> BrickEvent Name Tick -> EventM Name (Next (Space2 CellState))
  125. handleEvent g (AppEvent Tick) = continue $ step rps g
  126. handleEvent g (VtyEvent (V.EvKey (V.KChar 'q') [])) = halt g
  127. handleEvent g _ = continue g
  128. drawUI :: Int -> Int -> Space2 CellState -> [Widget Name]
  129. drawUI h w g = [ C.center $ drawGrid h w g ]
  130. drawGrid :: Int -> Int -> Space2 CellState -> Widget Name
  131. drawGrid h w g = vBox rows
  132. where
  133. bw = bound2cw w h g
  134. rows = [ hBox $ cellsInRow r | r <- bw ]
  135. cellsInRow y = map drawCell y
  136. drawCell :: CellState -> Widget Name
  137. drawCell Paper = withAttr paperAttr $ str " "
  138. drawCell Scissors = withAttr scissorsAttr $ str " "
  139. drawCell Rock = withAttr rockAttr $ str " "
  140. rockAttr, scissorsAttr, paperAttr :: AttrName
  141. rockAttr = "rockAttr"
  142. paperAttr = "paperAttr"
  143. scissorsAttr = "scissorsAttr"