Search code examples
haskelliofold

Folding Over User Input in Haskell


I'm new to Haskell and have been programming a simple hangman game to get used to the language. I'm storing the game state in a datatype called GameState.

data GameState = GameState
  { word :: String,
    blanks :: String,
    wrongGuesses :: [Char]
  } deriving Show

I also have a function to update the state given an input character and another function to check if the game is finished.

updateState :: GameState -> Char -> GameState
updateState state c
  | (c `elem` (word state)) = state { blanks = newBlanks }
  | otherwise = state { wrongGuesses = c:(wrongGuesses state)}
  where newBlanks = foldr replaceAt (blanks state) $ elemIndices c (word state)
        replaceAt i = (take i) <> (const [c]) <> (drop (i + 1))

isPlaying :: GameState -> Bool
isPlaying state = ('_' `elem` (blanks state)) && (length (wrongGuesses state) < 5)

Given a list of characters, I can do a fold to simulate the game on the given input.

runGame :: GameState -> [Char] -> [GameState]
runGame initialState chars = takeWhile isPlaying $ scanl updateState initialState chars

My question is how to adapt this code to work with actual user input. I've tried using sequence, but the program just endlessly gets user input.

main = runGame (newState "secret") <$> (sequence $ repeat getChar)

Is there any way to fold over getChar similar to how runGame works and print the game state after each user input? I'd like to avoid explicit recursion like runGame does, and if possible, I'd like to stick with standard library functions.


Solution

  • Firstly: why doesn’t your program work? The issue is that when you do repeat getChar, that repeats getChar infinitely. Then you use sequence; because of how sequence is implemented, it needs to go through the whole list before returning. But that list is infinite! Result: an infinite loop.

    Now, let’s try to solve this. Often the first thing I do in this sort of scenario is to forget about functions such as sequence and just write it as a recursive function:

    main = runGameIO (newState "secret")
      where
        runGameIO :: GameState -> IO ()
        runGameIO curState = do
            input <- getChar
            let newState = updateState curState input
            if isPlaying newState        -- if still playing
                then runGameIO newState  -- then repeat with new state
                else return ()           -- else finish
    

    Now, is there any way to simplify runGameIO? I can’t see any as it is now. Certainly, we can see now that sequence won’t work: sequence requires that each item given to it is independent, i.e. each monadic action doesn’t depend on a previous monadic action. (That’s why you can also implement sequence with an Applicative constraint instead of a Monad constraint.) But this problem is all about responding given the previous state! So clearly sequence won’t work.

    Next, let’s desugar the do-notation to see if we can spot anything:

    runGameIO :: GameState -> Io ()
    runGameIO curState =
        getChar >>= \input ->
        let newState = updateState curState input
        in if isPlaying newState then runGameIO newState else return ()
    

    Hmm… still nothing, really. But this makes it more obvious that you can use fmap here:

    runGameIO :: GameState -> Io ()
    runGameIO curState =
        fmap (updateState curState) getChar >>= \newState ->
        if isPlaying newState then runGameIO newState else return ()
    

    At this point, there’s often some clever trick which can be used to get rid of the explicit recursion. But I can’t see anything to do here. If you weren’t restricting yourself to the standard library, I would say to use iterateUntilM from the monad-loops package, but you can’t use that. Sometimes explicit recursion is just best, and this seems to be one of those cases.