module Main where -- alone in a room: a scary game -- vai a dormire -- scary room -- escape -- blink exit, blink enemies -- pit -- randomly generated import Terminal.Game main :: IO () main = gameLoop "Alone in a room" (GameState (10, 10) Stop False) logicFun drawFun (\gs -> gsQuit gs) 5 -- STATE -- data GameState = GameState { gsCoord :: (Integer, Integer), gsMove :: Move, gsQuit :: Bool } data Move = N | S | E | W | Stop deriving (Show, Eq) logicFun :: GameState -> Maybe Char -> IO GameState logicFun gs (Just 'q') = return $ gs { gsQuit = True } logicFun (GameState cs m b) Nothing = return $ GameState (pos m cs) m b -- xxx duplicated code logicFun (GameState cs m b) (Just c) = let m' = move m c in return $ GameState (pos m' cs) m' b -- SCI movement move :: Move -> Char -> Move move N 'w' = Stop move S 's' = Stop move W 'a' = Stop move E 'd' = Stop move _ 'w' = N move _ 's' = S move _ 'a' = W move _ 'd' = E move m _ = m -- todo add boundaries pos :: Move -> (Integer, Integer) -> (Integer, Integer) pos Stop cs = cs pos N (r, c) = (r-1, c ) pos S (r, c) = (r+1, c ) pos E (r, c) = (r , c+1) pos W (r, c) = (r , c-1) -- DRAW -- drawFun :: GameState -> Plane drawFun (GameState (r, c) _ _) = blankPlane 80 25 & (1, 1) % box '_' 80 25 & (2, 2) % box ' ' 78 23 & (15, 20) % textBox "tap WASD to move, tap again to stop" 10 4 & (r, c) % cell '@'