import System.IO
import qualified Data.Vector as V
-import qualified Brick as B
import Parse
import Sim
import Render
--- ui :: B.Widget ()
--- ui = B.str "hello" <+> B.str "World"
-
hGetLines :: Handle -> IO [String]
hGetLines h = do
line <- hGetLine h
return (line:lines)
main = do
+ -- handle file stuff
argv <- getArgs
(opts, fname) <- ekitaiOpts argv
handle <- openFile fname ReadMode
contents <- hGetLines handle
hClose handle
- -- putStrLn $ show $ stringToSim contents
- initialState <- buildInitialState $ stringToSim contents
- endState <- B.defaultMain ekitaiApp initialState
- -- print endState
+ -- start brick
+ ekitaiMain $ stringToSim contents
return 0
--- main :: IO ()
--- main = do
- -- return 0
-
-module Render ( buildInitialState, ekitaiApp ) where
+module Render ( ekitaiMain ) where
import Brick.AttrMap
import Brick.Main
import Brick.Types
import Brick.Widgets.Core
-import Graphics.Vty.Input.Events
+import Brick.BChan (newBChan, writeBChan)
+import Graphics.Vty
+
+import Control.Monad (forever, void)
+import Control.Monad.IO.Class (liftIO)
+import Control.Concurrent (threadDelay, forkIO)
import qualified Data.Vector as V
import Sim
{ ekitaiStateSim :: Simulation
} deriving (Show)
-ekitaiApp :: App EkitaiState e ResourceName
+-- custom event
+data Tick = Tick
+
+ekitaiApp :: App EkitaiState Tick ResourceName
ekitaiApp = App
{ appDraw = drawEkitai
, appChooseCursor = showFirstCursor
, appAttrMap = const $ attrMap mempty []
}
+ekitaiMain sim = do
+ chan <- newBChan 10
+ -- tick game
+ forkIO $ forever $ do
+ writeBChan chan Tick
+ threadDelay 50000
+ let buildVty = Graphics.Vty.mkVty Graphics.Vty.defaultConfig
+ initialVty <- buildVty
+ initialState <- buildInitialState sim
+ endState <- customMain initialVty buildVty (Just chan) ekitaiApp initialState
+ return 0
+
buildInitialState :: Simulation -> IO EkitaiState
buildInitialState sim =
pure EkitaiState
}
drawEkitai :: EkitaiState -> [Widget ResourceName]
--- drawEkitai state = [ vBox $ drawSim $ ekitaiStateSim state ]
drawEkitai state = [ vBox [str $ simToString $ ekitaiStateSim state] ]
-handleEkitaiEvent :: EkitaiState -> BrickEvent n e -> EventM n (Next EkitaiState)
-handleEkitaiEvent s e =
- case e of
- VtyEvent vtye ->
- case vtye of
- EvKey (KChar 'q') [] -> halt s
- EvKey (KChar 's') [] -> continue s { ekitaiStateSim = physStep $ ekitaiStateSim s }
- _ -> continue s
- _ -> continue s
+handleEkitaiEvent :: EkitaiState -> BrickEvent n Tick -> EventM n (Next EkitaiState)
+handleEkitaiEvent s (VtyEvent (EvKey (KChar 'q') [])) = halt s
+handleEkitaiEvent s (AppEvent Tick) = continue s { ekitaiStateSim = physStep $ ekitaiStateSim s }
+handleEkitaiEvent s _ = continue s