[Haskell-cafe] Can we come out of a monad?

aditya siram aditya.siram at gmail.com
Sat Jul 31 16:33:25 EDT 2010


Skipped content of type multipart/alternative-------------- next part --------------
-- 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
                


More information about the Haskell-Cafe mailing list