[Haskell-cafe] Loop with the StateT monad

p75213 at gmail.com p75213 at gmail.com
Sat Mar 18 05:52:12 UTC 2017


This is an exercise to learn the StateT monad. The program implements
the game Morra. The two players are the computer and a person. The state
accumulates the score of the computer and player. The program works for
one iteration of function morra only. However I am at a loss how to loop
it. I have tried a few things but nothing seems to work. I have narrowed
the problem down to the "p <- liftIO getChar" statement. The second time
through the loop it isn't executed. I have bracketed the statement with
"liftIO $ putStrLn "before" and liftIO $ putStrLn "after". This is the
program:

module Morra where

import Control.Monad.Trans.State.Lazy
import Control.Monad.IO.Class
import Data.Char (isDigit, digitToInt)
import System.Random (randomRIO)
import Control.Monad (when)

morra :: StateT (Int, Int) IO ()
morra = do
   liftIO $ putStrLn "before"
   p <- liftIO getChar
   liftIO $ putStrLn "after"
   when (isDigit p) $ do
     let p' = digitToInt p
     c <- liftIO $ randomRIO (1, 2)
     liftIO $ putStrLn ("P: " ++ [p])
     liftIO $ putStrLn ("C: " ++ show c)
     (pt, ct) <- get
     if even (c + p') then do
       liftIO $ putStrLn "Computer Wins"
       put (pt, ct + 1)
     else do
       liftIO $ putStrLn "Player Wins"
       put (pt + 1, ct)
     morra

main :: IO ()
main = do
   putStrLn "-- p is Player"
   putStrLn "-- c is Computer"
   putStrLn "-- Player is odds, Computer is evens."
   (personS,compS) <- execStateT morra (0,0)
   putStrLn ("Person Score: " ++ show personS)
   putStrLn ("Computer Score: " ++ show compS)
   if personS > compS then
     putStrLn "Winner is Person"
   else
     putStrLn "Winner is Computer"


and this is the output:

*Morra> main
-- p is Player
-- c is Computer
-- Player is odds, Computer is evens.
before
1
after
P: 1
C: 2
Player Wins
before
after
Person Score: 1
Computer Score: 0
Winner is Person
*Morra>



More information about the Haskell-Cafe mailing list