-- ================================== -- Module name: PlayFoo -- Project: Foo -- Copyright (C) 2007 Bartosz Wójcik -- Created on: 01.10.2007 -- Last update: 28.11.2007 -- Version: % {- This program is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program. If not, see . -} -- ================================== module Main where -- Simply user interface aksing for initial game parameters. import Court import Foo main = do player1 <- selectPlayer1 alg1 <- selectAlgorithm player1 player2 <- selectPlayer2 alg2 <- selectAlgorithm player2 nbrOfGames <- selectNumerOfGames court 8 8 (player1,toEnum alg1) (player2,toEnum alg2) nbrOfGames algDisp :: [String] algDisp = ["Select playing algorithm"] ++ map (\(a,n) -> (show a ++ " - " ++ show n)) (zip [GoAhead ..] [0..]) algNum :: [String] algNum = map (\(a,n) -> (show n)) (zip [GoAhead ..] [0..]) enterValue :: [String] -> [String] -> IO String enterValue possibleValues messages = do mapM putStrLn messages word <- getLine if any (word ==) possibleValues then return word else enterValue possibleValues messages selectPlayer1 :: IO Bool selectPlayer1 = enterValue ["c","h"] ["Enter Player 1","c - computer","h - human"] >>= (\x -> return (x == "c")) selectPlayer2 :: IO Bool selectPlayer2 = enterValue ["c","h"] ["Enter Player 2","c - computer","h - human"] >>= (\x -> return (x == "c")) selectAlgorithm :: Bool -> IO Int selectAlgorithm True = enterValue algNum algDisp >>= (\x -> return (read x)) selectAlgorithm False = return 0 selectNumerOfGames :: IO Int selectNumerOfGames = enterValue (map show [1..12]) ["Enter number of games {1,..,12}"] >>= (\x -> return (read x))