[Haskell-cafe] State Monad
Mark Carroll
mark at ixod.org
Fri Mar 4 10:44:40 EST 2005
On Fri, 4 Mar 2005, Mark Carroll wrote:
(snip)
> Enclosed is a programme that asks for two ints from standard input, adds
(snip)
Let me try again. (-:
-- Mark
-------------- next part --------------
module StackMTest
where
import StackM
import Control.Monad
import Control.Monad.Trans
import System.IO
import System.Random
add :: Num a => StackM a IO ()
add =
do x <- popM
y <- popM
pushM (x + y)
throwTenDie :: StackM Int IO ()
throwTenDie = lift (getStdRandom (randomR (1, 10))) >>= pushM
stackMTest :: StackM Int IO Int
stackMTest =
do pushNumber
pushNumber
throwTenDie
add
add
popM
where
pushNumber =
do text <- lift $ getLine
pushM (read text)
main :: IO ()
main = runStackM stackMTest >>= print
More information about the Haskell-Cafe
mailing list