[Haskell-beginners] StateT, list monad

Daniel Fischer daniel.is.fischer at web.de
Wed Sep 23 18:36:09 EDT 2009


Am Donnerstag 24 September 2009 00:03:03 schrieb Michael Mossey:
> Trying to understand Douglas Auclair's article
> "MonadPlus - What a super monad!" here
> <http://www.haskell.org/sitewiki/images/6/6a/TMR-Issue11.pdf>
>
> Defines
>
> splits :: Eq a => [a] -> [(a,[a])]
> splits list = do x <- list
>                  return (x, delete x list)
>
> choose :: Eq a => StateT [a] [] a
> choose = StateT (\s -> splits s)
>
> I'm trying to understand what "StateT [a] [] a" means:

StateT stateType innerMonad resultType

The state is a list of a, the inner monad is the list monad, apart from the newtype 
wrapper, it's

[a] -> [(a,[a])]

>
> I wrote
>
> t1 :: StateT [Int] [] [Int]
> t1 = do
>   s <- get
>   return s
>
> That compiles. Then I tried to write
>
> t2 :: StateT [Int] [] [Int]
> t2 = do
>   x <- [1,2,3]
>   s <- get
>   return (x:s)
>
> I thought this would be fine because [1,2,3] is an example of a list monad.

Within one do-block, you can use only one monad.

do x <- action1
   y <- action2
   return (f x y)

desugars into

action1 >>= (\x -> (action2 >>= (\y -> (return (f x y)))))

(I used more parentheses than necessary to make the associativity clear, with less 
clutter, it's

action1 >>= \x -> action2 >>= \y -> return (f x y)
.)

The type of (>>=) is

(>>=) :: Monad m => m a -> (a -> m b) -> m b

so you can use only one monad in such an expression.

With StateT (most monad transformers, I think), you can achieve what you want with

t2 :: StateT [Int] [] [Int]
t2 = do
  x <- lift [1,2,3]
  s <- get
  return (x:s)

'lift' lifts actions in the inner monad to StateT actions.
>
> But I get
>
> "Can't match expected type StateT [Int] [] t
> against inferred type [a]"
>




More information about the Beginners mailing list