[Haskell-beginners] Haskell state monad example - type mismatch error

Antoine Latter aslatter at gmail.com
Fri Jul 22 16:59:29 CEST 2011


On Fri, Jul 22, 2011 at 9:50 AM, Rohit Garg <rpg.314 at gmail.com> wrote:
> Hi,
>
> I am trying out a simple haskell state monad example. I think I have
> understood the concept of monads, but I am getting stuck at using
> State monad. As far as I understand, the code below should compile,
> but it is throwing a type mismatch error in the argument to show. The
> rest of the code, however, type checks all right.
>

You need to include the function 'runState' or 'evalState' somewhere -
a value of type 'State x y' is not a function, so trying to apply it
to values as if it were a function is not going to work.

http://hackage.haskell.org/packages/archive/mtl/latest/doc/html/Control-Monad-State-Lazy.html#v:runState
http://hackage.haskell.org/packages/archive/mtl/latest/doc/html/Control-Monad-State-Lazy.html#v:evalState

Antoine

> If any one can point out what I am doing wrong, it would be really helpful.
>
> Thanks and regards,
> Rohit
>
> ===============================
> import Control.Monad.State
> import Data.Word
>
> type LCGState = Word32
>
> lcg :: LCGState -> (Integer, LCGState)
> lcg s0 = (output, s1)
>    where s1 = 1103515245 * s0 + 12345
>          output = fromIntegral s1 * 2^16 `div` 2^32
>
> seed :: LCGState
> seed = 5
>
> getRandom :: State LCGState Integer
> getRandom = do
>    s0 <- get
>    let (x,s1) = lcg s0
>    put s1
>    return x
>
> addThreeRandoms :: State LCGState Integer
> addThreeRandoms = do
>    a <- getRandom
>    b <- getRandom
>    c <- getRandom
>    return (a+b+c)
>
> main :: IO ()
> main = putStrLn show(addThreeRandoms seed)
>
> --
> Rohit Garg
>
> http://rpg-314.blogspot.com/
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>



More information about the Beginners mailing list