Skip to content
Snippets Groups Projects
Commit 25b780ab authored by Unai Zalakain's avatar Unai Zalakain
Browse files

Switch to optparse-applicative for command line parsing

It supports parsing arguments and inserting custom strings into the help
message.
parent 955c5013
No related branches found
No related tags found
No related merge requests found
......@@ -64,7 +64,7 @@ executable snorkels
ansi-terminal >=0.6 && <0.7,
bimap >=0.3.2 && <0.3.3,
parsec >=3.1.11 && <3.1.12,
options >=1.2.1.1 && <1.2.1.2
optparse-applicative >=0.13.0 && <0.13.1
-- Directories containing source files.
hs-source-dirs: src
......@@ -96,7 +96,7 @@ library
ansi-terminal >=0.6 && <0.7,
bimap >=0.3.2 && <0.3.3,
parsec >=3.1.11 && <3.1.12,
options >=1.2.1.1 && <1.2.1.2
optparse-applicative >=0.13.0 && <0.13.1
-- Directories containing source files.
hs-source-dirs: src
......
......@@ -3,36 +3,58 @@ module Main where
import qualified Data.Bimap as Bimap
import Data.Function
import qualified Data.Map.Strict as Map
import Data.Monoid
import System.Random (getStdGen)
import Options
import Options.Applicative
import Snorkels.Types
import Snorkels.Play
import qualified Snorkels.CLI as CLI
import Snorkels.CLI (cli)
import Snorkels.RandomAgent (randomAgent)
import qualified Snorkels.Board as B
data MainOptions = MainOptions { optNumStones :: Int
, optWidth :: Int
, optHeight :: Int
, optNumPlayers :: Int
} deriving (Eq)
data MainParser = MainParser { optNumStones :: Int
, optWidth :: Int
, optHeight :: Int
, optNumPlayers :: Int
} deriving (Eq)
instance Options MainOptions where
defineOptions = pure MainOptions
<*> simpleOption "num-stones" 3
"Number of stones randomly thrown on the board"
<*> simpleOption "width" 7
"Width of the board"
<*> simpleOption "height" 7
"Height of the board"
<*> simpleOption "players" 2
"Number of players"
mainParser :: Parser MainParser
mainParser = MainParser
<$> option auto
( long "stones"
<> short 's'
<> value 3
<> metavar "#STONES"
<> help "Number of stones randomly thrown on the board"
)
<*> option auto
( long "width"
<> short 'w'
<> value 7
<> metavar "WIDTH"
<> help "Width of the board"
)
<*> option auto
( long "height"
<> short 'h'
<> value 7
<> metavar "HEIGHT"
<> help "Height of the board"
)
<*> option auto
( long "players"
<> short 'p'
<> value 2
<> metavar "#PLAYERS"
<> help "Number of players"
)
create :: MainOptions -> IO (Either String Game)
create :: MainParser -> IO (Either String Game)
create options
| max (options&optWidth) (options&optHeight) > 26 = return $ Left "Cannot have more than 26 on either axis."
| otherwise = do g <- getStdGen
......@@ -40,16 +62,25 @@ create options
where players = take (optNumPlayers options) [Green ..]
game = Game { pieces = Map.empty
, boardSize = (optWidth options, optHeight options)
, playerTypes = Map.fromList [(p, CLI.cli) | p <- players]
, playerTypes = Map.fromList [(Green, cli), (Purple, randomAgent)]
, currentPlayer = Green
, switches = Bimap.empty
}
run :: MainParser -> IO ()
run options = do game <- create options
case game of
Left message -> print message
Right g -> do play g
return ()
main :: IO ()
main = runCommand $ \opts args -> do
game <- create opts
case game of
Left message -> print message
Right g -> do play g
return ()
main = execParser opts >>= run
where
opts = info (helper <*> mainParser)
( fullDesc
<> progDesc "TODO"
<> header "Snorkels -- strategic board game")
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment