
Good morning all, I think I've got the hang of the way state is carried and fancy operators work in monads but still have a major sticky issue. With lazy evaluation where is it written that if you write things with no dependencies with a "do" things will be done in order ? Or isn't it ? Is it a feature of the language we're supposed to accept ? Is it something in the implementation of IO ? Is the do keyword more than just a syntactic sugar for a string of binds and lambdas ? Jon

It actually isn't written anywhere, and multiple statements in a do actually don't have to be evaluated in in the order they're written, for monads in general.
For most monads though, the implementation of >>= examines the left argument sufficiently to force things to be evaluated in that order (at least to the level of the monad's constructors).
IO in particular is implemented such that the effects of everything on the left of the bind (or earlier in a do block) will have been carried out before any of the effects from the right of the bind (later in the do). But even in the IO monad laziness can "delay" evaluation of pure computation mixed in with the IO actions; it just can't change the order the actions are executed in.
On 15 April 2015 7:07:24 pm AEST, Jon Schneider
Good morning all,
I think I've got the hang of the way state is carried and fancy operators work in monads but still have a major sticky issue.
With lazy evaluation where is it written that if you write things with no dependencies with a "do" things will be done in order ? Or isn't it ?
Is it a feature of the language we're supposed to accept ?
Is it something in the implementation of IO ?
Is the do keyword more than just a syntactic sugar for a string of binds and lambdas ?
Jon
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

Hi,
You can consider that:
type IO a = World -> (World, a)
Where World is the state of the impure world.
So when you have:
getLine :: IO String
putStrLn :: String -> IO ()
Is is in fact:
getLine :: World -> (World, String)
putStrLn :: String -> World -> (World, ())
You can compose IO actions with:
(>>=) :: IO a -> (a -> IO b) -> IO b
(>>=) :: (World -> (World,a)) -> (a -> World -> (World,b)) -> World ->
(World,b)
(>>=) f g w = let (w2,a) = f w in g a w2
do-notation is just syntactic sugar for this operator.
So there is an implicit dependency between both IO functions: the state of
the World (which obviously doesn't appear in the compiled code).
Sylvain
2015-04-15 11:07 GMT+02:00 Jon Schneider
Good morning all,
I think I've got the hang of the way state is carried and fancy operators work in monads but still have a major sticky issue.
With lazy evaluation where is it written that if you write things with no dependencies with a "do" things will be done in order ? Or isn't it ?
Is it a feature of the language we're supposed to accept ?
Is it something in the implementation of IO ?
Is the do keyword more than just a syntactic sugar for a string of binds and lambdas ?
Jon
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

With lazy evaluation where is it written that if you write things with no dependencies with a "do" things will be done in order ? Or isn't it ?
Since Haskell is purely functional the evaluation order shouldn't matter unless you do IO or for efficiency purposes. In general you can use "seq :: a -> b -> b" or Bang patterns (!) to control execution order. "seq" will evaluate "a" to Weak Head Normal Form (WHNF) and then return "b". WHNF just means it will evaluate until it finds a Constructor. In the case of lists for instance it will see if your value is ":" or "[]". Now you can use that to implement your monads. For the state monad for instance there is a strict and a "lazy" version. newtype State s a = State { runState :: s -> (a,s) } instance Monad (State s) where act1 >>= f2 = State $ \s1 -> runState (f2 input2) s2 where (input2, s2) = runState act1 s1 instance Monad (State s) where act1 >>= f2 = State $ \s1 -> s2 `seq` runState (f2 input2) s2 where (input2, s2) = runState act1 s1 You can see in the second implementation s2 has to be evaluated to WHNF. So the runState on the 3rd line has to be evaluated before the runState on the 2nd line.
Is it something in the implementation of IO ?
In the case of IO monad you are almost guaranteed that things get executed in order. The one exception is (unsafeInterleaveIO :: IO a -> IO a). This will only be evaluated when you use the result (use the result means make a case statement to see which constructor it is. e.g. ":" or "[]"). LazyIO probably also uses unsafeInterleaveIO and should in my opinion be called unsafeIO. The problem with unsafeInterleaveIO is that you have to catch the IOErrors at arbitrary places. For instance, you can get a read error when looking at a part of a string because the reading was delayed until you look at it.
Is the do keyword more than just a syntactic sugar for a string of binds and lambdas ?
No, "do" is not more than syntactic sugar. The way to control execution order is "seq" and bang patterns. Hope this helps Silvio

Perhaps I need to be more specific. main = do a <- getLine b <- getLine Can we say "a" absolutely always receives the first line of input and if so what makes this the case rather than "b" receiving it ? Or do things need to be slightly more complicated to achieve this ? Sorry it's just the engineer in me. I think once I've got this clear I'll be happy to move on. Jon

In your example a and b will be ordered as you would expect.
On Wed, Apr 15, 2015 at 9:26 AM, Jon Schneider
Perhaps I need to be more specific.
main = do a <- getLine b <- getLine
Can we say "a" absolutely always receives the first line of input and if so what makes this the case rather than "b" receiving it ? Or do things need to be slightly more complicated to achieve this ?
Sorry it's just the engineer in me. I think once I've got this clear I'll be happy to move on.
Jon
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

And this is because the implementation of IO is *specifically* crafted to guarantee this ordering. It is not a property of monads in general, or do syntax in general.
On 15 April 2015 11:31:38 pm AEST, Ryan Yates
In your example a and b will be ordered as you would expect.
On Wed, Apr 15, 2015 at 9:26 AM, Jon Schneider
wrote: Perhaps I need to be more specific.
main = do a <- getLine b <- getLine
Can we say "a" absolutely always receives the first line of input and if so what makes this the case rather than "b" receiving it ? Or do things need to be slightly more complicated to achieve this ?
Sorry it's just the engineer in me. I think once I've got this clear I'll be happy to move on.
Jon
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
------------------------------------------------------------------------
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

And this is because the implementation of IO is *specifically* crafted to guarantee this ordering. It is not a property of monads in general, or do syntax in general.
Yes, this is an important point. My "as you would expect" was pointed at the IO part of Jon's example, not the monad part :D. Thanks for clarifying.

And this is because the implementation of IO is *specifically* crafted to guarantee this ordering. It is not a property of monads in general, or do syntax in general.
Is it? The example main = do a <- getLine b <- getLine let c = foo a b -- I guess you'd want to do something about a and b eventually isn't really representative of monads, as it could be done just as well with the applicative functor interface (and apparently there are plans for GHC 7.12 to figure it out on its own). Applicative instance for IO indeed does order effects left to right, so this could be used as an example of "specific crafting". Changing it to, let's say main = do a <- getLine b <- getLine c <- foo a b makes it obvious there's no way to evaluate c before a and b, whatever monad that would be, as foo may c can change the shape of the monad anyway it pleases. For example if the monad in question was Maybe, there would be no way to tell whether foo returns Just or Nothing without actually evaluating it. (a and b could still be reordered, but again, this is a feature of an applicative functor, which all monads must derive from, but not of the monadic interface as of itself) Best regards, Marcin Mrotek

On Wed, 15 Apr 2015 17:34:50 +0200, Marcin Mrotek
Changing it to, let's say
main = do a <- getLine b <- getLine c <- foo a b
makes it obvious there's no way to evaluate c before a and b, whatever monad that would be, as foo may c can change the shape of the monad anyway it pleases.
import Debug.Trace foo _ _ = return () main = do a <- trace "a" <$> getLine b <- trace "b" <$> getLine c <- trace "c" <$> foo a b print c Running this program: first input second input c () So as you can see, ‘a’ and ‘b’ never get evaluated.

Sorry, I got it wrong. I should have said "there's no way to evaluate c without evaluating getline twice (<=> evaluating the constructor of the monad type, but not necessarily any further) ", but I guess this is what Jon Schneider meant by:
Can we say "a" absolutely always receives the first line of input and if so what makes this the case rather than "b" receiving it ?
Best regards, Marcin Mrotek

Hi Jon,
On 15 Apr 2015, at 14:26, Jon Schneider
wrote: Perhaps I need to be more specific.
main = do a <- getLine b <- getLine
Can we say "a" absolutely always receives the first line of input and if so what makes this the case rather than "b" receiving it ? Or do things need to be slightly more complicated to achieve this ?
No, that is the case. The IO monad acts like a state monad under the hood, and getLine changes that "IO state", to one in which the next line has just been read in. So the contents of 'b' will be line that was read immediately after the line read leading to the contents of 'b'
Sorry it's just the engineer in me. I think once I've got this clear I'll be happy to move on.
I'm an engineer too - know the feeling. But, imaging a pure function f that does something with strings, and which can fail badly (unhandled runtime exception) if the string is ill-formed. Now consider main = do c <- fmap f $ getLine d <- getLine .... something involving c .... Now, if the first getLine returns an ill-formed string, laziness may mean that the second getLine occurs, and we see the program crash with a runtime error in the evaluation of c after two getLines. In effect the evaluation of f is deferred until it is needed in the 3rd line... Hope this helps!
Jon
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
Andrew Butterfield School of Computer Science & Statistics Trinity College Dublin 2, Ireland

Let's just have a look at the monad instance of IO which is defined in the files ghc-prim/GHC/Types.hs and base/GHC/Base.hs newtype IO a = IO (State# RealWorld -> (# State# RealWorld, a #)) instance Monad IO where ... (>>=) = bindIO ... bindIO :: IO a -> (a -> IO b) -> IO b bindIO (IO m) k = IO $ \ s -> case m s of (# new_s, a #) -> unIO (k a) If you can forget for a minute about all the # you will end up with this. newtype IO a = IO (RealWorld -> (RealWorld, a)) bindIO (IO m) k = IO $ \ s -> case m s of (new_s, a) -> unIO (k a) when the following part is evaluated: case m s of (new_s, a) -> unIO (k a) (m s) has to be evaluated first in order to ensure that the result matches the pattern (new_s, a) and is not bottom/some infinite calculation/an error. This is why IO statements are evaluated in order. Silvio

I think this is the thing under the bonnet I was after though to be perfectly honest is slightly beyond me at the time of writing. Thank you all. Jon
Let's just have a look at the monad instance of IO which is defined in the files ghc-prim/GHC/Types.hs and base/GHC/Base.hs
newtype IO a = IO (State# RealWorld -> (# State# RealWorld, a #))
instance Monad IO where ... (>>=) = bindIO ...
bindIO :: IO a -> (a -> IO b) -> IO b bindIO (IO m) k = IO $ \ s -> case m s of (# new_s, a #) -> unIO (k a)
If you can forget for a minute about all the # you will end up with this.
newtype IO a = IO (RealWorld -> (RealWorld, a))
bindIO (IO m) k = IO $ \ s -> case m s of (new_s, a) -> unIO (k a)
when the following part is evaluated:
case m s of (new_s, a) -> unIO (k a)
(m s) has to be evaluated first in order to ensure that the result matches the pattern (new_s, a) and is not bottom/some infinite calculation/an error.
This is why IO statements are evaluated in order.
Silvio _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

Others have already discussed this in terms of GHC's model of IO, but as Tom Ellis indicates, this model is a bit screwy, and not really the best way to think about it. I think it is much more useful to think of it in terms of a "free monad". That is, think about the `IO` type as a *data structure*. An `IO a` value is a sort of recipe for producing a value of type `a`. That is, data IO :: * -> * where ReturnIO :: a -> IO a BindIO :: IO a -> (a -> IO b) -> IO b HPutStr :: Handle -> String -> IO () HGetStr :: Handle -> IO String .... And then think about the runtime system as an interpreter whose job is to run the programs represented by these IO values. Perhaps I need to be more specific. main = do a <- getLine b <- getLine Can we say "a" absolutely always receives the first line of input and if so what makes this the case rather than "b" receiving it ? Or do things need to be slightly more complicated to achieve this ? Sorry it's just the engineer in me. I think once I've got this clear I'll be happy to move on. Jon _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

Simon PJ's "Tackling the awkward squad" has an excellent (and highly
readable) account of IO, if you want a more precise treatment. (It also
covers concurrency, exceptions, and FFI to a degree.)
http://research.microsoft.com/en-us/um/people/simonpj/papers/marktoberdorf/
It's hard to choose a favorite amongst Simon's writings, but this one
stands out in my opinion in its lucidity, and how clear it makes these
"awkward" parts of Haskell, without giving up any rigor.
-Levent.
On Thu, Apr 16, 2015 at 6:06 PM, David Feuer
Others have already discussed this in terms of GHC's model of IO, but as Tom Ellis indicates, this model is a bit screwy, and not really the best way to think about it. I think it is much more useful to think of it in terms of a "free monad". That is, think about the `IO` type as a *data structure*. An `IO a` value is a sort of recipe for producing a value of type `a`. That is,
data IO :: * -> * where ReturnIO :: a -> IO a BindIO :: IO a -> (a -> IO b) -> IO b HPutStr :: Handle -> String -> IO () HGetStr :: Handle -> IO String ....
And then think about the runtime system as an interpreter whose job is to run the programs represented by these IO values. Perhaps I need to be more specific.
main = do a <- getLine b <- getLine
Can we say "a" absolutely always receives the first line of input and if so what makes this the case rather than "b" receiving it ? Or do things need to be slightly more complicated to achieve this ?
Sorry it's just the engineer in me. I think once I've got this clear I'll be happy to move on.
Jon
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

On Wed, Apr 15, 2015 at 3:06 PM, silvio
Now you can use that to implement your monads. For the state monad for instance there is a strict and a "lazy" version.
newtype State s a = State { runState :: s -> (a,s) }
instance Monad (State s) where act1 >>= f2 = State $ \s1 -> runState (f2 input2) s2 where (input2, s2) = runState act1 s1
instance Monad (State s) where act1 >>= f2 = State $ \s1 -> s2 `seq` runState (f2 input2) s2 where (input2, s2) = runState act1 s1
Note that these do not correspond to the Strict and Lazy State in transformers. The former (which you call lazy) corresponds to Strict from transformers. The lazier version uses lazy pattern matching in bind. Erik

Note that these do not correspond to the Strict and Lazy State in transformers. The former (which you call lazy) corresponds to Strict from transformers. The lazier version uses lazy pattern matching in bind.
I knew I was going to make a mistake somewhere :). The problem is they are transformers and i wanted an example without transformers to confuse the issue So what would be a correct lazy version?? instance Monad (State s) where act1 >>= f2 = State $ \s1 -> runState (f2 (fst res)) (snd res) where res = runState act1 s1 instance Monad (State s) where act1 >>= f2 = State $ \s1 -> runState (f2 input2) s2 where ~(input2, s2) = runState act1 s1 These should do the same right? Silvio

Hi Jon, On Wed, Apr 15, 2015 at 10:07:24AM +0100, Jon Schneider wrote:
With lazy evaluation where is it written that if you write things with no dependencies with a "do" things will be done in order ? Or isn't it ?
I'm not sure where this is written, but it's certainly a property of the IO type. In the expression do x1 <- action1 x2 <- action2 ... then the IO action of the expression `action1` will occur before that of `action2`. (As a caveat, one has to be careful about the concept of "when an action occurs". If `action1` involved reading a file lazily with `System.IO.readFile`[1], say, then the actual read may not take place until `action2` has already finished. However, from the point of view behaviour we consider "observable", a lazy read is indistinguishable from a strict read. Lazy IO is rather counterintuitive. I suggest you stay away from it!) As a side point, appeals to the "real world" in attempts to explain this are probably unhelpful at best. GHC may well implement IO using a fake value of type `RealWorld` but that's beside the point. A conforming Haskell implementation is free to implement IO however it sees fit.
Is it a feature of the language we're supposed to accept ?
Sort of. It's a property of the IO type.
Is it something in the implementation of IO ?
Yes.
Is the do keyword more than just a syntactic sugar for a string of binds and lambdas ?
No. Tom [1] http://hackage.haskell.org/package/base-4.8.0.0/docs/System-IO.html#v:readFi...

Just for the record, lazy IO uses black magic called unsafeInterleaveIO under the hood, which, as the name suggests, deliberately interferes with the execution order imposed by binds.
Best regards,
Marcin Mrotek
-----Wiadomość oryginalna-----
Od: "Tom Ellis"
With lazy evaluation where is it written that if you write things with no dependencies with a "do" things will be done in order ? Or isn't it ?
I'm not sure where this is written, but it's certainly a property of the IO type. In the expression do x1 <- action1 x2 <- action2 ... then the IO action of the expression `action1` will occur before that of `action2`. (As a caveat, one has to be careful about the concept of "when an action occurs". If `action1` involved reading a file lazily with `System.IO.readFile`[1], say, then the actual read may not take place until `action2` has already finished. However, from the point of view behaviour we consider "observable", a lazy read is indistinguishable from a strict read. Lazy IO is rather counterintuitive. I suggest you stay away from it!) As a side point, appeals to the "real world" in attempts to explain this are probably unhelpful at best. GHC may well implement IO using a fake value of type `RealWorld` but that's beside the point. A conforming Haskell implementation is free to implement IO however it sees fit.
Is it a feature of the language we're supposed to accept ?
Sort of. It's a property of the IO type.
Is it something in the implementation of IO ?
Yes.
Is the do keyword more than just a syntactic sugar for a string of binds and lambdas ?
No. Tom [1] http://hackage.haskell.org/package/base-4.8.0.0/docs/System-IO.html#v:readFi... _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

Jon Schneider wrote:
Good morning all,
I think I've got the hang of the way state is carried and fancy operators work in monads but still have a major sticky issue.
With lazy evaluation where is it written that if you write things with no dependencies with a "do" things will be done in order ? Or isn't it ?
Is it a feature of the language we're supposed to accept ?
Is it something in the implementation of IO ?
Is the do keyword more than just a syntactic sugar for a string of binds and lambdas ?
You have to distinguish between *evaluation order*, which dictates how a Haskell expression is evaluated, and something I'd like to call *execution order*, which specifies how the IO monad works. The point is that the latter is very much independent of the former. Evaluating the expression `getLine :: IO String` and "executing" the expression `getLine :: IO String` are two entirely different things. I recommend the tutorial Simon Peyton Jones. "Tackling the awkward squad: monadic input/output, concurrency, exceptions, and foreign-language calls in Haskell" http://research.microsoft.com/en-us/um/people/simonpj/papers/marktoberdorf/ for more on this. Best regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

On 2015-04-15 05:07 AM, Jon Schneider wrote:
With lazy evaluation where is it written that if you write things with no dependencies with a "do" things will be done in order ? Or isn't it ?
Is it a feature of the language we're supposed to accept ?
It is an axiomatic feature. It is unfortunately that the Haskell Report is only half-explicit on this. But here it goes. In Chapter 7, opening: "The order of evaluation of expressions in Haskell is constrained only by data dependencies; an implementation has a great deal of freedom in choosing this order. Actions, however, must be ordered in a well-defined manner for program execution – and I/O in particular – to be meaningful. Haskell’s I/O monad provides the user with a way to specify the sequential chaining of actions, and an implementation is obliged to preserve this order." It does not say clearly how you specify an order, but it is going to be the >>= operator. For example, main = getLine >>= \_ -> putStrLn "bye" specifies to stall for your input, and then, to tell you "bye". In that order. (Perform an experiment to confirm or refute it!) * It stalls for your input, even if your input is not needed. * It tells you "bye", even if you don't need to hear it. * And it stalls for your input before outputting, not the other way round. There is no laziness or optimizer re-ordering for this. "An implementation is obliged to preserve the order." In the rest of Chapter 7, several I/O actions from the library are described. A few are decribed as "read lazily" --- these are in fact the odd men out who postpone inputting, not the common case. The common case, where it does not say "read lazily", is to grab input here-and-now and produce output here-and-now. Lastly, throughout the Haskell Report, apart from the few I/O actions that "read lazily", there is no other laziness specified. That is, lazy evaluation is *not* specified. "An implementation has a great deal of freedom in choosing this order."
participants (14)
-
Albert Y. C. Lai
-
Andrew Butterfield
-
Ben
-
David Feuer
-
Erik Hesselink
-
Heinrich Apfelmus
-
Jon Schneider
-
Levent Erkok
-
Marcin Mrotek
-
Niklas Haas
-
Ryan Yates
-
silvio
-
Sylvain Henry
-
Tom Ellis