Add cli opts for score, level, and restricting unicode

This commit is contained in:
Sam Tay 2017-07-02 17:47:21 -04:00
parent 2c150c7b27
commit 8e2240c87c
3 changed files with 72 additions and 9 deletions

View file

@ -1,15 +1,77 @@
module Main where module Main where
import Tetris (Game) import Control.Monad (when)
import Data.Maybe (fromMaybe)
import Data.Monoid ((<>))
import System.Exit (exitSuccess)
import Tetris (Game(..))
import UI.PickLevel (pickLevel) import UI.PickLevel (pickLevel)
import UI.Game (playGame) import UI.Game (playGame)
-- | TODO possibly allow a small number of CLI args, import Options.Applicative
-- like tetris --high-score
main :: IO ()
main = pickLevel >>= playGame >>= handleEndGame
-- | TODO possibly save high score (with 3 initials? kick it real old school?) to ~/.tetris data Opts = Opts
handleEndGame :: Game -> IO () { hardDrop :: Maybe HardDropOpt
, level :: Maybe Int
, score :: Bool
} deriving (Show) -- TODO remove
data HardDropOpt = AsciiOnly | CustomChars String deriving (Show) -- TODO remove
opts :: Parser Opts
opts = Opts
<$> optional hardDropOpt
<*> optional (option auto
( long "level"
<> short 'l'
<> metavar "LEVEL"
<> help "Specify level (unspecified results in prompt)" ))
<*> switch
( long "high-score"
<> help "Print high score and exit" )
hardDropOpt :: Parser HardDropOpt
hardDropOpt = asciiOpt <|> custOpt
where
asciiOpt = flag' AsciiOnly
( long "ascii-only"
<> short 'a'
<> help "Use '[]' as hard drop preview cell instead of '◤◢'" )
custOpt = CustomChars <$> option twoChar
( long "preview-chars"
<> short 'p'
<> metavar "CHARS"
<> help "Custom two character preview cell" )
fullopts :: ParserInfo Opts
fullopts = info (helper <*> opts)
( fullDesc
<> header "tetris - the iconic game right in your terminal" )
twoChar :: ReadM String
twoChar = do
cs <- str
if length cs /= 2
then readerError "Preview must be two characters long"
else return cs
hdOptStr :: HardDropOpt -> String
hdOptStr AsciiOnly = "[]"
hdOptStr (CustomChars s) = s
main :: IO ()
main = do
(Opts hd ml hs) <- execParser fullopts -- get CLI opts/args
let mp = hdOptStr <$> hd -- determine hard drop preview cell
when hs (getHighScore >>= print >> exitSuccess) -- show high score and exit
l <- fromMaybe pickLevel (return <$> ml) -- pick level prompt if necessary
g <- playGame l mp -- play game
handleEndGame (_score g) -- save & print score
handleEndGame :: Int -> IO ()
handleEndGame = const $ return () handleEndGame = const $ return ()
getHighScore :: IO Int
getHighScore = error "Not yet implemented"

View file

@ -41,8 +41,8 @@ app = App { appDraw = drawUI
, appAttrMap = const theMap , appAttrMap = const theMap
} }
playGame :: Int -> IO Game playGame :: Int -> Maybe String -> IO Game
playGame lvl = do playGame lvl _ = do
let delay = levelToDelay lvl let delay = levelToDelay lvl
chan <- newBChan 10 chan <- newBChan 10
forkIO $ forever $ do forkIO $ forever $ do

View file

@ -33,6 +33,7 @@ executable tetris
main-is: Main.hs main-is: Main.hs
ghc-options: -threaded -rtsopts -with-rtsopts=-N ghc-options: -threaded -rtsopts -with-rtsopts=-N
build-depends: base >= 4.7 && < 5 build-depends: base >= 4.7 && < 5
, optparse-applicative
, tetris , tetris
default-language: Haskell2010 default-language: Haskell2010