module Main where import Terminal.Game main :: IO () main = do runGame (GameState (10, 10) Stop False) logicFun drawFun (\gs -> gsQuit gs) 10 return () -- xxx no () in iok0 ----------- -- TYPES -- ----------- data GameState = GameState { gsCoord :: Coords, gsMove :: Move, gsQuit :: Bool } data Move = N | S | E | W | Stop deriving (Show, Eq) boundaries :: (Coords, Coords) boundaries = ((1, 1), (25, 80)) ----------- -- LOGIC -- ----------- logicFun :: GameState -> Event -> GameState logicFun gs (KeyPress 'q') = gs { gsQuit = True } logicFun gs Tick = gs { gsCoord = pos (gsMove gs) (gsCoord gs) } logicFun gs (KeyPress c) = gs { gsMove = move (gsMove gs) c } -- 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 pos :: Move -> (Integer, Integer) -> (Integer, Integer) pos m oldcs | oob newcs = oldcs | otherwise = newcs where newcs = new m oldcs new Stop cs = cs new N (r, c) = (r-1, c ) new S (r, c) = (r+1, c ) new E (r, c) = (r , c+1) new W (r, c) = (r , c-1) ((lr, lc), (hr, hc)) = boundaries oob (r, c) = r <= lr || c <= lc || r >= hr || c >= hc ---------- -- DRAW -- ---------- drawFun :: GameState -> Plane drawFun (GameState (r, c) _ _) = blankPlane mw mh & (1, 1) % box '_' mw mh & (2, 2) % box ' ' (mw-2) (mh-2) & (15, 20) % textBox "Tap WASD to move, tap again to stop." 10 4 & (20, 60) % textBox "Press Q to quit." 8 10 & (r, c) % cell '@' # invert where mh :: Height mw :: Width (mh, mw) = snd boundaries