[Haskell-cafe] Really confused
Stefan Holdermans
stefan at cs.uu.nl
Thu Sep 22 03:42:56 EDT 2005
Mark,
On Sep 21, 2005, at 8:12 PM, Mark Carter wrote:
> instance Monad SM where
> -- defines state propagation
> SM c1 >>= fc2 = SM (\s0 -> let (r,s1) = c1 s0
> SM c2 = fc2 r in
> c2 s1)
> return k = SM (\s -> (k,s))
>
> just confuses me no end.
I think, Philippa already did a good job explaining what goes on here.
If I may add to that, I myself often find it quite helpful to first
try to implement the function myself and then have a look at the
provided implementation to see where it coincides with my attempt
and, more importantly, where differences occur.
For the bind operator, (>>=), of the state monad, SM, you then start
with what you already know, i.e., the types:
data SM a = SM (S -> (a, S))
(>>=) :: SM a -> (a -> SM b) -> SM b
(For some abstract type S representing the state.)
Then , you try to write down your own definition of (>>=) without
looking at the provided implementation.
The left-hand side is fairly easy, for SM has only one constructor:
SM h >>= f = ...
Keep in mind the types of h and f:
h :: S -> (a, S)
f :: a -> SM b
Our goal is to produce a value of type SM b. Again, since SM has only
one constructor, there's no doubt on the form of such a value:
SM h >>= f = SM g
With
g :: S -> (b, S)
It remains to find a suitable definition of the function g. By its
type, we know that g should take an argument of type S, so we have:
SM h >>= f = SM g
where
g s = ...
To construct the right-hand side of g, we have available the
functions h and f. Arguably the only useful thing you can do with a
function is applying it. Here, h is the only function that can be
applied to a value of type S, so let's apply it to s. Then, by the
type of h, we obtain a pair (a, s') with a :: a and s' :: S:
SM h >>= f = SM g
where
g s = let (a, s') = h s
in ...
The first component of the pair, a, can now be fed as an argument to
the function f to obtain a a value of type SM b. Once again, because
SM has only one constructor, the form of this value is obvious:
SM h >>= f = SM g
where
g s = let (a, s') = h s
SM k = f a
in ...
With
k :: S -> (b, S)
Note that the the result type of k is exactly the result type we need
for g. So all that's left is supplying k with an argument of type S.
Choosing s', we obtain:
SM h >>= f = SM g
where
g s = let (a, s') = h s
SM k = f a
in k s'
Rewriting this a bit will give you the provided definition for (>>=).
Note how we have let the types guide the construction of (>>=). Of
course, it's not all that simple. For instance, choosing the original
state s to be passed to the function k in the last step would have
also given us a type-correct program. However, that definition would
not have captured the concept of sequencing, for the intermediate
state s' would have been discarded. So, although following the types
can make defining functions that seem complicated at first sight more
easy, you still have to be aware of what you are defining. However,
as soon as you get a bit more familiar with the concept of a monad
and, more particular, the bind operation, understanding non-trivial
monads like the state monad turns out to be not that hard after all.
HTH,
Stefan
More information about the Haskell-Cafe
mailing list