
Hi, I'm interested in learning how to program games. Since I have to start somewhere, I decided to write a simple Hangman game. I'm wondering if anyone can look at my code and give me some feedback. Thank you. -- Hangman game module Main where import Data.Char import Data.List import System.IO import System.Random import Control.Monad.State data GameState = GameState { gsAnswer :: String, -- the answer gsKnown :: [Maybe Char], -- partial answer known to the user gsGuesses :: [Char], -- incorrect letters guessed so far gsWrong :: Int, -- number of incorrect guesses gsWonLost :: Maybe Bool -- Just true = won, Just false = lost } deriving (Show) newGameState :: String -> GameState newGameState answer = GameState{ gsAnswer = map toUpper answer, gsKnown = (map (filt $ not . isAlpha) answer), gsGuesses = [], gsWrong = 0, gsWonLost = Nothing} data UserInput = UIGuess Char | UIQuit | UINewGame | UIRefresh deriving (Show) main :: IO () main = do hSetBuffering stdout NoBuffering putStr "Welcome to Hangman!\n\n" putStr instructions runStateT startNewGame undefined return () startNewGame :: StateT GameState IO () startNewGame = do nWord <- liftIO $ getStdRandom (randomR (0,length wordList - 1)) let word = wordList !! nWord let gs = newGameState word put gs liftIO $ putStrLn $ renderGameState gs gameLoop gameLoop :: StateT GameState IO () gameLoop = do ui <- liftIO getUserInput case ui of UIGuess c -> do modify $ handleGuess c gs <- get liftIO $ putStrLn $ renderGameState gs case (gsWonLost gs) of Nothing -> gameLoop Just True -> do liftIO $ putStrLn "Congratulations, you won!" startNewGame Just False -> do liftIO $ putStrLn "You've been hanged!" liftIO $ putStrLn $ "The word was \'" ++ (gsAnswer gs) ++ "\'." startNewGame UIQuit -> do gs <- get liftIO $ putStrLn $ "The word was \'" ++ (gsAnswer gs) ++ "\'." liftIO $ putStrLn "Thank you for playing!" UINewGame -> do gs <- get liftIO $ putStrLn $ "The word was \'" ++ (gsAnswer gs) ++ "\'." startNewGame UIRefresh -> do gs <- get liftIO $ putStrLn $ renderGameState gs gameLoop getUserInput :: IO UserInput getUserInput = do putStr "Hangman> " response <- getLine if null response then getUserInput else do let c:cs = response if isAlpha c then return $ UIGuess $ toUpper c else if c == ':' && not (null cs) then case toLower (head cs) of 'q' -> return UIQuit 'n' -> return UINewGame 'r' -> return UIRefresh '?' -> do putStr instructions getUserInput otherwise -> do putStrLn $ "Unknown command \'" ++ cs ++ "\'" putStrLn $ "Use \':?\' for help." getUserInput else do putStrLn $ "Invalid input \'" ++ response ++ "\'" putStrLn $ "Use \':?\' for help." getUserInput instructions :: String instructions = "Instructions:\n" ++ "To guess a letter, type the letter and press enter.\n" ++ "To quit or restart the game, use the following commands:\n" ++ " :q = quit\n" ++ " :n = new game\n" ++ " :r = re-display the game state\n" ++ " :? = show instructions\n" ++ "\n" filt :: (a -> Bool) -> a -> Maybe a filt pred x = if pred x then Just x else Nothing handleGuess :: Char -> GameState -> GameState handleGuess ch state = if (elem ch $ gsGuesses state) then state else if (elem ch $ gsAnswer state) then let revealed = map (filt (== ch)) (gsAnswer state) known = zipWith mplus (gsKnown state) revealed won = all (maybe False (const True)) known in state{gsKnown = known, gsWonLost = filt id won} else let wrong = 1 + (gsWrong state) in state{gsGuesses = ch:(gsGuesses state), gsWrong = wrong, gsWonLost = filt not (wrong < 7)} wordList :: [String] wordList = ["alligator", "angelfish", "ant", "bear", "buffalo", "butterfly", "canary", "chameleon", "crab", "dinosaur", "dog", "dolphin", "eel", "elephant", "flamingo", "frog", "giraffe", "goldfish", "grasshopper", "hedgehog", "hippopotamus", "horse", "iguana", "jaguar", "jellyfish", "kangaroo", "kinkajou", "lemur", "lizard", "llama", "meerkat", "moose", "mouse", "narwhal", "nautilus", "nuthatch", "ostrich", "owl", "panda", "pelican", "quail", "quokka", "raccoon", "rhinoceros", "salamander", "sea horse", "sea urchin", "snail", "tiger", "toucan", "uakari", "unicorn", "vampire bat", "vulture", "walrus", "wildebeest", "worm", "xenops", "yak", "yellow jacket", "zebra"] renderGameState :: GameState -> String renderGameState gs = let noose = renderNoose $ gsWrong gs report = ["","The Word:","",word,"","Your Guesses:","",guessed] word = intersperse ' ' $ map (maybe '_' id) (gsKnown gs) guessed = gsGuesses gs in (concat $ zipWith (++) noose $ map (++ "\n") report) renderNoose :: Int -> [String] renderNoose n | n <= 0 = [ " ___ ", " / | ", " | ", " | ", " | ", " | ", " | ", " -+- "] renderNoose 1 = [ " ___ ", " / | ", " | O ", " | ", " | ", " | ", " | ", " -+- "] renderNoose 2 = [ " ___ ", " / | ", " | O ", " | | ", " | ", " | ", " | ", " -+- "] renderNoose 3 = [ " ___ ", " / | ", " | O ", " | --| ", " | ", " | ", " | ", " -+- "] renderNoose 4 = [ " ___ ", " / | ", " | O ", " | --|-- ", " | ", " | ", " | ", " -+- "] renderNoose 5 = [ " ___ ", " / | ", " | O ", " | --|-- ", " | | ", " | ", " | ", " -+- "] renderNoose 6 = [ " ___ ", " / | ", " | O ", " | --|-- ", " | | ", " | / ", " | ", " -+- "] renderNoose n | n >= 7 = [ " ___ ", " / | ", " | O ", " | --|-- ", " | | ", " | / \\ ", " | ", " -+- "]

Hi Ronald, Ronald Guida wrote:
I'm interested in learning how to program games. Since I have to start somewhere, I decided to write a simple Hangman game. I'm wondering if anyone can look at my code and give me some feedback.
Lots of fun, thanks! And nicely written. One point is that while it's OK to do your random calculation directly in IO for this simple case, in general you will have many random calculations and you will want to avoid forcing them all into IO. You can add one more field to GameState that holds a random generator. Let's say you call it gsRandGen. Make sure that gsRandGen gets initialized somewhere. Define this utility function: rand :: MonadState GameState m => (StdGen -> (a, StdGen)) -> m a rand f = do gs <- get let (x, g) = f $ gsRandGen gs put $ gs {gsRandGen = g} return x Now, instead of:
nWord <- liftIO $ getStdRandom (randomR (0,length wordList - 1))
you can write:
nWord <- rand $ randomR (0,length wordList - 1)
If you want, you can even remove the dependence on StdGen by making some of your function types polymorphic, qualified where necessary by RandomGen g => ... Regards, Yitz

Ronald Guida wrote:
Hi,
I'm interested in learning how to program games. Since I have to start somewhere, I decided to write a simple Hangman game. I'm wondering if anyone can look at my code and give me some feedback. Nicely written. 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. So here are a few pointers to ways of rewriting it to keep the IO to the top level and the actual work in a functional style:
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. 3: Your current design uses a random number generator in the IO monad. Someone already suggested moving that into the GameState. But you can also generate an infinite list of random numbers. Can you make your game a function of a list of random numbers? 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? Good luck, Paul.

Hi Paul, You gave some suggestions of other styles of Haskell programming that Ronald could try for his program. These styles are definitely worth knowing, so if Ronald is not familiar with them, he may want to try them out. However, in most cases, I think what Ronald already did is nicer than what you are suggesting. 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.
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. There is a lot of liftIO, because that is the bulk of the work in this program. But Ronald cleanly separated out the game logic, and even the pure parts of the UI logic, into pure functions like "handleGuess" and "renderGameState". I personally might have kept a more consistently monadic style by writing those as pure monads, like: handleGuess :: MonadState GameState m => Char -> m () renderGameState :: MonadState GameState m -> m String In certain situations, that approach gives more flexiblity. Like for refactoring, or adding new features. But Ronald's approach is also very nice, and I might also do that.
1: Your GameState type can itself be made into a monad.
Yes, it can. But StateT GameState IO is the perfect monad for this game - writing a new monad would just be reinventing the wheel. It would certainly be a good learning experience for understanding the inner workings of the state monad transformer, though.
2: You can layer monads by using monad transformers. Extend the solution to part 1 by using StateT IO instead of just State.
I think he is already using that type.
3: Your current design uses a random number generator in the IO monad. Someone already suggested moving that into the GameState. But you can also generate an infinite list of random numbers. Can you make your game a function of a list of random numbers?
He could, but 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. Generating an infinite list from a random generator "burns up" the generator, making it unusable for any further calculations. Sometimes that doesn't matter, but I think it's a bad habit. I admit you'll catch me doing it sometimes though, in "quick and dirty" situations like at the GHCi prompt.
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?
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. In many situations it's hard to avoid without making a wreck out of your whole program structure (though more and more tools are becoming available to help, such as the ByteString stuff). Ronald did great without it - why resort to that? All that said - this is clearly a matter of taste, of course. Thanks for bringing up a variety of approaches. Regards, Yitz

I wrote:
Generating an infinite list from a random generator "burns up" the generator, making it unusable for any further calculations.
Jake McArthur wrote:
That's what the split function is for. ^_^
Yes, that is a nice approach. I have been avoiding it due to the following comment in the docs for System.Random: "This is very useful in functional programs... but very little work has been done on statistically robust implementations of split ([System.Random#Burton, System.Random#Hellekalek] are the only examples we know of)." And my own experience has been that cases where I need split tend to be in a state monad anyway, where there isn't any real advantage to split. That said, looking around briefly, I came up with this paper by L'Ecuyer et al that does seem to describe a decent random generator with properties of split worked out: http://citeseer.ist.psu.edu/493863.html L'Ecuyer's implementations in C, C++ and Java are here: http://www.iro.umontreal.ca/~lecuyer/myftp/streams00/ If we had something like that in Haskell, I might use split more often. Regards, Yitz

On Tue, 2008-01-22 at 01:41 +0200, Yitzchak Gale wrote:
I wrote:
Generating an infinite list from a random generator "burns up" the generator, making it unusable for any further calculations.
Jake McArthur wrote:
That's what the split function is for. ^_^
Yes, that is a nice approach. I have been avoiding it due to the following comment in the docs for System.Random:
"This is very useful in functional programs... but very little work has been done on statistically robust implementations of split ([System.Random#Burton, System.Random#Hellekalek] are the only examples we know of)."
And my own experience has been that cases where I need split tend to be in a state monad anyway, where there isn't any real advantage to split.
That said, looking around briefly, I came up with this paper by L'Ecuyer et al that does seem to describe a decent random generator with properties of split worked out:
http://citeseer.ist.psu.edu/493863.html
L'Ecuyer's implementations in C, C++ and Java are here:
http://www.iro.umontreal.ca/~lecuyer/myftp/streams00/
If we had something like that in Haskell, I might use split more often.
According to the documentation http://www.haskell.org/ghc/docs/latest/html/libraries/random/System-Random.h... That -is- what we have.

I wrote:
That said, looking around briefly, I came up with this paper by L'Ecuyer et al that does seem to describe a decent random generator with properties of split worked out:
Derek Elkins wrote:
According to the documentation That -is- what we have.
No, we have a much older algorithm of L'Ecuyer. It has a much smaller period - 2e18 vs. 3e51. Much less was known about testing generator randomness at that time. More importantly, very little was said in that paper about splitting. The newer algorithm includes all the computational details about splitting. Sadly, even the newer paper does not propose any tests for the independence properties of streams after splitting. The assumption seems to be that the voluminous testing of the underlying generator is sufficient for that also. Regards, Yitz

On Tue, 2008-01-22 at 02:24 +0200, Yitzchak Gale wrote:
I wrote:
That said, looking around briefly, I came up with this paper by L'Ecuyer et al that does seem to describe a decent random generator with properties of split worked out:
Derek Elkins wrote:
According to the documentation That -is- what we have.
No, we have a much older algorithm of L'Ecuyer. It has a much smaller period - 2e18 vs. 3e51. Much less was known about testing generator randomness at that time.
Yeah, my fault.

"Yitzchak Gale"
L'Ecuyer's implementations in C, C++ and Java are here:
http://www.iro.umontreal.ca/~lecuyer/myftp/streams00/
If we had something like that in Haskell, I might use split more often.
Speaking of that, the generators that come in the box are awfully slow, I ended up calling into http://www.math.sci.hiroshima-u.ac.jp/ ~m-mat/MT/SFMT/index.html via the ffi. I wouldn't know how to fit it into the Random type, though, it only supports floats and doubles, and converting the C source to use a struct for its data to make it instantiable is another obstacle. -- (c) this sig last receiving data processing entity. Inspect headers for past copyright information. All rights reserved. Unauthorised copying, hiring, renting, public performance and/or broadcasting of this signature prohibited.

Achim Schneider wrote:
Speaking of that, the generators that come in the box are awfully slow, I ended up calling into http://www.math.sci.hiroshima-u.ac.jp/~m-mat/MT/SFMT/index.html via the ffi.
Yes, it would be nice to have the Mersenne Twister available. Not only for speed - it is widely used, so it could sometimes be very useful for us to be able to generate random sequences that are bit-compatible with the sequences generated in other languages.
I wouldn't know how to fit it into the Random type, though, it only supports floats and doubles, and converting the C source to use a struct for its data to make it instantiable is another obstacle.
A few people worked all of that out. It's not a big deal. But it never was quite finished and put into the libraries. Yes, it is all the rage these days to do the calculations in floating point, due to the properties of current processors. It's not a problem to fit it into the RandomGen class - just convert to an Int when you're done. But that slows things down. Too bad the current Random class always forces you to go through Int. It was a good idea back then. We could fix this without breaking any current code. Regards, Yitz

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

Ronald Guida
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?
What about carrying a list of Strings inside the State? Write a RandomGen and Random instance that return some dictionary file in random order. -- (c) this sig last receiving data processing entity. Inspect headers for past copyright information. All rights reserved. Unauthorised copying, hiring, renting, public performance and/or broadcasting of this signature prohibited.

Ronald Guida wrote:
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?
Achim Schneider wrote:
What about carrying a list of Strings inside the State?
Right, I think you need that if the word list can be reloaded, or selected at run time.
Write a RandomGen and Random instance that return some dictionary file in random order.
Whoa, I don't think we need to go that far. But good idea to extract out selecting the random word into a separate function. Later on you may want to change how that works, e.g., you may use larger word lists and switch to reading the word each time from a file. So this function should return the word in your monad. Changing the probability distribution sounds like a stretch, I can't think of too many games where you would ever want to do that at run time. In a game with real-time feedback, you may want to fiddle with the generator for speed reasons. Regards, Yitz
participants (6)
-
Achim Schneider
-
Derek Elkins
-
Jake McArthur
-
Paul Johnson
-
Ronald Guida
-
Yitzchak Gale