{-# LANGUAGE NamedFieldPuns #-}
module Game.H2048.UI.Simple
( drawBoard
, playGame
, main
, Board
)
where
import Data.Maybe
import Game.H2048.Core
import Data.List
import Text.Printf
import Control.Monad.IO.Class
import Control.Monad.Random
import Control.Applicative
import Control.Arrow
import System.IO
helpString :: String
helpString = "'i'/'k'/'j'/'l' to move, 'q' to quit."
drawBoard :: Board -> IO ()
drawBoard bd =
putStrLn horizSeparator >>
mapM_ drawRow (fromBoard bd)
where
cellWidth = length " 2048 "
horizSeparator' = intercalate "+" (replicate 4 (replicate cellWidth '-'))
horizSeparator = "+" ++ horizSeparator' ++ "+"
prettyCell c =
if c == 0
then replicate cellWidth ' '
else printf " %4d " c
drawRow row = do
putChar '|'
mapM_ (prettyCell >>> putStr >>> (>> putChar '|')) row
putChar '\n'
putStrLn horizSeparator
playGame :: (MonadIO m, MonadRandom m, Alternative m) => (Board, Int) -> m ()
playGame args@(b,score) |
GS {hasWon, isAlive} <- gameState b =
if isAlive
then liftIO (handleUserMove hasWon) >>= handleGame
else liftIO (endGame args hasWon)
where
endGame (b',score') win = do
drawBoard b'
putStrLn $ if win then "You won" else "Game over"
_ <- printf "Final score: %d\n" score'
hFlush stdout
handleUserMove w = fix $ \self -> do
let scoreFormat =
if w
then "You win, current score: %d\n"
else "Current score: %d\n"
drawBoard b
_ <- printf scoreFormat score
hFlush stdout
c <- getChar
putStrLn ""
hFlush stdout
case c of
'q' -> pure Nothing
'i' -> putStrLn "Up" >> pure (Just DUp)
'k' -> putStrLn "Down" >> pure (Just DDown)
'j' -> putStrLn "Left" >> pure (Just DLeft)
'l' -> putStrLn "Right" >> pure (Just DRight)
_ -> do
putStrLn helpString
self
handleGame =
maybe
(pure ())
((`updateBoard` b) >>>
maybe
(liftIO (putStrLn "Invalid move") >> playGame args)
(\(newBoard, scoreObtained) -> do
newB <- fromJust <$> insertNewCell newBoard
playGame (newB, score + scoreObtained)))
main :: IO ()
main = do
bfMod <- hGetBuffering stdin
hSetBuffering stdin NoBuffering
g <- newStdGen
putStrLn helpString
_ <- evalRandT (initGameBoard >>= playGame) g
hSetBuffering stdin bfMod