[Haskell-beginners] bad state monad instances

Alexander Dunlap alexander.dunlap at gmail.com
Tue Jun 22 22:13:30 EDT 2010


Change the instance head to

instance MonadState s (State s) where

It looks like the tutorial has the two parameters for MonadState in
the opposite order as does the mtl package.

Alex

On Tue, Jun 22, 2010 at 6:53 PM, Keith Sheppard <keithshep at gmail.com> wrote:
> Hi,
>
> I'm working on understanding the state monad, and I got stumped pretty
> much right away. When I run the following script (with instances
> copied verbatim from
> http://www.haskell.org/all_about_monads/html/statemonad.html )
>
> #!/usr/bin/env runhaskell
> \begin{code}
> {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-}
> import Control.Monad.State(Monad, MonadState(..))
>
> newtype State s a = State { runState :: (s -> (a,s)) }
>
> instance Monad (State s) where
>    return a        = State $ \s -> (a,s)
>    (State x) >>= f = State $ \s -> let (v,s') = x s in runState (f v) s'
>
> instance MonadState (State s) s where
>    get   = State $ \s -> (s,s)
>    put s = State $ \_ -> ((),s)
>
> main :: IO ()
> main = putStrLn "hello"
>
> \end{code}
>
>
> It fails with:
> statemonadtest.lhs:11:20:
>    `State s' is not applied to enough type arguments
>    Expected kind `*', but `State s' has kind `* -> *'
>    In the instance declaration for `MonadState (State s) s'
>
> Can you see what I'm doing wrong? I must be making a really basic
> mistake but I'm not sure what it is.
>
> Thanks, Keith
> --
> keithsheppard.name
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>


More information about the Beginners mailing list