[Haskell-beginners] State monad to help pass around game settings
David McBride
toad3k at gmail.com
Fri Apr 7 12:33:10 UTC 2017
The basic outline for using StateT for settings is the following.
Hopefully this will give you an idea of how to get started.
import Control.Monad.State
data Color = White | Red deriving (Enum, Show)
data Shape = Square deriving (Enum, Show)
data Stuff = Stuff deriving Show
data Settings = Settings {
sColor :: Color,
sShape :: Shape
} deriving Show
data MyApp = MyApp {
settings :: Settings,
otherStuff :: Stuff
} deriving Show
main = do
(_, settings) <- runStateT proc (MyApp (Settings White Square) Stuff)
print settings
-- A reusable prompt function.
prompt :: String -> [a] -> (Char -> a) -> IO a
prompt question opts c2r = do
putStrLn question
mapM undefined opts
c <- getChar
let r = c2r c -- turn a Char into a Shape or a Color.
return r
proc :: StateT MyApp IO ()
proc = do
getColor
getShape
getColor :: StateT MyApp IO ()
getColor = do
color <- liftIO $ prompt "What color would you like?" [Red, White] undefined
MyApp settings otherstuff <- get
put $ (MyApp (settings { sColor = color })) otherstuff
getShape :: StateT MyApp IO ()
getShape = undefined
On Thu, Apr 6, 2017 at 9:26 PM, Dave Martin <davemartinnyc at aol.com> wrote:
> I'm trying to write a game with a "settings menu" where the user can adjust
> gameplay options. Right now I pass all the settings around as parameters.
> I'm trying to figure out how to use the State monad to simplify this task,
> but I can't figure out how to start. Or maybe my whole design approach is
> wrongheaded, and not in keeping with best practices. Haskell is my first
> language. This is the kind of thing I have now:
>
> mainM color shape =
> putStrLn "\n\nMain Menu" >>
> (putStrLn . unlines) [
> "(1) Set",
> "(2) Display",
> "(3) Quit"] >>
> putStr "? " >>
> getChar >>= \c ->
> case c of
> '1' -> set color shape
> '2' -> display color shape
> '3' -> return ()
> _ -> mainM color shape
>
> set color shape =
> putStrLn "\n\nSettings" >>
> (putStrLn . unlines) [
> "(1) Color",
> "(2) Shape",
> "(3) Main Menu"] >>
> putStr "? " >>
> getChar >>= \c ->
> case c of
> '1' -> setColor color shape
> '2' -> setShape color shape
> '3' -> mainM color shape
> _ -> set color shape
>
> setColor color shape =
> putStr ("\n\nColor is " ++ color ++ ". New color? ") >>
> getLine >>= \cs ->
> set cs shape
>
> setShape color shape =
> putStr ("\n\nShape is " ++ shape ++ ". New shape? ") >>
> getLine >>= \cs ->
> set color cs
>
> display color shape =
> putStrLn ("\n\nColor is " ++ color ++ ". Shape is " ++ shape ++ ".") >>
> mainM color shape
>
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>
More information about the Beginners
mailing list