Kaveh Shahbazian wrote:
Thanks All
This is about my tries to understand monads and handling state - as
you perfectly know - is one of them. I have understood a little about
monads but that knowledge does not satidfy me. Again Thankyou

There are many tutorials available from the wiki at
http://www.haskell.org/haskellwiki/Books_and_tutorials#Using_Monads
and http://www.haskell.org/haskellwiki/Monad

Another way is to look at the source code for the State monad and StateT monad transformer, then you can see that the mysterious monad is nothing other than a normal data or newtype declaration together with an instance declaration ie:

   -- from State.hs
   newtype State s a = S (s -> (a,s))

   instance Monad (State s) where
         return a       = S (\s -> (a, s))
         S m >>= k   = S (\s ->
                                       let
                                           (a, s1) = m s
                                           S n    = k a
                                       in n s1)

So if you want to understand what's going on when you write:

   do
         x <- q
         p

a first step is to remove the syntactic sugar to get:

   q >>= (\x -> p)

and then replace the >>= with it's definition for the monad you're using.

For example with the State monad, (q) must be some expression which evaluates to something of the form S fq where fq is a function with type s -> (a,s), and similarly, (\x -> p) must have type a ->S ( s -> (a,s)). If we choose names for these values which describe the types we have:

   q = S s_as
   p = a_S_s_as

so        q >>= (\x -> p)
===    S s_as >>= a_S_s_as
===    S (\s0 ->
                 let
                       (a1, s1) = s_as s0
                       S s_a2s2 = a_S_s_as a1
                 in
                       s_a2s2 s1)

If we use State.runState s0 (q >>= (\x -> p)) to execute this composite action, from the source we see that:

   runState         :: s -> State s a -> (a,s)
   runState s (S m)  = m s

so
          runState s0 (q >>= (\x -> p))
===    runState s0 (S (\s0 -> let ... in s_a2s2 s1))
===    (\s0 -> let ... in s_a2s2 s1) s0
===    s_a2s2 s1
===    a2s2 -- ie (a2, s2)

Anyway I hope I haven't made things more complicated! ;-)
The best thing is to just try and work through some examples yourself with pencil and paper and read lots of tutorials until things start clicking into place.

Regards, Brian.

--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to