[Haskell-cafe] Funny State monad dependency

Daniel Fischer daniel.is.fischer at web.de
Wed Apr 16 09:22:09 EDT 2008


Am Mittwoch, 16. April 2008 14:56 schrieb Hans Aberg:
> When I load the State module in Hugs, then I can define the function
> f below, but I do not immediately see exactly what function "return"
> returns. Explanation welcome.
>
> For example:
>    > f [2..4] [6..9]
>
>    [6,7,8,9,6,7,8,9,6,7,8,9]
> That is, it just repeats the second argument as many times as the
> length of the second argument.
>
>    Hans Aberg
>
> --------
> import Control.Monad.State
>
> f :: Monad a => a b -> a c -> a c
> f x y = x >>= (return y)
> --------
>
The point is the

instance Monad ((->) a) where
    return x = const x
    f >>= g = \x -> g (f x) x

which is defined in Control.Monad.Instances  (try in GHCI:
Prelude> let f x y = x >>= (return y)
Prelude> :t f
f :: (Monad ((->) a), Monad m) => m a -> m b -> m b
). This is imported into Control.Monad.State and hence the instance is 
visible.

By the type of (>>=), (return y) must have type (a -> m b), on the other hand, 
if y has type c, then (return y) has type (m' c) for some monad m'. Unifying 
m' c and a -> m b gives then m' === ((->) a) and c === m b.

Now according to the instance, return y === const y, so f is the same as
g x y = x >>= (const y).


More information about the Haskell-Cafe mailing list