Each monad implementation is different. In the case of the State monad your
'execState' call extracts a non-monadic value.

Of the basic monads I found the State monad the most confusing because of
the complicated way in which it threads state through the computation. In
the end, desugaring the do-notation and tracing through the code manually
was the most helpful to me so I encourage you to do the same. After I did
this a couple of times I got the gist of it.

I have attached a trace of your State monad functions 'modifiedImage' and
'drawPixels' which shows the intermediate stages explicitly. If you follow
the steps you will see that there is no magic in how a non-monadic value is
extracted from the State monad.

Let me know if I can be of more help.

-deech


When I am looking at a confusing monad like the State monad

On Fri, Jul 30, 2010 at 1:23 AM, C K Kashyap <ckkash...@gmail.com> wrote:

> Hi,
> In the code here -
> http://hpaste.org/fastcgi/hpaste.fcgi/view?id=28393#a28393
> If I look at the type of modifiedImage, its simply ByteString - but isn't
> it actually getting into and back out of the state monad? I am of the
> understanding that once you into a monad, you cant get out of it? Is this
> breaking the "monad" scheme?
> --
> Regards,
> Kashyap
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
-- First we need some pieces from the Monad library 
newtype State s a = State {runState :: a -> (a,s)}
                  = runState :: State s a -> (a -> (a,s)) 

execState = snd (runState m s)

-- Bind operation for State monads
m >>= k = State $ \s -> let
                          (a, s') = runState m s
                        in runState (k a) s'
              
-- Your example with the last two 'setPixel ...' lines removed for simplicity
drawPixels = do
      setPixel 5 10 (255, 255, 255)
      setPixel 100 100 (255, 0, 0)
      setPixel 101 100 (255, 0, 0)
      
modifiedImage = execState drawPixels  blankImage

-- Your example with each call to 'setPixel ...' replaced with some shortened
-- names. So, for example, pix_5_10 = setPixel 5 10 (255,255,255)
drawPixels = do
      pix_5_10
      pix_100_100
      pix_101_100
 
-- Desugared version of drawPixel
drawPixels
  = pix_5_10          >>=
    \_ -> pix_100_100 >>= 
    \_ -> pix101_100
        
-- Trace of drawPixels          
drawPixels
  = State $ \s -> let (a,s') = runState (State (\a -> ((), pix_5_10 a))) s
                        in runState ((\_ -> State (\a -> ((),pix_100_100 a)) >>=
                                      \_ -> State (\a -> ((),pix_101_100 a))) a)
                                     s'
       
  = State $ \s -> runState ((\_ -> State $ \a -> ((),pix_100_100 a) >>=
                             \_ -> State $ \a -> ((),pix_101_100 a)) ())
                            (pix_5_10 s)
  = State $ \s -> runState (State $
                               \s -> runState (State $ \a -> ((),pix_101_100 
a)) $ pix_100_100 s)
                           (pix_5_10 s)
  = State $ \s -> runState (State $
                               \s -> (\a -> ((),pix_101_100 a)) $ pix_100_100 s)
                           (pix_5_10 s')
  = State $ \s -> (\s -> \a -> ((),pix_101_100 a) $ pix_100_100 s) pix_5_10 s   
                

-- Trace of modifiedImage
modifiedImage = execState drawPixels blankImage
              = execState (State $ \s -> (\s -> \a -> ((),pix_101_100 a) $ 
pix_100_100 s) pix_5_10 s) blankImage
              = snd (\s -> (\s -> \a -> ((),pix_101_100 a) $ pix_100_100 s) 
pix_5_10 s) blankImage
              = snd ((\s -> (\a -> ((),pix_101_100 a)) $ pix_100_100 s) $ 
pix_5_10 blankImage
              = snd ((\a -> ((),pix_101_100 a)) pix_100_100 $ pix_5_10 
blankImage)
              = snd ((), pix_101_100 $ pix_100_100 $ pix_5_10 blankImage)
              = pix_101_100 $ pix_100_100 $ pix_5_10 blankImage
                
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to