
I'm trying to define a type called Stream. For now, assume that that the type has 3 fields: uid, x, y. X and y represent a point in space that a stream occupies, and uid is a unique identifier for the stream. The uid should be "auto-generated". It's important that streams have an identity so that they can be referred to and manipulated. Streams will be put together into a list, and they'll eventually need to be able to point to one another. It would be nice to be able to print the uid, just to show that it works. Now it occured to me that what one might want to generate the uids is a monad, let's call it UID. It'll have a function get, which returns another identifier. I assumed that the best solution for the problem would be in terms of monads, because successive calls to get return different results; i.e. there's a bit of state going on inside. The values returned can start from 1, and increment by 1 each time. I had a look at some documentation at: http://www.haskell.org/tutorial/monads.html and I'm afraid my brain just froze. I get the idea that data SM a = SM (S -> (a,S)) maps a state to a result, and a new state. OTOH, looking at 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. Any pointers, like am I taking completely the wrong approach anyway? I'm also puzzled as to how the initial state would be set. ___________________________________________________________ Yahoo! Messenger - NEW crystal clear PC to PC calling worldwide with voicemail http://uk.messenger.yahoo.com

On Wed, 21 Sep 2005, Mark Carter wrote:
I get the idea that data SM a = SM (S -> (a,S)) maps a state to a result, and a new state. OTOH, looking at
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.
It really broke my brain for a while too - I had to graph the thing out on a piece of paper before I could follow what it was doing. The return should be easy enough, no? In the >>= code, c is "unboxed computation", fc is "function yielding computation", r is "result" and s is "state" - the first line of the let gets the result of the first computation and the state after it, the second line applies fc2 to the result to get the second computation and then the final line applies the computation to the intermediate state. There's a little boxing and unboxing going on, but that's pretty much it.
Any pointers, like am I taking completely the wrong approach anyway? I'm also puzzled as to how the initial state would be set.
You set the initial state with a "run" function, like so: runSM (SM f) initialState = f initialState The result will be a tuple: (result, finalState) -- flippa@flippac.org The task of the academic is not to scale great intellectual mountains, but to flatten them.

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
participants (3)
-
Mark Carter
-
Philippa Cowderoy
-
Stefan Holdermans