[Haskell-cafe] State of Ignorance

Hans van Thiel hthiel.char at zonnet.nl
Fri Mar 9 12:58:31 EST 2007


Hello All,

I have the following functions, based on Thompson's CFP example (also in
Control.Monad.State documentation) of using a state monad on a tree. My
functions (on a list) work, but I don't understand why.

Main> getInds ["house","tree","cat","house","cat","dog","tree"]
[0,1,2,0,2,3,1]
Main> getTb ["house","tree","cat","house","cat","dog","tree"]
["house","tree","cat","dog"]

This, from CFP, is clear enough.

repl1 :: String -> [String] -> ([String], Int)
repl1 x tb 
         | elem x tb = (tb, fromJust (elemIndex x tb))
         | otherwise = (tb ++ [x], length tb)

then, turn this into a function to a state monad type:

toMyState :: String -> MyState String Int   
toMyState x = MyStateC (repl1 x)

where the monad is defined as:

data MyState a b = MyStateC ([a] -> ([a], b))

instance Monad (MyState a) where
   return x = MyStateC (\tb -> (tb, x))
   (MyStateC st) >>= f =  
       MyStateC (\tb -> let                       
                          (newtb, y) = st tb
                          (MyStateC trans) = f y 
                        in trans newtb )

Now I understand this (barely) in the sense that >>= works through
defining how f takes its values from st. So, f would be the function:
toMystate and trans would be: (repl1 x). 
But then y would have to be of type String, whereas the y in the tuple
would have type Int, since it is generated by st. I just don't get it.

Next the book explains how to extract values from a state and again
that's pretty clear:

extr1 :: MyState a b -> b
extr1 (MyStateC st) = snd (st [])

extr2 :: MyState a b -> [a]
extr2 (MyStateC st) = fst (st [])

I have a list instead of a tree, so I tried:

strtoMS :: [String] -> [MyState String Int]
strtoMS ls = map toMyState ls 

and the final functions are:

getInds :: [String] -> [Int]
getInds =  extr1 . sequence . strtoMS

getTb :: [String] -> [String]
getTb = extr2 . sequence . strtoMS

They work, but now I don't understand sequence, defined in the Prelude.
From: a Tour of the Haskell Monad Functions
http://members.chello.nl/hjgtuyl/tourdemonad.html

sequence :: Monad m => [m a] -> m [a]
sequence = foldr mcons (return [])
  where
    mcons p q = p >>= \x -> q >>= \y -> return (x : y)

This has a different bind (>>=) from the one in the MyState monad, 
yet is appears to perform all the state transformations. 

The documentation says:
"sequence xs evaluates all monadic values in the list xs, from left to right,
 and returns a list of the "contents" of these monads, placing this list 
in a monad of the same type. Note, that "evaluating" can be interpreted 
as "performing an action", for example in the case of print."

It looks to me as if sequence works here because values of MyState are 
themselves functions, but how?

Many thanks for any pointers and clarification!

Hans van Thiel




More information about the Haskell-Cafe mailing list