[Haskell-beginners] Trying to grasp Monads - IO and delayed actions

John M. Dlugosz ngnr63q02 at sneakemail.com
Sun Apr 6 07:41:41 UTC 2014


A spiral approach to learning: you understand, then you learn more, and then you are more 
confused than ever.

I recall that a function in the IO Monad just combines actions to make a big action list, 
and doesn't actually do the side-effect-laden "work" until it is later triggered, normally 
because the program is defined to evaluate main.

Depending on the time of day and which example I pick, I can sometimes follow what's 
"really happening" in the definition of >>=.  But here are some specific questions:

In <http://www.haskell.org/haskellwiki/Monads_as_computation>

> What is a for-each loop really? It's something which performs some action based on each
> element of a list. So we might imagine a function with the type:
>
> forM :: (Monad m) => [a] -> (a -> m b) -> m [b]
>
> (as an added bonus, we'll have it collect the results of each iteration).
>
> We can write this with sequence and map:
>
> forM xs f = sequence (map f xs)
>
> we apply the function to each element of the list to construct the action for that
> iteration, and then sequence the actions together into a single computation.
>

So map by itself produces a [m b].  Why does it need to be turned into m [b]?  What does 
the 'sequence' accomplish, other than restructuring the results that already exist?

The reason I asked about (#⋯#) is because I wanted to see what IO was really doing, to see 
what the difference was between using >>= initially and then somehow "cranking" it later.

<http://hackage.haskell.org/package/base-4.6.0.1/docs/src/GHC-Base.html#%3E%3E%3D> lists
> instance  Monad IO  where
>     {-# INLINE return #-}
>     {-# INLINE (>>)   #-}
>     {-# INLINE (>>=)  #-}
>     m >> k    = m >>= \ _ -> k
>     return    = returnIO
>     (>>=)     = bindIO
>     fail s    = failIO s
>
> returnIO :: a -> IO a
> returnIO x = IO $ \ s -> (# s, x #)
>
> bindIO :: IO a -> (a -> IO b) -> IO b
> bindIO (IO m) k = IO $ \ s -> case m s of (# new_s, a #) -> unIO (k a) new_s
>
> thenIO :: IO a -> IO b -> IO b
> thenIO (IO m) k = IO $ \ s -> case m s of (# new_s, _ #) -> unIO k new_s
>
> unIO :: IO a -> (State# RealWorld -> (# State# RealWorld, a #))
> unIO (IO a) = a

where bindIO is the function of interest.  In a chain of commands, getLine might be the 
'k' argument to bindIO.  Somewhere there's a real machine function called to do the 
reading from the file, right?






More information about the Beginners mailing list