Trying to grasp Monads - IO and delayed actions

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%3... 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?

[IO b] is a list of functions that perform side-effects. You can remove
elements of the list, add new ones, change the order of the elements, etc.
All of these operations are pure because you do not execute side-effecting
functions: you just manipulate a list. When you use "sequence" on it and
get a "IO [b]", you build a single function that calls every function of
the previous list in sequence (think ";" in imperative programming
languages) and returns their results in a list. As long as you don't call
it, no side-effect occurs.
The IO monad is used to ensure that side-effecting functions are performed
in a deterministic order and are not mixed up with pure code. See my
introduction in [1], maybe it can help you understand the motivation and
the code in GHC.Base where RealWorld is used explicitly.
Cheers
Sylvain
[1]
http://www.sylvain-henry.info/home/data/uploads/talks/shenry-2013-02-05-hask...
slide 20)
2014-04-06 9:41 GMT+02:00 John M. Dlugosz
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?
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On April 6, 2014 10:41:41 AM GMT+03:00, "John M. Dlugosz"
A spiral approach to learning: you understand, then you learn more, and then you are more confused than ever.
Excellent characterization of learning. Mind if I use it?
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?
In essence, what a value of type Monad m => [m a] means is that you have a list full of monadic actions. It's a bit like having a list of functions - while you can certainly use the actions and functions, respectively, they haven't been evaluated *yet*. Whereas a value of type Monad m => m [a] represents a monadic action returning some list of values. Thus, sequence is collecting the values computed by each action. This is all made clear by the implementation of sequence: sequence ms = foldr k (return []) ms where k m m' = do { x <- m; xs <- m'; return (x:xs) } Note that lists aren't special, Data.Traversable defines sequence for all traversable values: sequence = unwrapMonad . traverse . WrapMonad
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%3... 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? Yes. I don't know enough about GHC's implementation of the Prelude, but basically, what's going on here is that IO works a bit like State, except it uses unboxed tuples and doesn't have an evalState function. getLine and its ilk are all probably defined using primitive operations. That basically sums up my knowledge of how IO works. Hoping to help, Gesh

On 4/6/2014 4:47 AM, Gesh wrote:
On April 6, 2014 10:41:41 AM GMT+03:00, "John M. Dlugosz"
wrote: A spiral approach to learning: you understand, then you learn more, and then you are more confused than ever.
Excellent characterization of learning. Mind if I use it?
By my guest. See http://www.dlugosz.com/zeta/?p=241
participants (3)
-
Gesh
-
John M. Dlugosz
-
Sylvain Henry