
Thank you for the positive responses. The best kind of feedback is the kind that makes me have to think, and I've done alot of thinking. _Regarding monads and interfaces_ Paul Johnson wrote:
1: Your GameState type can itself be made into a monad. Take a look at the "All About Monads" tutorial, especially the State monad. Think about the invariants in GameState; can you produce a new monad that guarantees these invariants through a limited set of actions. How do these actions correspond to user perceptions?
2: You can layer monads by using monad transformers. Extend the solution to part 1 by using StateT IO instead of just State.
OK, Here's the new monad and the corresponding transformer.
type Hangman = State GameState type HangmanT = StateT GameState
And here's an interface for the Hangman monad.
newHangmanGame :: (MonadState GameState m) => String -> m () newHangmanGame = put . newGameState
renderHangmanGame :: (MonadIO m, MonadState GameState m) => m () renderHangmanGame = get >>= return . renderGameState >>= liftIO . putStrLn
guessLetter :: (MonadState GameState m) => Char -> m () guessLetter = modify . handleGuess
getWonLost :: (MonadState GameState m) => m (Maybe Bool) getWonLost = get >>= return . gsWonLost
getAnswer :: (MonadState GameState m) => m String getAnswer = get >>= return . gsAnswer
This all seems a little pointless :) for a simple game, nevertheless I proceeded to modify startNewGame and gameLoop to use the Hangman interface. The modifications were trivial. The type signatures for startNewGame and gameLoop become:
startNewGame :: HangmanT IO () gameLoop :: HangmanT IO ()
_Regarding random numbers_ Yitzchak Gale wrote:
You can add one more field to GameState that holds a random generator.
I tried it; it was very easy. Paul Johnson wrote:
Can you make your game a function of a list of random numbers?
Yitzchak Gale wrote:
I would advise against that technique. In more complex games, you may need to do many different kinds of random calculations in complex orders. Keeping a random generator inside a state monad is perfect for that. And since Ronald already set up the plumbing for the state monad, he is already home.
I simply modified startNewGame and gameLoop to accept a list of integers. In startNewGame, I use the first integer in the list to choose a word, and then I pass the rest of the list to gameLoop. In gameLoop, I simply pass the list along to every recursive call to startNewGame or gameLoop.
main :: IO () main = do ... g <- getStdGen let rs = randomRs (0,length wordList - 1) g runStateT (startNewGame rs) undefined return ()
startNewGame :: [Int] -> HangmanT IO () startNewGame (r:rs) = do let word = wordList !! r newHangmanGame word renderHangmanGame gameLoop rs
gameLoop :: [Int] -> HangmanT IO () gameLoop rs = ...
I suppose I could easily push the list of random numbers into GameState to avoid manually threading it around my program. If I did that, then the only difference between the two techniques would be (1) adding a field to hold a random number generator, vs (2) adding a field to hold an infinite list of random numbers. If I store a list of numbers, then I have to choose a probability distribution at initialization time. If I store the generator, then I am free to change the probability distribution on the fly. For a Hangman game, the only time I need to change the probability distribution is if I load a new word list. If I wanted to be able to load a new word list, then perhaps I need to carry the word list inside the GameState as well? _Random numbers continued_ So let me create a HangmanRand monad to encapsulate the process of selecting random words.
type HangmanRand = State RandState type HangmanRandT = StateT RandState
data RandState = RandState { rsRandGen :: StdGen, -- the random number generator rsWordList :: [String] -- the word list }
initHangmanRand :: (MonadState RandState m) => [String] -> StdGen -> m () initHangmanRand words g = put $ RandState{ rsRandGen = g, rsWordList = words}
getRandomWord :: (MonadState RandState m) => m String getRandomWord = do rs <- get let words = rsWordList rs let (n, g) = randomR (0,length words - 1) $ rsRandGen rs put $ rs{rsRandGen = g} return $ words !! n
I can easily modify the game to use HangmanRand. My gameLoop doesn't have to change at all (apart from the type signature).
main :: IO () main = do hSetBuffering stdout NoBuffering putStr "Welcome to Hangman!\n\n" putStr instructions let seed = 5 let g = mkStdGen seed runStateT (runStateT (initGame wordList g) undefined) undefined return ()
initGame :: [String] -> StdGen -> HangmanT (HangmanRandT IO) () initGame words g = do lift $ initHangmanRand words g startNewGame
startNewGame :: HangmanT (HangmanRandT IO) () startNewGame = do word <- lift getRandomWord newHangmanGame word renderHangmanGame gameLoop
gameLoop :: HangmanT (HangmanRandT IO) () gameLoop = ...
If I wanted to make my program a function of a list of random numbers, then I would need to change main, initGame, and the implementation of HangmanRand. Again, the gameLoop wouldn't have to change at all. _Regarding user input_ Paul Johnson wrote:
4: User input can also be considered as a list. Haskell has "lazy input", meaning that you can treat user input as a list that actually only gets read as it is required. Can you make your game a function of the list of user inputs? How does this interact with the need to present output to the user? What about the random numbers?
Yitzchak Gale wrote:
That type of "lazy IO" is considered by many to be one of Haskell's few warts. It is a hole in the type system that lets a small amount of side-effects leak through, and even that small amount leads to bugs.
It turns out there is only one place in my entire code where I request input from the user. This place is the call to getLine inside the function getUserInput:
getUserInput :: IO UserInput getUserInput = do putStr "Hangman> " response <- getLine ...
I tried changing this to:
getUserInput :: [String] -> IO (UserInput, [String]) getUserInput (response:rs)= do putStr "Hangman> " ...
In order to make this work, I need to thread the list of inputs around my program. Thus:
startNewGame :: [String] -> HangmanT IO [String] gameLoop :: [String] -> HangmanT IO [String]
To get the whole thing started:
main :: IO () main = do ... rs <- hGetContents stdin >>= return . lines ...
This approach fails because the "Hangman>" prompt is not printed until immediately /after/ the user enters a response. I tried using hFlush but that didn't work. In order to keep input and output synchronized, I had to do this:
getUserInput :: [String] -> IO (UserInput, [String]) getUserInput rs'= do putStr "Hangman> " let (response:rs) = rs' ...
Apparently, if I am accepting my input as a list, then I have to be careful to avoid forcing the elements of that list until I actually need them. Meanwhile, just like with the random numbers, I can avoid manually threading the list of inputs through the program. All I would have to do is push the list of inputs into the GameState and add a utility function that pulls off one input at a time. Or better yet, I could create a HangmanIO monad to store the list of inputs.
type HangmanIO = State HangmanIOState type HangmanIOT = StateT HangmanIOState
initHangmanIO :: (MonadState HangmanIOState m) => [String] -> m () initHangmanIO userInputs = put $ HangmanIOState{ hioInputList = userInputs}
getResponse :: (MonadState HangmanIOState m) => m String getResponse = do s <- get let (x:xs) = hioInputList s put $ s{hioInputList = xs} return x
data HangmanIOState = HangmanIOState { hioInputList :: [String] -- the list of user inputs }
I have to modify the program like this:
main :: IO () main = do hSetBuffering stdout NoBuffering putStr "Welcome to Hangman!\n\n" putStr instructions let seed = 5 let g = mkStdGen seed responses <- hGetContents stdin >>= return . lines runStateT (runStateT (runStateT (initGame wordList g responses) undefined) undefined) undefined return ()
initGame :: [String] -> StdGen -> [String] -> HangmanT (HangmanRandT (HangmanIOT IO)) () initGame words g responses = do lift $ initHangmanRand words g lift $ lift $ initHangmanIO responses startNewGame
startNewGame :: HangmanT (HangmanRandT (HangmanIOT IO)) () startNewGame = ...
gameLoop :: HangmanT (HangmanRandT (HangmanIOT IO)) () gameLoop = do ui <- lift $ lift getUserInput ...
getUserInput :: (MonadIO m, MonadState HangmanIOState m) => m UserInput getUserInput = do liftIO $ putStr "Hangman> " response <- getResponse ... -- and I have to use liftIO for my output commands
I successfully moved my game input from the IO monad to my HangmanIO monad. I actually attempted to go all the way and move /output/ from the IO monad to HangmanIO as well. The resulting program uses "interact" at the top level in main. Unfortunately, the program doesn't work. None of the output actually appears until I quit the game, and then all the output is produced at one time. And this time I have no idea how to fix it. Moving random number generation and IO around has been a nice learning exercise for me. In particular, moving the random number generator into its own monad (or into GameState) seems like a very useful thing to do. On the other hand, moving the game's IO into its own monad (HangmanIO) seems like reinventing the wheel. My understanding is that back in ancient times "main" had the signature "String -> String". Programs were very hard to write because they needed to have just the right mix of laziness and strictness to ensure proper interleaving of inputs and outputs. Then one day someone realized that there's this esoteric concept in category theory that could solve the IO problem, and the rest is history. I'm simply better off using the IO monad. _Regarding scalability_ Paul Johnson wrote:
The design reads very much like a straight translation from the imperative style, which is why so much of it is in the IO monad. There is nothing wrong with this for a simple game like Hangman, but for larger games it doesn't scale.
Yitzchak Gale wrote:
It's a state monad, and most of his code is in that style. It doesn't read to me like imperative style at all. And it scales beautifully.
To see if my code can scale, I would have to think about extensions to my Hangman game, or think about more complicated games. I think this one will have to wait until much later. -- Ron