
This is just my view on whether Haskell is pure, being offered up for criticism. I haven't seen this view explicitly articulated anywhere before, but it does seem to be implicit in a lot of explanations - in particular the description of Monads in SBCs "Tackling the Awkward Squad". I'm entirely focused on the IO monad here, but aware that it's just one concrete case of an abstraction. Warning - it may look like trolling at various points. Please keep going to the end before making a judgement. To make the context explicit, there are two apparently conflicting viewpoints on Haskell... 1. The whole point of the IO monad is to support programming with side-effecting actions - ie impurity. 2. The IO monad is just a monad - a generic type (IO actions), a couple of operators (primarily return and bind) and some rules - within a pure functional language. You can't create impurity by taking a subset of a pure language. My view is that both of these are correct, each from a particular point of view. Furthermore, by essentially the same arguments, C is also both an impure language and a pure one. See what I mean about the trolling thing? I'm actually quite serious about this, though - and by the end I think Haskell advocates will generally approve. First assertion... Haskell is a pure functional language, but only from the compile-time point of view. The compiler manipulates and composes IO actions (among other things). The final resulting IO actions are finally swallowed by unsafePerformIO or returned from main. However, Haskell is an impure side-effecting language from the run-time point of view - when the composed actions are executed. Impurity doesn't magically spring from the ether - it results from the translation by the compiler of IO actions to executable code and the execution of that code. In this sense, IO actions are directly equivalent to the AST nodes in a C compiler. A C compiler can be written in a purely functional way - in principle it's just a pure function that accepts a string (source code) and returns another string (executable code). I'm fudging issues like separate compilation and #include, but all of these can be resolved in principle in a pure functional way. Everything a C compiler does at compile time is therefore, in principle, purely functional. In fact, in the implementation of Haskell compilers, IO actions almost certainly *are* ASTs. Obviously there's some interesting aspects to that such as all the partially evaluated and unevaluated functions. But even a partially evaluated function has a representation within a compiler that can be considered an AST node, and even AST nodes within a C compiler may represent partially evaluated functions. Even the return and bind operators are there within the C compiler in a sense, similar to the do notation in Haskell. Values are converted into actions. Actions are sequenced. Though the more primitive form isn't directly available to the programmer, it could easily be explicitly present within the compiler. What about variables? What about referential transparency? Well, to a compiler writer (and equally for this argument) an identifier is not the same thing as the variable it references. One way to model the situation is that for every function in a C program, all explicit parameters are implicitly within the IO monad. There is one implicit parameter too - a kind of IORef to the whole system memory. Identifiers have values which identify where the variable is within the big implicit IORef. So all the manipulation of identifiers and their reference-like values is purely functional. Actual handling of variables stored within the big implicit IORef is deferred until run-time. So once you accept that there's an implicit big IORef parameter to every function, by the usual definition of referential transparency, C is as transparent as Haskell. The compile-time result of each function is completely determined by its (implicit and explicit) parameters - it's just that that result is typically a way to look up the run-time result within the big IORef later. What's different about Haskell relative to C therefore... 1. The style of the "AST" is different. It still amounts to the same thing in this argument, but the fact that most AST nodes are simply partially-evaluated functions has significant practical consequences, especially with laziness mixed in too. There's a deep connection between the compile-time and run-time models (contrast C++ templates). 2. The IO monad is explicit in Haskell - side-effects are only permitted (even at run-time) where the programmer has explicitly opted to allow them. 3. IORefs are explicit in Haskell - instead of always having one you can have none, one or many. This is relevant to an alternative definition of referential transparency. Politicians aren't considered transparent when they bury the relevant in a mass of the irrelevant, and even pure functions can be considered to lack transparency in that sense. Haskell allows (and encourages) you to focus in on the relevant - to reference an IORef Bool or an IORef Int rather than dealing with an IORef Everything. That last sentence of the third point is my most recent eureka - not so long ago I posted a "Haskell is just using misleading definitions - it's no more transparent than C" rant, possibly on Stack Overflow. Wrong again :-( So - what do you think?

Le Wed, 28 Dec 2011 17:39:52 +0000,
Steve Horne
This is just my view on whether Haskell is pure, being offered up for criticism. I haven't seen this view explicitly articulated anywhere before, but it does seem to be implicit in a lot of explanations - in particular the description of Monads in SBCs "Tackling the Awkward Squad". I'm entirely focused on the IO monad here, but aware that it's just one concrete case of an abstraction.
Warning - it may look like trolling at various points. Please keep going to the end before making a judgement.
It is not yet a troll for me as I am a newbie ^^
To make the context explicit, there are two apparently conflicting viewpoints on Haskell...
1. The whole point of the IO monad is to support programming with side-effecting actions - ie impurity. 2. The IO monad is just a monad - a generic type (IO actions), a couple of operators (primarily return and bind) and some rules - within a pure functional language. You can't create impurity by taking a subset of a pure language.
My view is that both of these are correct, each from a particular point of view. Furthermore, by essentially the same arguments, C is also both an impure language and a pure one.
See what I mean about the trolling thing? I'm actually quite serious about this, though - and by the end I think Haskell advocates will generally approve.
First assertion... Haskell is a pure functional language, but only from the compile-time point of view. The compiler manipulates and composes IO actions (among other things). The final resulting IO actions are finally swallowed by unsafePerformIO or returned from main. However, Haskell is an impure side-effecting language from the run-time point of view - when the composed actions are executed. Impurity doesn't magically spring from the ether - it results from the translation by the compiler of IO actions to executable code and the execution of that code.
In this sense, IO actions are directly equivalent to the AST nodes in a C compiler. A C compiler can be written in a purely functional way - in principle it's just a pure function that accepts a string (source code) and returns another string (executable code). I'm fudging issues like separate compilation and #include, but all of these can be resolved in principle in a pure functional way. Everything a C compiler does at compile time is therefore, in principle, purely functional.
In fact, in the implementation of Haskell compilers, IO actions almost certainly *are* ASTs. Obviously there's some interesting aspects to that such as all the partially evaluated and unevaluated functions. But even a partially evaluated function has a representation within a compiler that can be considered an AST node, and even AST nodes within a C compiler may represent partially evaluated functions.
Even the return and bind operators are there within the C compiler in a sense, similar to the do notation in Haskell. Values are converted into actions. Actions are sequenced. Though the more primitive form isn't directly available to the programmer, it could easily be explicitly present within the compiler.
What about variables? What about referential transparency?
Well, to a compiler writer (and equally for this argument) an identifier is not the same thing as the variable it references.
One way to model the situation is that for every function in a C program, all explicit parameters are implicitly within the IO monad. There is one implicit parameter too - a kind of IORef to the whole system memory. Identifiers have values which identify where the variable is within the big implicit IORef. So all the manipulation of identifiers and their reference-like values is purely functional. Actual handling of variables stored within the big implicit IORef is deferred until run-time.
So once you accept that there's an implicit big IORef parameter to every function, by the usual definition of referential transparency, C is as transparent as Haskell. The compile-time result of each function is completely determined by its (implicit and explicit) parameters - it's just that that result is typically a way to look up the run-time result within the big IORef later.
Now as you ask here is my point of view: IO monad doesn't make the language impure for me, since you can give another implementation which is perfectly pure and which has the same behaviour (although completely unrealistic): -- An alternative to IO monad data IO_ = IO_ { systemFile :: String -> String -- ^ get the contents of the file , handlers :: Handler -> (Int, String) -- ^ get the offset of the handler } type IO a = IO { trans :: IO_ -> (a, IO_) } instance Monad IO where bind m f = IO { trans = \io1 -> let (a, io2) = trans m io1 in trans (f a) io2 } return a = IO { trans = \io_ -> (a, io_) } -- An example: hGetChar hGetChar :: Handler -> IO Char hGetChar h = IO { trans = \io_ -> let (pos, file) = handlers io_ h c = (systemFile file) !! pos newHandlers = \k -> if h==k then (1+pos, file) else handlers io_ k in (c, IO_ {systemFile = systemFile io_ ,handlers = newHandlers}) } Now how would this work? In a first time, you load all your system file before running the program (a "side-effect" which does not modify already used structures; it is just initialization), then you run the program in a perfectly pure way, and at the end you commit all to the system file (so you modify structures the running program won't access as it has terminated). I am too lazy (like many Haskellers) to show how to implement the other IO functions; but if you believe me you can do it, you can see that I haven't done any side effect. Now the "main" function has type: IO (), that is it is an encapsulated function of type : IO_ -> ((), IO_); in other words, simply an environment transformation. main really is a pure function. It is quite different from C, as in Haskell you need to provide the environment in which it is executed (stored in the type IO_); in C, it is not the case "read(5/*file descriptor, that is an int which cannot contain an environment*/, buff/*buffer (int*), cannot contain an environment*/, len/*size (int) to be read, cannot contain an environment*/); /*return type: void, cannot contain an environment*/" but this expression modifies an environment, which is the side effect. To make C pure, we need to say that all function calls are implicitly given an environment, but in C we have no way to expose this environment, and the typing system doesn't tell us if the call of the function only access or also modifies the environment. In haskell, the environment is explicitely passed to each function (although the 'do' notations tends to hide it, but it is only syntactic sugar), so by reading the signature and unfolding all "data/type/newtype" definitions, we can tell if there is or not side effect; for C, we must unfold 'terms' to understand that. In Haskell, 'hGetChar h >>= \c -> hPutChar i' always has the same value, but 'trans (hGetChar h >>= \c -> hPutChar i) (IO_ A)' 'trans (hGetChar h >>= \c -> hPutChar i) (IO_ B)' may have different values according to A and B. In C, you cannot express this distinction, since you only have: 'read(h, &c, 1); write(i, &c, 1);' and cannot pass explicitely the environment. As you can see my point of view is really different, as I do not think in the "AST way" (even if I have always heard of it, and think it is another good way to think of the monads; in fact the 2 point of view are the same for me, but express differently).
What's different about Haskell relative to C therefore...
1. The style of the "AST" is different. It still amounts to the same thing in this argument, but the fact that most AST nodes are simply partially-evaluated functions has significant practical consequences, especially with laziness mixed in too. There's a deep connection between the compile-time and run-time models (contrast C++ templates). 2. The IO monad is explicit in Haskell - side-effects are only permitted (even at run-time) where the programmer has explicitly opted to allow them. 3. IORefs are explicit in Haskell - instead of always having one you can have none, one or many. This is relevant to an alternative definition of referential transparency. Politicians aren't considered transparent when they bury the relevant in a mass of the irrelevant, and even pure functions can be considered to lack transparency in that sense. Haskell allows (and encourages) you to focus in on the relevant - to reference an IORef Bool or an IORef Int rather than dealing with an IORef Everything.
That last sentence of the third point is my most recent eureka - not so long ago I posted a "Haskell is just using misleading definitions - it's no more transparent than C" rant, possibly on Stack Overflow. Wrong again :-(
So - what do you think?
my 2 cents NB. I encountered a situation where my vision of things was broken: hGetContents :: Handle -> IO ByteString in Data.ByteString.Lazy as BS The following two programs BS.hGetContents h >>= \b -> close h >> let x = BS.length b in print x -- ^ Dangerous, never do it! BS.hGetContents h >>= \b -> let x = BS.length b in close h >> print x -- ^ The right way to do is a problem for me, as BS.length doesn't receive an environment as a parameter, so as they are given the SAME b, they should give the same result. (For me all BS.ByteString operations should be done inside a Monad; the non-lazy ByteString doesn't have this problem of course)

Sorry for the delay. I've written a couple of long replies already, and both times when I'd finished deleting all the stupid stuff there was nothing left - it seems I'm so focussed on my own view, I'm struggling with anything else today. Maybe a third try... On 28/12/2011 19:38, AUGER Cédric wrote:
Le Wed, 28 Dec 2011 17:39:52 +0000, Steve Horne
a écrit : This is just my view on whether Haskell is pure, being offered up for criticism. I haven't seen this view explicitly articulated anywhere before, but it does seem to be implicit in a lot of explanations - in particular the description of Monads in SBCs "Tackling the Awkward Squad". I'm entirely focused on the IO monad here, but aware that it's just one concrete case of an abstraction.
IO monad doesn't make the language impure for me, since you can give another implementation which is perfectly pure and which has the same behaviour (although completely unrealistic):
Now how would this work? In a first time, you load all your system file before running the program (a "side-effect" which does not modify already used structures; it is just initialization), then you run the program in a perfectly pure way, and at the end you commit all to the system file (so you modify structures the running program won't access as it has terminated). I don't see how interactivity fits that model. If a user provides input in response to an on-screen prompt, you can't do all the input at the start (before the prompt is delayed) and you can't do all the output at the end.
Other than that, I'm OK with that. In fact if you're writing a compiler that way, it seems fine - you can certainly delay output of the generated object code until the end of the compilation, and the input done at the start of the compilation (source files) is separate from the run-time prompt-and-user-input thing. See - I told you I'm having trouble seeing things in terms of someone elses model - I'm back to my current obsession again here.
In Haskell, 'hGetChar h>>= \c -> hPutChar i' always has the same value, but 'trans (hGetChar h>>= \c -> hPutChar i) (IO_ A)' 'trans (hGetChar h>>= \c -> hPutChar i) (IO_ B)' may have different values according to A and B.
In C, you cannot express this distinction, since you only have: 'read(h,&c, 1); write(i,&c, 1);' and cannot pass explicitely the environment. Agreed. Haskell is definitely more powerful in that sense.

Le Thu, 29 Dec 2011 01:03:34 +0000,
Steve Horne
Sorry for the delay. I've written a couple of long replies already, and both times when I'd finished deleting all the stupid stuff there was nothing left - it seems I'm so focussed on my own view, I'm struggling with anything else today. Maybe a third try...
On 28/12/2011 19:38, AUGER Cédric wrote:
Le Wed, 28 Dec 2011 17:39:52 +0000, Steve Horne
a écrit : This is just my view on whether Haskell is pure, being offered up for criticism. I haven't seen this view explicitly articulated anywhere before, but it does seem to be implicit in a lot of explanations - in particular the description of Monads in SBCs "Tackling the Awkward Squad". I'm entirely focused on the IO monad here, but aware that it's just one concrete case of an abstraction.
IO monad doesn't make the language impure for me, since you can give another implementation which is perfectly pure and which has the same behaviour (although completely unrealistic):
Now how would this work? In a first time, you load all your system file before running the program (a "side-effect" which does not modify already used structures; it is just initialization), then you run the program in a perfectly pure way, and at the end you commit all to the system file (so you modify structures the running program won't access as it has terminated). I don't see how interactivity fits that model. If a user provides input in response to an on-screen prompt, you can't do all the input at the start (before the prompt is delayed) and you can't do all the output at the end.
Yes and no, in fact you can think of interactivity as a component of the environment (you can also tell that "stdin" is the file of what will be input) and the IO system as causality guardness (ie, you are not allowed to pick an input before prompting the query).
Other than that, I'm OK with that. In fact if you're writing a compiler that way, it seems fine - you can certainly delay output of the generated object code until the end of the compilation, and the input done at the start of the compilation (source files) is separate from the run-time prompt-and-user-input thing.
See - I told you I'm having trouble seeing things in terms of someone elses model - I'm back to my current obsession again here.
In Haskell, 'hGetChar h>>= \c -> hPutChar i' always has the same value, but 'trans (hGetChar h>>= \c -> hPutChar i) (IO_ A)' 'trans (hGetChar h>>= \c -> hPutChar i) (IO_ B)' may have different values according to A and B.
In C, you cannot express this distinction, since you only have: 'read(h,&c, 1); write(i,&c, 1);' and cannot pass explicitely the environment. Agreed. Haskell is definitely more powerful in that sense.
There have been a lot of answers in this thread, but I didn't see one about what I posted: I encountered a situation where my vision of things was broken: hGetContents :: Handle -> IO ByteString in Data.ByteString.Lazy as BS The following two programs BS.hGetContents h >>= \b -> close h >> let x = BS.length b in print x -- ^ Dangerous, never do it! BS.hGetContents h >>= \b -> let x = BS.length b in close h >> print x -- ^ The right way to do is a problem for me, as BS.length doesn't receive an environment as a parameter, so as they are given the SAME b, they should give the same result. (For me all BS.ByteString operations should be done inside a Monad; the non-lazy ByteString doesn't have this problem of course) *** In fact I am not sure there will be a problem with the "BS.length", but I had one in a very similar situation, for me the referential transparency was broken. How to interpret that? Is it some ugly thing to keep compliant with the non Lazy? Is it perfectly ok with the semantics, but I misunderstand the semantics? Is it some inconsistency nobody thought of? (although I have seen some very similar comment in this thread)

Steve Horne wrote:
This is just my view on whether Haskell is pure, being offered up for criticism. I haven't seen this view explicitly articulated anywhere before, but it does seem to be implicit in a lot of explanations - in particular the description of Monads in SBCs "Tackling the Awkward Squad". I'm entirely focused on the IO monad here, but aware that it's just one concrete case of an abstraction.
Warning - it may look like trolling at various points. Please keep going to the end before making a judgement.
To make the context explicit, there are two apparently conflicting viewpoints on Haskell...
1. The whole point of the IO monad is to support programming with side-effecting actions - ie impurity. 2. The IO monad is just a monad - a generic type (IO actions), a couple of operators (primarily return and bind) and some rules - within a pure functional language. You can't create impurity by taking a subset of a pure language.
My view is that both of these are correct, each from a particular point of view. Furthermore, by essentially the same arguments, C is also both an impure language and a pure one. [...]
Purity has nothing to do with the question of whether you can express IO in Haskell or not. The word "purity" refers to the fact that applying a value foo :: Int -> Int (a "function") to another value *always* evaluates to the same result. This is true in Haskell and false in C. The beauty of the IO monad is that it doesn't change anything about purity. Applying the function bar :: Int -> IO Int to the value 2 will always give the same result: bar 2 = bar (1+1) = bar (5-3) Of course, the point is that this result is an *IO action* of type IO Int , it's not the Int you would get "when executing this action". Best regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

On 28/12/2011 20:44, Heinrich Apfelmus wrote:
Steve Horne wrote:
This is just my view on whether Haskell is pure, being offered up for criticism. I haven't seen this view explicitly articulated anywhere before, but it does seem to be implicit in a lot of explanations - in particular the description of Monads in SBCs "Tackling the Awkward Squad". I'm entirely focused on the IO monad here, but aware that it's just one concrete case of an abstraction.
Warning - it may look like trolling at various points. Please keep going to the end before making a judgement.
To make the context explicit, there are two apparently conflicting viewpoints on Haskell...
1. The whole point of the IO monad is to support programming with side-effecting actions - ie impurity. 2. The IO monad is just a monad - a generic type (IO actions), a couple of operators (primarily return and bind) and some rules - within a pure functional language. You can't create impurity by taking a subset of a pure language.
My view is that both of these are correct, each from a particular point of view. Furthermore, by essentially the same arguments, C is also both an impure language and a pure one. [...]
Purity has nothing to do with the question of whether you can express IO in Haskell or not.
...
The beauty of the IO monad is that it doesn't change anything about purity. Applying the function
bar :: Int -> IO Int
to the value 2 will always give the same result:
Yes - AT COMPILE TIME by the principle of referential transparency it
always returns the same action. However, the whole point of that action
is that it might potentially be executed (with potentially
side-effecting results) at run-time. Pure at compile-time, impure at
run-time. What is only modeled at compile-time is realized at run-time,
side-effects included.
Consider the following...
#include

Le 28/12/2011 22:45, Steve Horne a écrit :
Yes - AT COMPILE TIME by the principle of referential transparency it always returns the same action. However, the whole point of that action is that it might potentially be executed (with potentially side-effecting results) at run-time. Pure at compile-time, impure at run-time. What is only modeled at compile-time is realized at run-time, side-effects included. (...)
I hope If convinced you I'm not making one of the standard newbie mistakes. I've done all that elsewhere before, but not today, honest. Sorry, perhaps this is not a standard newbie mistake, but you - apparently - believe that an execution of an action on the "real world" is a side effect.
I don't think it is. Even if a Haskell programme fires an atomic bomb, a very impure one, /*there are no side effects within the programme itself*/. If you disagree, show them. I don't think that speaking about "compile-time purity" is correct. Jerzy Karczmarczuk

On 28/12/2011 22:01, Jerzy Karczmarczuk wrote:
Le 28/12/2011 22:45, Steve Horne a écrit :
Yes - AT COMPILE TIME by the principle of referential transparency it always returns the same action. However, the whole point of that action is that it might potentially be executed (with potentially side-effecting results) at run-time. Pure at compile-time, impure at run-time. What is only modeled at compile-time is realized at run-time, side-effects included. (...)
I hope If convinced you I'm not making one of the standard newbie mistakes. I've done all that elsewhere before, but not today, honest. Sorry, perhaps this is not a standard newbie mistake, but you - apparently - believe that an execution of an action on the "real world" is a side effect.
I don't think it is. Even if a Haskell programme fires an atomic bomb, a very impure one, /*there are no side effects within the programme itself*/. True. But side-effects within the program itself are not the only relevant side-effects.
As Simon Baron-Cohen says in "Tackling the Awkward Squad"... Yet the ultimate purpose of running a program is invariably to cause some side effect: a changed file, some new pixels on the screen, a message sent, or whatever. Indeed it's a bit cheeky to call input/output "awkward" at all. I/O is the raison d'^etre of every program. --- a program that had no observable effect whatsoever (no input, no output) would not be very useful. Of course he then says... Well, if the side effect can't be in the functional program, it will have to be outside it. Well, to me, that's a bit cheeky too - at least if taken overliterally. Even if you consider a mutation of an IORef to occur outside the program, it affects the later run-time behaviour of the program. The same with messages sent to stdout - in this case, the user is a part of the feedback loop, but the supposedly outside-the-program side-effect still potentially affects the future behaviour of the program when it later looks at stdin. A key point of functional programming (including its definitions of side-effects and referential transparency) is about preventing bugs by making code easier to reason about. Saying that the side-effects are outside the program is fine from a compile-time compositing-IO-actions point of view. But as far as understanding the run-time behaviour of the program is concerned, that claim really doesn't change anything. The side-effects still occur, and they still affect the later behaviour of the program. Declaring that they're outside the program doesn't make the behaviour of that program any easier to reason about, and doesn't prevent bugs. A final SBC quote, still from "Tackling the Awkward Squad"... There is a clear distinction, enforced by the type system, between actions which may have side effects, and functions which may not. SBC may consider the side-effects to be outside the program, but he still refers to "actions which may have side-effects". The side-effects are still there, whether you consider them inside or outside the program, and as a programmer you still have to reason about them.

On 28/12/2011 23:56, Bernie Pope wrote:
On 29 December 2011 10:51, Steve Horne
wrote: As Simon Baron-Cohen says in "Tackling the Awkward Squad"... I think you've mixed up your Simons; that should be Simon Peyton Jones.
Oops - sorry about that. FWIW - I'm diagnosed Aspergers. SBC diagnosed me back in 2001, shortly after 9/1/1. Yes, I *am* pedantic - which doesn't always mean right, of course. Not relevant, but what the hell.

We can do functional programming on Java. We use all the design patterns
for that.
At the very end, everything is just some noisy, hairy, side-effectfull,
gotofull machinery code.
The beauty of Haskell is that it allows you to limit the things you need to
reason about. If I see a function with the type "(a, b) -> a" I don't need
to read a man page to see where I should use it or not. I know what it can
do by its type. In C I can not do this. What can I say about a function
"int foo(char* bar)"? Does it allocate memory? Does it asks a number for
the user on stdin? Or does it returns the length of a zero-ending char
sequence? In fact it can do anything, and I can't forbid that. I can't
guarantee that my function has good behaviour. You need to trust the man
page.
Em 28/12/2011 22:24, "Steve Horne"
On 28/12/2011 23:56, Bernie Pope wrote:
On 29 December 2011 10:51, Steve Horne
> wrote: As Simon Baron-Cohen says in "Tackling the Awkward Squad"...
I think you've mixed up your Simons; that should be Simon Peyton Jones.
Oops - sorry about that.
FWIW - I'm diagnosed Aspergers. SBC diagnosed me back in 2001, shortly after 9/1/1.
Yes, I *am* pedantic - which doesn't always mean right, of course.
Not relevant, but what the hell.
______________________________**_________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe

On 29/12/2011 00:57, Thiago Negri wrote:
We can do functional programming on Java. We use all the design patterns for that.
At the very end, everything is just some noisy, hairy, side-effectfull, gotofull machinery code.
The beauty of Haskell is that it allows you to limit the things you need to reason about. If I see a function with the type "(a, b) -> a" I don't need to read a man page to see where I should use it or not. I know what it can do by its type. In C I can not do this. What can I say about a function "int foo(char* bar)"? Does it allocate memory? Does it asks a number for the user on stdin? Or does it returns the length of a zero-ending char sequence? In fact it can do anything, and I can't forbid that. I can't guarantee that my function has good behaviour. You need to trust the man page.
Well, I did say (an unoriginal point) that "The IO monad is explicit in Haskell - side-effects are only permitted (even at run-time) where the programmer has explicitly opted to allow them.". So yes. The "it could do anything!!!" claims are over the top and IMO counterproductive, though. The type system doesn't help the way it does in Haskell, but nevertheless, plenty of people reason about the side-effects in C mostly-successfully. Mostly /= always, but bugs can occur in any language.

On Wed, Dec 28, 2011 at 3:45 PM, Steve Horne
On 28/12/2011 20:44, Heinrich Apfelmus wrote:
Steve Horne wrote:
This is just my view on whether Haskell is pure, being offered up for criticism. I haven't seen this view explicitly articulated anywhere before, but it does seem to be implicit in a lot of explanations - in particular the description of Monads in SBCs "Tackling the Awkward Squad". I'm entirely focused on the IO monad here, but aware that it's just one concrete case of an abstraction.
Warning - it may look like trolling at various points. Please keep going to the end before making a judgement.
To make the context explicit, there are two apparently conflicting viewpoints on Haskell...
1. The whole point of the IO monad is to support programming with side-effecting actions - ie impurity. 2. The IO monad is just a monad - a generic type (IO actions), a couple of operators (primarily return and bind) and some rules - within a pure functional language. You can't create impurity by taking a subset of a pure language.
My view is that both of these are correct, each from a particular point of view. Furthermore, by essentially the same arguments, C is also both an impure language and a pure one. [...]
Purity has nothing to do with the question of whether you can express IO in Haskell or not.
...
The beauty of the IO monad is that it doesn't change anything about purity. Applying the function
bar :: Int -> IO Int
to the value 2 will always give the same result:
Yes - AT COMPILE TIME by the principle of referential transparency it always returns the same action. However, the whole point of that action is that it might potentially be executed (with potentially side-effecting results) at run-time. Pure at compile-time, impure at run-time. What is only modeled at compile-time is realized at run-time, side-effects included.
I don't think I would put it that way - the value 'bar 2' is a regular Haskell value. I can put it in a list, return it from a function and all other things: myIOActions :: [IO Int] myIOActions = [bar 2, bar (1+1), bar (5-3)] And I can pick any of the elements of the list to execute in my main function, and I get the same main function either way.
Consider the following...
#include
int main (int argc, char*argv) { char c; c = getchar (); putchar (c); return 0; }
The identifier c is immutable. We call it a variable, but the compile-time value of c is really just some means to find the actual value in the "big implicit IORef" at runtime - an offset based on the stack pointer or whatever. Nothing mutates until compile-time, and when that happens, the thing that mutates (within that "big implicit IORef") is separate from that compile-time value of c.
In C and in Haskell - the side-effects are real, and occur at run-time.
That doesn't mean Haskell is as bad as C - I get to the advantages of Haskell at the end of my earlier post. Mostly unoriginal, but I think the bit about explicit vs. implicit IORefs WRT an alternate view of transparency is worthwhile.
I hope If convinced you I'm not making one of the standard newbie mistakes. I've done all that elsewhere before, but not today, honest.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 29/12/2011 01:53, Antoine Latter wrote:
The beauty of the IO monad is that it doesn't change anything about purity. Applying the function
bar :: Int -> IO Int
to the value 2 will always give the same result:
Yes - AT COMPILE TIME by the principle of referential transparency it always returns the same action. However, the whole point of that action is that it might potentially be executed (with potentially side-effecting results) at run-time. Pure at compile-time, impure at run-time. What is only modeled at compile-time is realized at run-time, side-effects included.
I don't think I would put it that way - the value 'bar 2' is a regular Haskell value. I can put it in a list, return it from a function and all other things:
myIOActions :: [IO Int] myIOActions = [bar 2, bar (1+1), bar (5-3)]
And I can pick any of the elements of the list to execute in my main function, and I get the same main function either way. Yes - IO actions are first class values in Haskell. They can be derived using all the functional tools of the language. But if this points out a flaw in my logic, it's only a minor issue in my distinction between compile-time and run-time.
Basically, there is a phase when a model has been constructed representing the source code. This model is similar in principle to an AST, though primarily (maybe entirely?) composed of unevaluated functions rather than node-that-represents-whatever structs. This phase *must* be completed during compilation. Of course evaluation of some parts of the model can start before even parsing is complete, but that's just implementation detail. Some reductions (if that's the right term for a single evaluation step) of that model cannot be applied until run-time because of the dependence on run-time inputs. Either the reduction implies the execution of an IO action, or an argument has a data dependency on an IO action. Many reductions can occur either at compile-time or run-time. In your list-of-actions example, the list is not an action itself, but it's presumably a part of the expression defining main which returns an IO action. The evaluation of the expression to select an action may have to be delayed until run-time with the decision being based on run-time input. The function that does the selection is still pure. Even so, this evaluation is part of the potentially side-effecting evaluation and execution of the main IO action. Overall, the run-time execution is impure - a single side-effect is enough. So... compile-time pure, run-time impure.

Steve Horne wrote:
Heinrich Apfelmus wrote:
Purity has nothing to do with the question of whether you can express IO in Haskell or not.
....
The beauty of the IO monad is that it doesn't change anything about purity. Applying the function
bar :: Int -> IO Int
to the value 2 will always give the same result:
Yes - AT COMPILE TIME by the principle of referential transparency it always returns the same action. However, the whole point of that action is that it might potentially be executed (with potentially side-effecting results) at run-time. Pure at compile-time, impure at run-time. What is only modeled at compile-time is realized at run-time, side-effects included.
Well, it's a matter of terminology: "impure" /= "has side effects". The ability of a language to describe side effects is not tied to its (im)purity. Again, purity refers to the semantics of functions (at run-time): given the same argument, will a function always return the same result? The answer to this question solely decides whether the language is pure or impure. Note that this depends on the meaning of "function" within that language. In C, side-effects are part of the semantics of functions, so it's an impure language. In Haskell, on the other hand, functions will always return the same result, so the language is pure. You could say that side effects have been moved from functions to some other type (namely IO) in Haskell. Best regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

Sorry, a long and pseudo-philosophical treatise. Trash it before reading. Heinrich Apfelmus:
You could say that side effects have been moved from functions to some other type (namely IO) in Haskell. I have no reason to be categorical, but I believe that calling the interaction of a Haskell programme with the World - a "side effect" is sinful, and it is a source of semantical trouble.
People do it, SPJ (cited by S. Horne) did it as well, and this is too bad. People, when you eat a sandwich: are you doing "side effects"?? If you break a tooth on it, this IS a side effect, but neither the eating nor digesting it, seems to be one. This term should be used in a way compatible with its original meaning, that something happens implicitly, "behind the curtain", specified most often in an informal way (not always deserving to be called "operational"). If you call all the assignments "side effects", why not call - let x = whatever in Something - also a "local side-effect"? Oh, that you can often transform let in the application of lambda, thus purely functional? Doesn't matter, Steve Horne will explain you that (sorry for the irony): "let is a compile-time pure construct ; at execution this is impure, because x got a value". S.H. admits that he reasons within his model, and has problems with others. Everybody has such problems, but I see here something the (true) Frenchies call "un dialogue de sourds". For me a Haskell programme is ABSOLUTELY pure, including the IO. The issue is that `bind` within the IO monad has an implicit parameter, the World. In fact, a stream of Worlds, every putWhatever, getLine, etc. passes to a new instance. We do not control this World, we call it "imperative" (whatever this means, concerning eating a sandwich, or exploding an impure neutron bomb), so we abuse the term "side effect" as hell! The "Haskell sector" of the global world, the programme itself is just a function. Pure as the robe of an angel. Simply, you are not allowed by the Holy Scripts to look under this robe. == The rest is a (pure of course) délire. Well, you might not believe me, but philosophically you don't need to imagine the World as imperative. Personally I am a believer in the Quantum Religion. If you accept all them Holy Dogmas of Unitarity, of Linearity, etc., if you believe in the True Quantum Nature of the real world, - then it becomes ... functional. Pure. Without a single trace of any "side effects". The problem is that residing inside this world precludes the possibility of considering *observed things* as pure, they are conceptually detached from the stream of the Universe Vectors. They "change", so you say: HaHa!! A particle got ASSIGNED a new position! This is an imperative side-effect! - - while from the point of view of an external observer, a common evolution operator transformed both of you, YOU and the particle into a new instance of this sector. OK, I stop here, otherwise the digestion of your sandwiches may produce some side effects. Jerzy Karczmarczuk Caen, France. (William the Conqueror was here. Produced one nice side-effect.)

On 29/12/2011 10:05, Jerzy Karczmarczuk wrote:
Sorry, a long and pseudo-philosophical treatise. Trash it before reading.
Heinrich Apfelmus:
You could say that side effects have been moved from functions to some other type (namely IO) in Haskell. I have no reason to be categorical, but I believe that calling the interaction of a Haskell programme with the World - a "side effect" is sinful, and it is a source of semantical trouble.
People do it, SPJ (cited by S. Horne) did it as well, and this is too bad. People, when you eat a sandwich: are you doing "side effects"?? If you break a tooth on it, this IS a side effect, but neither the eating nor digesting it, seems to be one.
By definition, an intentional effect is a side-effect. To me, it's by deceptive redefinition - and a lot of arguments rely on mixing definitions - but nonetheless the jargon meaning is correct within programming and has been for decades. It's not going to go away. Basically, the jargon definition was coined by one of the pioneers of function programming - he recognised a problem and needed a simple way to describe it, but in some ways the choice of word is unfortunate. The important thing is to make sure that the explanations you trust aren't based on mixing of the jargon and everyday meanings of "side-effect". In part that's what my original e-mail is about - accepting the definitions of side-effect and referential transparency that are standard within functional programming, eliminating the common non-sequiturs and seeing if functional programming really does still make sense at the end. What would have surprised me when I started this unintentional journey (each step basically being a rant at one functional programming advocate or another) is that actually functional programming in Haskell really does make sense.
This term should be used in a way compatible with its original meaning, that something happens implicitly, "behind the curtain", specified most often in an informal way (not always deserving to be called "operational"). If you call all the assignments "side effects", why not call - let x = whatever in Something - also a "local side-effect"? Oh, that you can often transform let in the application of lambda, thus purely functional?
Doesn't matter, Steve Horne will explain you that (sorry for the irony): "let is a compile-time pure construct ; at execution this is impure, because x got a value".
Well, I was even more absurd than that - in C, I said there were two values (the "reference" and the value referenced) for every variable. Sometimes, eliminating all the subtle contradictions necessarily leads to a much more pedantic world than intuition is happy to deal with.
S.H. admits that he reasons within his model, and has problems with others. Everybody has such problems, but I see here something the (true) Frenchies call "un dialogue de sourds". For me a Haskell programme is ABSOLUTELY pure, including the IO. The issue is that `bind` within the IO monad has an implicit parameter, the World. In fact, a stream of Worlds, every putWhatever, getLine, etc. passes to a new instance.
As I said earlier, a politician who buries the relevant in a huge mass of the irrelevant is not considered transparent. To call this "world" parameter referentially transparent is, to me, argument by deceptive definitions. In any case, the "world" parameter is present in C - it's just implicit. You can translate C to Haskell and visa versa. Both the C and Haskell versions of a correctly translated program will have the same interactions with the world. Therefore there is a mathematical equivalence between Haskell and C. You can argue pedantry, but the pedantry must have a point - a convenient word redefinition will not make your bugs go away. People tried that with "it's not a bug it's a feature" and no-one was impressed.
Simply, you are not allowed by the Holy Scripts to look under this robe.
Ah yes - well that's exactly what I'm trying to do.

On Thu, 2011-12-29 at 18:07 +0000, Steve Horne wrote:
By definition, an intentional effect is a side-effect. To me, it's by deceptive redefinition - and a lot of arguments rely on mixing definitions - but nonetheless the jargon meaning is correct within programming and has been for decades. It's not going to go away.
Basically, the jargon definition was coined by one of the pioneers of function programming - he recognised a problem and needed a simple way to describe it, but in some ways the choice of word is unfortunate.
I don't believe this is true. "Side effect" refers to having a FUNCTION -- that is, a map from input values to output values -- such that when it is evaluated there is some effect in addition to computing the resulting value from that map. The phrase "side effect" refers to a very specific confusion: namely, conflating the performing of effects with computing the values of functions. Haskell has no such things. It's values of IO types are not functions at all, and their effects do not occur as a side effect of evaluating a function. Kleisli arrows in the IO monad -- that is, functions whose result type is an IO type, for example String -> IO () -- are common, yes, but note that even then, the effect still doesn't occur as a side effect of evaluating the function. Evaluating the function just gives you a specific value of the IO type, and performing the effect is still a distinct step that is not the same thing as function evaluation.
You can argue pedantry, but the pedantry must have a point - a convenient word redefinition will not make your bugs go away. People tried that with "it's not a bug it's a feature" and no-one was impressed.
This most certainly has a point. The point is that Haskell being a pure language allows you to reason more fully about Haskell programs using basic language features like functions and variables. Yes, since Haskell is sufficiently powerful, it's possible to build more and more complicated constructs that are again harder to reason about... but even when you do so, you end up using the core Haskell language to talk *about* such constructs... you retain the ability to get your hands on them and discuss them directly and give them names, not mere as side aspects of syntactic forms as they manifest themselves in impure languages. That is the point of what people are saying here (pedantry or not is a matter of your taste); it's directly relevant to day to day programming in Haskell. -- Chris Smith

On 29/12/2011 21:01, Chris Smith wrote:
On Thu, 2011-12-29 at 18:07 +0000, Steve Horne wrote:
By definition, an intentional effect is a side-effect. To me, it's by deceptive redefinition - and a lot of arguments rely on mixing definitions - but nonetheless the jargon meaning is correct within programming and has been for decades. It's not going to go away.
Basically, the jargon definition was coined by one of the pioneers of function programming - he recognised a problem and needed a simple way to describe it, but in some ways the choice of word is unfortunate. I don't believe this is true. "Side effect" refers to having a FUNCTION -- that is, a map from input values to output values -- such that when it is evaluated there is some effect in addition to computing the resulting value from that map. The phrase "side effect" refers to a very specific confusion: namely, conflating the performing of effects with computing the values of functions. Yes - again, by definition that is true. But that definition is not the everyday definition of side-effect. Repeating and explaining one definition doesn't make the other go away.
1. To say that the C printf function has the side-effect of printing to the screen - that's true. 2. To say that the C printf function has no side-effects because it works correctly - the only effects are intentional - that's also true. Two definitions of side-effect. The definition used for case 2 is a lot older than the definition used for case 1, and remains valid. It's the normal usage that most people are familiar with everywhere - not just in programming and computer science. I haven't failed to understand either definition - I simply accept that both are valid. Natural language is ambiguous - sad fact of life. Using similar mixed definitions to conclude that every C program is full of bugs (basically equating intentional effects with side-effects, then equating side-effects with unintentional bugs) is a fairly common thing in my experience, but it's a logical fallacy. If you aren't aware of the two definitions of side-effect, it's hard to get deal with that. Some people don't want anyone to figure out the fallacy - they like having this convenient way to attack C, irrespective of whether it's valid or not. Rare I think - mostly it's more confusion and memetics. But still, I'm convinced there's some sophistry in this. And I'm not the only person to think so, and to have reacted against that in the past. Extra sad - you don't need that fallacy to attack C. It's redundant. C is quite happy to demonstrate its many failings.

On 12/29/2011 11:06 PM, Steve Horne wrote:
On 29/12/2011 21:01, Chris Smith wrote:
On Thu, 2011-12-29 at 18:07 +0000, Steve Horne wrote:
By definition, an intentional effect is a side-effect. To me, it's by deceptive redefinition - and a lot of arguments rely on mixing definitions - but nonetheless the jargon meaning is correct within programming and has been for decades. It's not going to go away.
Basically, the jargon definition was coined by one of the pioneers of function programming - he recognised a problem and needed a simple way to describe it, but in some ways the choice of word is unfortunate. I don't believe this is true. "Side effect" refers to having a FUNCTION -- that is, a map from input values to output values -- such that when it is evaluated there is some effect in addition to computing the resulting value from that map. The phrase "side effect" refers to a very specific confusion: namely, conflating the performing of effects with computing the values of functions. Yes - again, by definition that is true. But that definition is not the everyday definition of side-effect.
Repeating and explaining one definition doesn't make the other go away.
That's what you seem to be doing a lot in this thread. It's very hard to glean what *exactly* you're trying to argue since you seem to be all over the place. (I hope this isn't taken as an insult, it certainly isn't meant as one.) Maybe a summary of your argument + counter-arguments (as you understand them) on a wiki would be helpful? Mail threads with 40+ posts aren't really useful for hashing out this kind of thing.
1. To say that the C printf function has the side-effect of printing to the screen - that's true.
No, it has the "effect" of printing to the screen. When you call printf() you *intend* for it to print something.
2. To say that the C printf function has no side-effects because it works correctly - the only effects are intentional - that's also true.
I realize this is nitpicking, but all of its effects may not be intentional. For example, given certain terminal settings it may also flush the buffer if you have a newline in the argument string. That's a side effect (may be desirable/undesirable). [--snip--]
Using similar mixed definitions to conclude that every C program is full of bugs (basically equating intentional effects with side-effects, then equating side-effects with unintentional bugs) is a fairly common thing in my experience, but it's a logical fallacy. If you aren't aware of the two definitions of side-effect, it's hard to get deal with that.
Some people don't want anyone to figure out the fallacy - they like having this convenient way to attack C, irrespective of whether it's valid or not. Rare I think - mostly it's more confusion and memetics. But still, I'm convinced there's some sophistry in this. And I'm not the only person to think so, and to have reacted against that in the past.
Extra sad - you don't need that fallacy to attack C. It's redundant. C is quite happy to demonstrate its many failings.
That's the flimsiest straw man I've ever seen.

On 30/12/2011 10:47, Bardur Arantsson wrote:
On 12/29/2011 11:06 PM, Steve Horne wrote:
Using similar mixed definitions to conclude that every C program is full of bugs (basically equating intentional effects with side-effects, then equating side-effects with unintentional bugs) is a fairly common thing in my experience, but it's a logical fallacy. If you aren't aware of the two definitions of side-effect, it's hard to get deal with that.
Some people don't want anyone to figure out the fallacy - they like having this convenient way to attack C, irrespective of whether it's valid or not. Rare I think - mostly it's more confusion and memetics. But still, I'm convinced there's some sophistry in this. And I'm not the only person to think so, and to have reacted against that in the past.
Extra sad - you don't need that fallacy to attack C. It's redundant. C is quite happy to demonstrate its many failings.
That's the flimsiest straw man I've ever seen.
Calling it a straw man won't convince anyone who has the scars from being attacked by those "straw men". I've been in those arguments, being told that C has side-effects therefore all C programs are full of bugs, whereas Haskell can't have similar bugs because it doesn't have side-effects. I'm really not interested in whose-side-are-you-on arguments. Trying to keep the two definitions separate is relevant, and that was my motivation for saying this - it's a fact that if you mix your definitions up enough you can "prove" anything. I like C++. I recognise the flaws in C++, as every everyday-user of the language must. Pretending they don't exist doesn't solve the issues - it's for OTT advocates, not developers. I don't insist that every virtuous-sounding term must apply to C++. I don't pretend every C++ advocate is an angel. I like Haskell. I can't claim to be an everyday user, but I'm learning more and using it more all the time. I'm still uncertain whether some flaws I see are real - some that I used to see weren't - but I'll address that over time by thinking and debating. I won't pretend every Haskell advocate is an angel. I've already confessed to being in the anti-Haskell role in arguments where the points I, ahem, emphatically made were (I now recognise) fallacious. So I won't even pretend I'm an angel. If someone who was on the other side in one of my rants makes this same keep-your-definitions-straight point while acting as a C advocate, is that also a straw-man?

On 12/30/2011 10:10 PM, Steve Horne wrote:
On 30/12/2011 10:47, Bardur Arantsson wrote:
On 12/29/2011 11:06 PM, Steve Horne wrote: Calling it a straw man won't convince anyone who has the scars from being attacked by those "straw men".
I've been in those arguments, being told that C has side-effects therefore all C programs are full of bugs, whereas Haskell can't have similar bugs because it doesn't have side-effects. [--snip--]
Please stop or quote someone.
I'm really not interested in whose-side-are-you-on arguments. Trying to keep the two definitions separate is relevant, and that was my motivation for saying this - it's a fact that if you mix your definitions up enough you can "prove" anything.
Yes, and if you throw up enough verbiage or move goalposts enough you (impersonal) can tire anyone. That doesn't prove anything.
I like C++. I recognise the flaws in C++, as every everyday-user of the language must. Pretending they don't exist doesn't solve the issues - it's for OTT advocates, not developers. I don't insist that every virtuous-sounding term must apply to C++. I don't pretend every C++ advocate is an angel.
I dislike C++. There's one reason for that: "Undefined behavior". Haskell still has some of that, but as long as you steer clear of unsafePerformIO, you're mostly good.
I like Haskell. I can't claim to be an everyday user, but I'm learning more and using it more all the time. I'm still uncertain whether some flaws I see are real - some that I used to see weren't - but I'll address that over time by thinking and debating. I won't pretend every Haskell advocate is an angel.
I really don't care if you like or dislike Haskell, nor does anyone else AFAICT. Thinking is good. Debating is also fine as long as you're prepared to listen what people are saying. [--snip--] Conal Elliot was right -- at least about the debate part :) That really *is* my last post on this thread.

On 12/29/2011 07:07 PM, Steve Horne wrote:
On 29/12/2011 10:05, Jerzy Karczmarczuk wrote:
Sorry, a long and pseudo-philosophical treatise. Trash it before reading.
Heinrich Apfelmus:
You could say that side effects have been moved from functions to some other type (namely IO) in Haskell. I have no reason to be categorical, but I believe that calling the interaction of a Haskell programme with the World - a "side effect" is sinful, and it is a source of semantical trouble.
People do it, SPJ (cited by S. Horne) did it as well, and this is too bad. People, when you eat a sandwich: are you doing "side effects"?? If you break a tooth on it, this IS a side effect, but neither the eating nor digesting it, seems to be one.
By definition, an intentional effect is a side-effect. To me, it's by deceptive redefinition - and a lot of arguments rely on mixing definitions - but nonetheless the jargon meaning is correct within programming and has been for decades. It's not going to go away.
This doesn't sound right to me. To me, a "side effect" is something which happens as a (intended or unintended) consequence of something else. An effect which you want to happen (e.g. by calling a procedure, or letting the GHC runtime interpreting an IO Int) is just "an effect".

On 30/12/2011 10:41, Bardur Arantsson wrote:
This doesn't sound right to me. To me, a "side effect" is something which happens as a (intended or unintended) consequence of something else. An effect which you want to happen (e.g. by calling a procedure, or letting the GHC runtime interpreting an IO Int) is just "an effect".
Trouble is, whether it sounds right doesn't really matter - that's just an artifact of the meaning you're most familiar with. Any specialist field has it's own jargon, including old words given new related-but-different meanings.

Quoth Steve Horne
On 30/12/2011 10:41, Bardur Arantsson wrote:
This doesn't sound right to me. To me, a "side effect" is something which happens as a (intended or unintended) consequence of something else. An effect which you want to happen (e.g. by calling a procedure, or letting the GHC runtime interpreting an IO Int) is just "an effect".
Trouble is, whether it sounds right doesn't really matter - that's just an artifact of the meaning you're most familiar with. Any specialist field has it's own jargon, including old words given new related-but-different meanings.
It may help to recall that the point of Haskell is to write computer programs, and by extension the point of discussing its properties and semantics. Mostly we intend to refine our understanding of those properties and semantics; sometimes we may hope to actually improve them by questioning things that haven't been, but perhaps could be, rigorously defined. (That's how I read some of Conal Elliott's recent posts, for example - but of course, it's still a legitimate question: does it matter, if we only want to write programs?) That's why we use terms in a sense that apply meaningfully to computer programming languages in general and Haskell in particular. To do otherwise - for example to insist on a definition of "pure" that could not even in principle apply to any useful programming language, or a definition of "side effect" that would have to apply every time a program does anything - seems to me like an inane waste of time, to put it mildly. Donn

Donn Cave
That's why we use terms in a sense that apply meaningfully to computer programming languages in general and Haskell in particular. To do otherwise - for example to insist on a definition of "pure" that could not even in principle apply to any useful programming language, or a definition of "side effect" that would have to apply every time a program does anything - seems to me like an inane waste of time, to put it mildly.
When one questions accepted definitions or beliefs, it is the sign of their vagueness. To be honest, the definitions of “side effect” and “purity” are vague indeed. I hope that eventually (probably in this very discussion) they will be refined.

On 29/12/2011 08:48, Heinrich Apfelmus wrote:
Steve Horne wrote:
Heinrich Apfelmus wrote:
Purity has nothing to do with the question of whether you can express IO in Haskell or not.
....
The beauty of the IO monad is that it doesn't change anything about purity. Applying the function
bar :: Int -> IO Int
to the value 2 will always give the same result:
Yes - AT COMPILE TIME by the principle of referential transparency it always returns the same action. However, the whole point of that action is that it might potentially be executed (with potentially side-effecting results) at run-time. Pure at compile-time, impure at run-time. What is only modeled at compile-time is realized at run-time, side-effects included.
Well, it's a matter of terminology: "impure" /= "has side effects". The ability of a language to describe side effects is not tied to its (im)purity.
Again, purity refers to the semantics of functions (at run-time): given the same argument, will a function always return the same result? The answer to this question solely decides whether the language is pure or impure. Note that this depends on the meaning of "function" within that language. In C, side-effects are part of the semantics of functions, so it's an impure language. In Haskell, on the other hand, functions will always return the same result, so the language is pure. You could say that side effects have been moved from functions to some other type (namely IO) in Haskell.
WRT the IO monad, "has side effects" is shorthand for "potentially has side effects, and potentially is sensitive to side-effects". Both are equally true - as soon as you opt to allow side-effects you also opt to allow sensitivity to side-effects, at least as far as the type system is concerned. For example an IORef - you can mutate the variable it references, and whenever you dereference it the result depends on whatever past mutations have occurred while the program was running. In a way, it's a shame - it might be interesting to separate causing and reacting to side-effects in the type system (while allowing both to be sequenced relative to each other of course - having I action and O action both subtypes of IO action perhaps). It could be a useful distinction to make in some cases in a preventing-classes-of-bugs-through-typechecking kind of way. The "const" keyword in C++ might be a relevant analogy - disallowing locally-caused mutation of an "IORef" while allowing sensitivity to mutations caused elsewhere. Anyway, if you're using IO actions, your code is not referentially transparent and is therefore impure - by your own definition of "impure". Causing side-effects may not be pedantically the issue, but the mix of causing and reacting to them - ie interacting with the "outside" - clearly means that some of your function results are dependent on what's happening "outside" your program. That includes side-effects "outside" your program yet caused by program program. Again, this is nothing new - it's clear from SPJs "Tackling the Awkward Squad" that this is what the IO monad is meant for, and if it's evil then at least it's controlled evil.

Quoth Steve Horne
Well, it's a matter of terminology: "impure" /= "has side effects". The ability of a language to describe side effects is not tied to its (im)purity.
Again, purity refers to the semantics of functions (at run-time): given the same argument, will a function always return the same result? The answer to this question solely decides whether the language is pure or impure. Note that this depends on the meaning of "function" within that language. In C, side-effects are part of the semantics of functions, so it's an impure language. In Haskell, on the other hand, functions will always return the same result, so the language is pure. You could say that side effects have been moved from functions to some other type (namely IO) in Haskell. ... Anyway, if you're using IO actions, your code is not referentially
On 29/12/2011 08:48, Heinrich Apfelmus wrote: ... transparent and is therefore impure - by your own definition of "impure". Causing side-effects may not be pedantically the issue, but the mix of causing and reacting to them - ie interacting with the "outside" - clearly means that some of your function results are dependent on what's happening "outside" your program. That includes side-effects "outside" your program yet caused by program program.
No, code can be referential transparent and pure and at the same time use IO actions. In order to understand that, you need to untangle the notion you describe above as "function result" from Haskell function value. We can talk endlessly about what your external/execution results might be for some IO action, but at the formulaic level of a Haskell program it's a simple function value, e.g., IO Int.
Again, this is nothing new - it's clear from SPJs "Tackling the Awkward Squad" that this is what the IO monad is meant for, and if it's evil then at least it's controlled evil.
IO is not evil. Donn

Entering tutorial mode here... On Thu, 2011-12-29 at 10:04 -0800, Donn Cave wrote:
We can talk endlessly about what your external/execution results might be for some IO action, but at the formulaic level of a Haskell program it's a simple function value, e.g., IO Int.
Not to nitpick, but I'm unsure what you might mean by "function value" there. An (IO Int) is not a function value: there is no function involved at all. I think the word function is causing some confusion, so I'll avoid calling things functions when they aren't. In answer to the original question, the mental shift that several people are getting at here is this: a value of the type (IO Int) is itself a meaningful thing to get your hands on and manipulate. IO isn't just some annotation you have to throw in to delineate where your non-pure stuff is or something like that; it's a type constructor, and IO types have values, which are just as real and meaningful as any other value in the system. For example, Type: Int Typical Values: 5, or 6, or -11 Type: IO Int Typical Values: (choosing a random number from 1 to 10 with the default random number generator), or (doing nothing and always returning 5), or (writing "hello" to temp.txt in the current working directory and returning the number of bytes written) These are PURE values... they do NOT have side effects. Perhaps they "describe" side effects in a sense, but that's a matter of how you interpret them; it doesn't change the fact that they play the role of ordinary values in Haskell. There are no special evaluation rules for them. Just like with any other type, you might then consider what operations you might want on values of IO types. For example, the operations you might want on Int are addition, multiplication, etc. It turns out that there is one major operation you tend to want on IO types: combine two of them by doing them in turn, where what you do second might depend on the result of what you do first. So we provide that operation on values of IO types... it's just an ordinary function, which happens to go by the name (>>=). That's completely analogous to, say, (+) for Int... it's just a pure function that takes two parameters, and produces a result. Just like (+), if you apply (>>=) to the same two parameters, you'll always get the same value (of an IO type) as a result. Now, of course, behind the scenes we're using these things to describe effectful actions... which is fine! In fact, our entire goal in writing any computer program in any language is *precisely* to describe an effectful action, namely what we'd like to see happen when our program is run. There's nothing wrong with that... when Haskell is described as pure, what is meant by that is that is lets us get our hands on these things directly, manipulate them by using functions to construct more such things, in exactly the same way we'd do with numbers and arithmetic. This is a manifestly different choice from other languages where those basic manipulations even on the simple types are pushed into the more nebulous realm of effectful actions instead. If you wanted to make a more compelling argument that Haskell is not "pure", you should look at termination and exceptions from pure code. This is a far more difficult kind of impurity to explain away: we do it, by introducing a special families of values (one per type) called "bottom" or _|_, but then we also have to introduce some special-purpose rules about functions that operate on that value... an arguably clearer way to understand non-termination is as a side-effect that Haskell does NOT isolate in the type system. But that's for another time. -- Chris Smith

On 29/12/2011 18:41, Chris Smith wrote:
Entering tutorial mode here...
We can talk endlessly about what your external/execution results might be for some IO action, but at the formulaic level of a Haskell program it's a simple function value, e.g., IO Int. Not to nitpick, but I'm unsure what you might mean by "function value"
On Thu, 2011-12-29 at 10:04 -0800, Donn Cave wrote: there. An (IO Int) is not a function value: there is no function involved at all. I think the word function is causing some confusion, so I'll avoid calling things functions when they aren't. Except that it *is* a function value.
These are PURE values... they do NOT have side effects. Perhaps they "describe" side effects in a sense, but that's a matter of how you interpret them; it doesn't change the fact that they play the role of ordinary values in Haskell. There are no special evaluation rules for them. The semantics of the execution of primitive IO actions are part of the Haskell language. The execution isn't pure functional. At compile-time
Basically, a data constructor is a self-referencing function. "Just 1" is a function that returns "Just 1" for instance. According to WinGHCI... Prelude> :type Just Just :: a -> Maybe a Prelude> The IO monad is a black box - we can't see the data constructors - but in principle it's the same thing. The value extracted out of the IO action when it is executed is a different thing, of course. there is no means to evaluate the key functions at all - no way to extract the result out of an IO action because the action cannot be executed and so doesn't (yet) have a result. At run-time, that restriction is removed, or the special evaluation rules are added in - either claim is fine but the effect that Haskell is doing something it couldn't do at compile-time. Yes, *Haskell* is doing it - it's still a part of what the Haskell language defines.

Quoth Steve Horne
On 29/12/2011 18:41, Chris Smith wrote: ...
On Thu, 2011-12-29 at 10:04 -0800, Donn Cave wrote:
We can talk endlessly about what your external/execution results might be for some IO action, but at the formulaic level of a Haskell program it's a simple function value, e.g., IO Int.
Not to nitpick, but I'm unsure what you might mean by "function value" there. An (IO Int) is not a function value: there is no function involved at all. I think the word function is causing some confusion, so I'll avoid calling things functions when they aren't.
Except that it *is* a function value.
He's right, I should have omitted "function", I just meant "value." I think the rest of what came out when he entered "tutorial mode" should be very helpful, if there's anything left that remains to be clarified about how Haskell manages to be a pure functional language. Donn

Anyway, if you're using IO actions, your code is not referentially transparent and is therefore impure - by your own definition of "impure". Causing side-effects may not be pedantically the issue, but the mix of causing and reacting to them - ie interacting with the "outside" - clearly means that some of your function results are dependent on what's happening "outside" your program. That includes side-effects "outside" your program yet caused by program program. No, code can be referential transparent and pure and at the same time use IO actions. In order to understand that, you need to untangle the notion you describe above as "function result" from Haskell function value. We can talk endlessly about what your external/execution results might be for some IO action, but at the formulaic level of a Haskell
Quoth Steve Horne
, ... program it's a simple function value, e.g., IO Int. To me, that only makes sense if you never run the compiled program - if
On 29/12/2011 18:04, Donn Cave wrote: the executable file is just an interesting artifact that you generated using a Haskell "interpreter". In reality, the behaviour of IO actions is part of Haskell. The precise meaning of primitive Haskell IO actions is defined. The effects of compositing to build larger IO actions is defined. The Haskell language and compiler take responsibility for meaning of IO actions. The effect of executing those actions, including the returned values, is absolutely relevant to the behaviour of the program. You can make the argument that "the world" is a parameter. Well - in C, "the world" can be considered an implicit parameter. In any case, this only gives referential transparency by what I'd call deceptive definition. Only a tiny piece of "the world" is relevant to your program. You've buried the relevant in a mass of the irrelevant, very much like a less-than-transparent politician. Your interaction is no more or less likely to have bugs depending on whether you define this as transparent or not - arguing about the definition is besides the point. If a program that causes and is sensitive to side-effects - that interacts with the outside world - is referentially transparent, then referential transparency has no relevant meaning.

Steve Horne wrote:
Heinrich Apfelmus wrote:
Again, purity refers to the semantics of functions (at run-time): given the same argument, will a function always return the same result? The answer to this question solely decides whether the language is pure or impure. Note that this depends on the meaning of "function" within that language. In C, side-effects are part of the semantics of functions, so it's an impure language. In Haskell, on the other hand, functions will always return the same result, so the language is pure. You could say that side effects have been moved from functions to some other type (namely IO) in Haskell.
Anyway, if you're using IO actions, your code is not referentially transparent and is therefore impure - by your own definition of "impure". Causing side-effects may not be pedantically the issue, but the mix of causing and reacting to them - ie interacting with the "outside" - clearly means that some of your function results are dependent on what's happening "outside" your program. That includes side-effects "outside" your program yet caused by program program.
No, that's not my definition of "impure". Also, my Haskell code is referentially transparent even though I'm using IO actions. If this sounds paradoxical, then it's probably worth mulling about some more. Maybe it helps to try to find an example of a function f :: A -> B for some cleverly chosen types A,B that is not pure, i.e. does not return the same values for equal arguments. Chris Smith explains it very eloquently and Donn Cove and Jerzy Karczmarczuk say the same thing. Best regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

On 29/12/2011 19:26, Heinrich Apfelmus wrote:
Steve Horne wrote:
Heinrich Apfelmus wrote:
Again, purity refers to the semantics of functions (at run-time): given the same argument, will a function always return the same result? The answer to this question solely decides whether the language is pure or impure. Note that this depends on the meaning of "function" within that language. In C, side-effects are part of the semantics of functions, so it's an impure language. In Haskell, on the other hand, functions will always return the same result, so the language is pure. You could say that side effects have been moved from functions to some other type (namely IO) in Haskell.
Anyway, if you're using IO actions, your code is not referentially transparent and is therefore impure - by your own definition of "impure". Causing side-effects may not be pedantically the issue, but the mix of causing and reacting to them - ie interacting with the "outside" - clearly means that some of your function results are dependent on what's happening "outside" your program. That includes side-effects "outside" your program yet caused by program program.
No, that's not my definition of "impure". Also, my Haskell code is referentially transparent even though I'm using IO actions. If this sounds paradoxical, then it's probably worth mulling about some more. Maybe it helps to try to find an example of a function f :: A -> B for some cleverly chosen types A,B that is not pure, i.e. does not return the same values for equal arguments. That doesn't prove Haskell pure.
Of course your challenge looks like a safe one. It can't be done because the IO monad is a black box - you can't e.g. pattern-match on it's data constructors. Of course you can extract values out of IO actions to work with them - the bind operator does this for you nicely, providing the value as an argument to the function you pass to the right-hand argument of the bind. But that function returns another IO action anyway - although you've extracted a value out and the value affects a computation, all you can do with it in the long run is return another IO action. Even so, that value can only be extracted out at run-time, after the action is executed. So, consider the following... getAnIntFromTheUser :: IO Int From a pure functional point of view, that should return the same action every time. Well, the partially evaluated getAnIntFromTheUser has the same structure each time - but the actual Int packaged inside the action isn't decided until runtime, when the action is executed. At compile-time, that action can only be partially evaluated - the final value OF THE ACTION depends on what Int the user chooses to give because that Int is a part of the action value. For your specific challenge, place that as a left-hand argument in a bind... f :: Int -> IO Int f = getAnIntFromTheUser >>= \i -> return (i+1) Well, the value of i isn't decidable until runtime. The value of i+1 is not decidable until runtime. The value of return (i+1) is not decidable until runtime and so on. It can only be partially evaluated at compile-time, but when it is fully evaluated, you get a different IO action returned by f depending on what Int you got from the user. And so we get right back to the referential-transparency-by-referencing-the-world-as-an-argument thing, I guess.

Steve Horne wrote:
Heinrich Apfelmus wrote:
Maybe it helps to try to find an example of a function f :: A -> B for some cleverly chosen types A,B that is not pure, i.e. does not return the same values for equal arguments.
[..] For your specific challenge, place that as a left-hand argument in a bind...
f :: Int -> IO Int f = getAnIntFromTheUser >>= \i -> return (i+1)
Well, the value of i isn't decidable until runtime. The value of i+1 is not decidable until runtime. The value of return (i+1) is not decidable until runtime and so on. It can only be partially evaluated at compile-time, but when it is fully evaluated, you get a different IO action returned by f depending on what Int you got from the user.
The function f :: Int -> IO Int f x = getAnIntFromTheUser >>= \i -> return (i+x) is pure according to the common definition of "pure" in the context of purely functional programming. That's because f 42 = f (43-1) = etc. Put differently, the function always returns the same IO action, i.e. the same value (of type IO Int) when given the same parameter. Best regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

On Fri, Dec 30, 2011 at 12:49 AM, Heinrich Apfelmus < apfelmus@quantentunnel.de> wrote:
The function
f :: Int -> IO Int f x = getAnIntFromTheUser >>= \i -> return (i+x)
is pure according to the common definition of "pure" in the context of purely functional programming. That's because
f 42 = f (43-1) = etc.
Put differently, the function always returns the same IO action, i.e. the same value (of type IO Int) when given the same parameter.
Two questions trouble me: How can we know whether this claim is true or not? What does the claim even mean, i.e., what does "the same IO action" mean, considering that we lack a denotational model of IO? - Conal

On Dec 30, 2011, at 10:19 AM, Conal Elliott wrote:
On Fri, Dec 30, 2011 at 12:49 AM, Heinrich Apfelmus
wrote: The function
f :: Int -> IO Int f x = getAnIntFromTheUser >>= \i -> return (i+x)
is pure according to the common definition of "pure" in the context of purely functional programming. That's because
f 42 = f (43-1) = etc.
Put differently, the function always returns the same IO action, i.e. the same value (of type IO Int) when given the same parameter.
Two questions trouble me:
How can we know whether this claim is true or not?
time t: f 42 (computational process implementing func application begins…) t+1: <keystroke> = 1 t+2: 43 (… and ends) time t+3: f 42 t+4: <keystroke> = 2 t+5: 44 Conclusion: f 42 != f 42 (This seems so extraordinarily obvious that maybe Heinrich has something else in mind.) -Gregg

On 30 December 2011 16:59, Gregg Reynolds
On Fri, Dec 30, 2011 at 12:49 AM, Heinrich Apfelmus < apfelmus@quantentunnel.de> wrote:
The function
f :: Int -> IO Int f x = getAnIntFromTheUser >>= \i -> return (i+x)
is pure according to the common definition of "pure" in the context of purely functional programming. That's because
f 42 = f (43-1) = etc.
Put differently, the function always returns the same IO action, i.e. the same value (of type IO Int) when given the same parameter.
time t: f 42 (computational process implementing func application begins…) t+1: <keystroke> = 1 t+2: 43 (… and ends)
time t+3: f 42 t+4: <keystroke> = 2 t+5: 44
Conclusion: f 42 != f 42
(This seems so extraordinarily obvious that maybe Heinrich has something else in mind.)
This seems such an obviously incorrect conclusion.
f42 is a funtion for returning a program for returning an int, not a function for returning an int.

On Dec 30, 2011, at 11:04 AM, Colin Adams wrote:
On 30 December 2011 16:59, Gregg Reynolds
wrote: On Fri, Dec 30, 2011 at 12:49 AM, Heinrich Apfelmus
wrote: The function
f :: Int -> IO Int f x = getAnIntFromTheUser >>= \i -> return (i+x)
is pure according to the common definition of "pure" in the context of purely functional programming. That's because
f 42 = f (43-1) = etc.
Put differently, the function always returns the same IO action, i.e. the same value (of type IO Int) when given the same parameter.
time t: f 42 (computational process implementing func application begins…) t+1: <keystroke> = 1 t+2: 43 (… and ends)
time t+3: f 42 t+4: <keystroke> = 2 t+5: 44
Conclusion: f 42 != f 42
(This seems so extraordinarily obvious that maybe Heinrich has something else in mind.)
This seems such an obviously incorrect conclusion.
f42 is a funtion for returning a program for returning an int, not a function for returning an int.
My conclusion holds: f 42 != f 42. Obviously, so I won't burden you with an explanation. ;) -Gregg

On 30 December 2011 17:17, Gregg Reynolds
On Dec 30, 2011, at 11:04 AM, Colin Adams wrote:
On 30 December 2011 16:59, Gregg Reynolds
wrote: On Fri, Dec 30, 2011 at 12:49 AM, Heinrich Apfelmus < apfelmus@quantentunnel.de> wrote:
The function
f :: Int -> IO Int f x = getAnIntFromTheUser >>= \i -> return (i+x)
is pure according to the common definition of "pure" in the context of purely functional programming. That's because
f 42 = f (43-1) = etc.
Put differently, the function always returns the same IO action, i.e. the same value (of type IO Int) when given the same parameter.
time t: f 42 (computational process implementing func application begins…) t+1: <keystroke> = 1 t+2: 43 (… and ends)
time t+3: f 42 t+4: <keystroke> = 2 t+5: 44
Conclusion: f 42 != f 42
(This seems so extraordinarily obvious that maybe Heinrich has something else in mind.)
This seems such an obviously incorrect conclusion.
f42 is a funtion for returning a program for returning an int, not a function for returning an int.
My conclusion holds: f 42 != f 42. Obviously, so I won't burden you with an explanation. ;)
-Gregg
Your conclusion is clearly erroneous. proof: f is a function, and it is taking the same argument each time. Therefore the result is the same each time.

On Fri, Dec 30, 2011 at 9:20 AM, Colin Adams
On 30 December 2011 17:17, Gregg Reynolds
wrote: On Dec 30, 2011, at 11:04 AM, Colin Adams wrote:
On 30 December 2011 16:59, Gregg Reynolds
wrote: On Fri, Dec 30, 2011 at 12:49 AM, Heinrich Apfelmus < apfelmus@quantentunnel.de> wrote:
The function
f :: Int -> IO Int f x = getAnIntFromTheUser >>= \i -> return (i+x)
is pure according to the common definition of "pure" in the context of purely functional programming. That's because
f 42 = f (43-1) = etc.
Put differently, the function always returns the same IO action, i.e. the same value (of type IO Int) when given the same parameter.
time t: f 42 (computational process implementing func application begins…) t+1: <keystroke> = 1 t+2: 43 (… and ends)
time t+3: f 42 t+4: <keystroke> = 2 t+5: 44
Conclusion: f 42 != f 42
(This seems so extraordinarily obvious that maybe Heinrich has something else in mind.)
This seems such an obviously incorrect conclusion.
f42 is a funtion for returning a program for returning an int, not a function for returning an int.
My conclusion holds: f 42 != f 42. Obviously, so I won't burden you with an explanation. ;)
-Gregg
Your conclusion is clearly erroneous.
proof: f is a function, and it is taking the same argument each time. Therefore the result is the same each time.
Careful of circular reasoning here. Is f actually a "function" in the mathematical sense? It's that math sense that you need to reach your conclusion. BTW, the more I hear words like "clearly" and "obvious", the more I suspect that fuzziness is being swept under the carpet. - Conal

On 30 December 2011 17:27, Conal Elliott
On Fri, Dec 30, 2011 at 9:20 AM, Colin Adams
wrote: proof: f is a function, and it is taking the same argument each time. Therefore the result is the same each time.
Careful of circular reasoning here. Is f actually a "function" in the mathematical sense? It's that math sense that you need to reach your conclusion.
Yes. Because Haskell is a functional programming language.

On Fri, Dec 30, 2011 at 9:30 AM, Colin Adams
On 30 December 2011 17:27, Conal Elliott
wrote: On Fri, Dec 30, 2011 at 9:20 AM, Colin Adams
wrote: proof: f is a function, and it is taking the same argument each time. Therefore the result is the same each time.
Careful of circular reasoning here. Is f actually a "function" in the mathematical sense? It's that math sense that you need to reach your conclusion.
Yes. Because Haskell is a functional programming language.
And how do you know that claim to be true? And do you mean a *purely* functional language? Otherwise f might be in the impure part. If you do mean *purely* functional, aren't you arguing for purity by assuming purity? Moreover, do you have a precise definition for "functional"? I've witnessed a lot of these arguments and have seen a diversity of interpretations. Which is why I recommend shifting away from such fuzzy terms and following Peter Landin's recommended more precise & substantive replacement, namely "denotative". (See http://conal.net/blog/posts/is-haskell-a-purely-functional-language/#comment... a quote and reference.) - Conal

On Dec 30, 2011, at 11:20 AM, Colin Adams wrote:
On 30 December 2011 17:17, Gregg Reynolds
wrote: On Dec 30, 2011, at 11:04 AM, Colin Adams wrote:
On 30 December 2011 16:59, Gregg Reynolds
wrote: On Fri, Dec 30, 2011 at 12:49 AM, Heinrich Apfelmus
wrote: The function
f :: Int -> IO Int f x = getAnIntFromTheUser >>= \i -> return (i+x)
is pure according to the common definition of "pure" in the context of purely functional programming. That's because
f 42 = f (43-1) = etc.
Conclusion: f 42 != f 42
(This seems so extraordinarily obvious that maybe Heinrich has something else in mind.)
This seems such an obviously incorrect conclusion.
f42 is a funtion for returning a program for returning an int, not a function for returning an int.
My conclusion holds: f 42 != f 42. Obviously, so I won't burden you with an explanation. ;)
-Gregg Your conclusion is clearly erroneous.
proof: f is a function, and it is taking the same argument each time. Therefore the result is the same each time.
That's called begging the question. f is not a function, so I guess your proof is flawed. It seems pretty clear that we're working with different ideas of what constitutes a function. When I use the term, I intend what I take to be the standard notion of a function in computation: not just a unique mapping from one input to one output, but one where the output is computable from the input. Any "function" that depends on a non-computable component is by that definition not a true function. For clarity let's call such critters quasi-functions, so we can retain the notion of application. Equality cannot be defined for quasi-functions, for obvious reasons. f is a quasi-function because it depends on getAnIntFromUser, which is not definable and is obviously not a function. When applied to an argument like 42, it yields another quasi-function, and therefore "f 42 = f 42" is false, or at least unknown, and the same goes for f 42 != f 42 I suppose. -Gregg

On Fri, Dec 30, 2011 at 9:43 AM, Gregg Reynolds
On Dec 30, 2011, at 11:20 AM, Colin Adams wrote: On 30 December 2011 17:17, Gregg Reynolds
wrote: On Dec 30, 2011, at 11:04 AM, Colin Adams wrote:
On 30 December 2011 16:59, Gregg Reynolds
wrote: On Fri, Dec 30, 2011 at 12:49 AM, Heinrich Apfelmus <
apfelmus@quantentunnel.de> wrote:
The function
f :: Int -> IO Int f x = getAnIntFromTheUser >>= \i -> return (i+x)
is pure according to the common definition of "pure" in the context of purely functional programming. That's because
f 42 = f (43-1) = etc.
Conclusion: f 42 != f 42
(This seems so extraordinarily obvious that maybe Heinrich has something else in mind.)
This seems such an obviously incorrect conclusion.
f42 is a funtion for returning a program for returning an int, not a function for returning an int.
My conclusion holds: f 42 != f 42. Obviously, so I won't burden you with an explanation. ;)
-Gregg
Your conclusion is clearly erroneous.
proof: f is a function, and it is taking the same argument each time. Therefore the result is the same each time.
That's called begging the question. f is not a function, so I guess your proof is flawed.
It seems pretty clear that we're working with different ideas of what constitutes a function. When I use the term, I intend what I take to be the standard notion of a function in computation: not just a unique mapping from one input to one output, but one where the output is computable from the input. Any "function" that depends on a non-computable component is by that definition not a true function. For clarity let's call such critters quasi-functions, so we can retain the notion of application. Equality cannot be defined for quasi-functions, for obvious reasons.
f is a quasi-function because it depends on getAnIntFromUser, which is not definable and is obviously not a function. When applied to an argument like 42, it yields another quasi-function, and therefore "f 42 = f 42" is false, or at least unknown, and the same goes for f 42 != f 42 I suppose.
-Gregg
Please don't redefine "function" to mean "computable function". Besides distancing yourself from math, I don't think doing so really helps your case. And on what do you base your claim that getAnIntFromUser is not definable? Or that applying it (what?) to 42 gives a quasi-function?

On Fri, Dec 30, 2011 at 9:43 AM, Conal Elliott
On Fri, Dec 30, 2011 at 9:43 AM, Gregg Reynolds
wrote: On Dec 30, 2011, at 11:20 AM, Colin Adams wrote: On 30 December 2011 17:17, Gregg Reynolds
wrote: On Dec 30, 2011, at 11:04 AM, Colin Adams wrote:
On 30 December 2011 16:59, Gregg Reynolds
wrote: On Fri, Dec 30, 2011 at 12:49 AM, Heinrich Apfelmus <
apfelmus@quantentunnel.de> wrote:
The function
f :: Int -> IO Int f x = getAnIntFromTheUser >>= \i -> return (i+x)
is pure according to the common definition of "pure" in the context of purely functional programming. That's because
f 42 = f (43-1) = etc.
Conclusion: f 42 != f 42
(This seems so extraordinarily obvious that maybe Heinrich has something else in mind.)
This seems such an obviously incorrect conclusion.
f42 is a funtion for returning a program for returning an int, not a function for returning an int.
My conclusion holds: f 42 != f 42. Obviously, so I won't burden you with an explanation. ;)
-Gregg
Your conclusion is clearly erroneous.
proof: f is a function, and it is taking the same argument each time. Therefore the result is the same each time.
That's called begging the question. f is not a function, so I guess your proof is flawed.
It seems pretty clear that we're working with different ideas of what constitutes a function. When I use the term, I intend what I take to be the standard notion of a function in computation: not just a unique mapping from one input to one output, but one where the output is computable from the input. Any "function" that depends on a non-computable component is by that definition not a true function. For clarity let's call such critters quasi-functions, so we can retain the notion of application. Equality cannot be defined for quasi-functions, for obvious reasons.
f is a quasi-function because it depends on getAnIntFromUser, which is not definable and is obviously not a function. When applied to an argument like 42, it yields another quasi-function, and therefore "f 42 = f 42" is false, or at least unknown, and the same goes for f 42 != f 42 I suppose.
-Gregg
Please don't redefine "function" to mean "computable function". Besides distancing yourself from math, I don't think doing so really helps your case.
And on what do you base your claim that getAnIntFromUser is not definable? Or that applying it (what?) to 42 gives a quasi-function?
Also: f is not a function, so I guess your proof is flawed.
Can you support the claim that f is not a function?

On Dec 30, 2011, at 11:43 AM, Conal Elliott wrote:
roof: f is a function, and it is taking the same argument each time. Therefore the result is the same each time.
That's called begging the question. f is not a function, so I guess your proof is flawed.
It seems pretty clear that we're working with different ideas of what constitutes a function. When I use the term, I intend what I take to be the standard notion of a function in computation: not just a unique mapping from one input to one output, but one where the output is computable from the input. Any "function" that depends on a non-computable component is by that definition not a true function. For clarity let's call such critters quasi-functions, so we can retain the notion of application. Equality cannot be defined for quasi-functions, for obvious reasons.
f is a quasi-function because it depends on getAnIntFromUser, which is not definable and is obviously not a function. When applied to an argument like 42, it yields another quasi-function, and therefore "f 42 = f 42" is false, or at least unknown, and the same goes for f 42 != f 42 I suppose.
-Gregg
Please don't redefine "function" to mean "computable function". Besides distancing yourself from math, I don't think doing so really helps your case.
No redefinition involved, just a narrowing of scope. I assume that, since we are talking about computation, it is reasonable to limit the discussion to the class of computable functions - which, by the way, are about as deeply embedded in orthodox mathematics as you can get, by way of recursion theory. What would be the point of talking about non-computable functions for the semantics of a programming language?
And on what do you base your claim that getAnIntFromUser is not definable?
Sorry, not definable might a little strong. "Not definable in the way we can define computable functions" work better? In any case I think you probably see what I'm getting at.
Or that applying it (what?) to 42 gives a quasi-function?
I can't think of a way to improve on what I've already written at the moment - it too would depend on IO - so if my meaning is not clear, so be it. Wait, here's another way of looking at it. Think of IO actions as random variables. So instead of getAnIntFromUser, use X as an integer random variable yielding something like: f :: Int -> IO Int f x = X >>= \i -> return (i+x) I would not call this f a function because I don't think it answers to the commonly accepted definition of a function. Ditto for the result of applying it to 42. Others obviously might consider it a function. De gustibus non set disputandem. -Gregg -Gregg

On Fri, Dec 30, 2011 at 10:24 AM, Gregg Reynolds
On Dec 30, 2011, at 11:43 AM, Conal Elliott wrote:
roof: f is a function, and it is taking the same argument each time.
Therefore the result is the same each time.
That's called begging the question. f is not a function, so I guess your proof is flawed.
It seems pretty clear that we're working with different ideas of what constitutes a function. When I use the term, I intend what I take to be the standard notion of a function in computation: not just a unique mapping from one input to one output, but one where the output is computable from the input. Any "function" that depends on a non-computable component is by that definition not a true function. For clarity let's call such critters quasi-functions, so we can retain the notion of application. Equality cannot be defined for quasi-functions, for obvious reasons.
f is a quasi-function because it depends on getAnIntFromUser, which is not definable and is obviously not a function. When applied to an argument like 42, it yields another quasi-function, and therefore "f 42 = f 42" is false, or at least unknown, and the same goes for f 42 != f 42 I suppose.
-Gregg
Please don't redefine "function" to mean "computable function". Besides distancing yourself from math, I don't think doing so really helps your case.
No redefinition involved, just a narrowing of scope. I assume that, since we are talking about computation, it is reasonable to limit the discussion to the class of computable functions - which, by the way, are about as deeply embedded in orthodox mathematics as you can get, by way of recursion theory. What would be the point of talking about non-computable functions for the semantics of a programming language?
And on what do you base your claim that getAnIntFromUser is not definable?
Sorry, not definable might a little strong. "Not definable in the way we can define computable functions" work better? In any case I think you probably see what I'm getting at.
Or that applying it (what?) to 42 gives a quasi-function?
I can't think of a way to improve on what I've already written at the moment - it too would depend on IO - so if my meaning is not clear, so be it.
Wait, here's another way of looking at it. Think of IO actions as random variables. So instead of getAnIntFromUser, use X as an integer random variable yielding something like:
f :: Int -> IO Int f x = X >>= \i -> return (i+x)
I would not call this f a function because I don't think it answers to the commonly accepted definition of a function. Ditto for the result of applying it to 42. Others obviously might consider it a function. De gustibus non set disputandem.
-Gregg
I'm recommending a shift to more well-defined terms in hopes to move this discussion away from tastes & opinions and from what's obvious (even if untrue or ill-defined). If you look at the signature of 'f', you can see that it's declared to be a function (and a computable one at that). To demonstrate that it's not actually a function, I'd expect you to show that it's one-to-many, which then raises the question of equality, as needed to distinguish one from many. - Conal

On Fri, 2011-12-30 at 12:24 -0600, Gregg Reynolds wrote:
No redefinition involved, just a narrowing of scope. I assume that, since we are talking about computation, it is reasonable to limit the discussion to the class of computable functions - which, by the way, are about as deeply embedded in orthodox mathematics as you can get, by way of recursion theory. What would be the point of talking about non-computable functions for the semantics of a programming language?
Computability is just a distraction here. The problem isn't whether "getAnIntFromUser" is computable... it is whether it's a function at all! Even uncomputable functions are first and foremost functions, and not being computable is just a property that they have. Clearly this is not a function at all. It doesn't even have the general form of a function: it has no input, so clearly it can't map each input value to a specific output value. Now, since it's not a function, it makes little sense to even try to talk about whether it is computable or not (unless you first define a notion of computability for something other than functions). If you want to talk about things that read values from the keyboard or such, calling them "uncomputable" is confusing, since the issue isn't really computability at all, but rather needing information from a constantly changing external environment. I suspect that at least some people talking about "functions" are using the word to mean a computational procedure, the sort of thing meant by the C programming language by that word. Uncomputable is a very poor word for that idea. -- Chris Smith

Chris Smith
Computability is just a distraction here. The problem isn't whether "getAnIntFromUser" is computable... it is whether it's a function at all! Even uncomputable functions are first and foremost functions, and not being computable is just a property that they have. Clearly this is not a function at all. It doesn't even have the general form of a function: it has no input, so clearly it can't map each input value to a specific output value. Now, since it's not a function, it makes little sense to even try to talk about whether it is computable or not (unless you first define a notion of computability for something other than functions).
Of course getAnIntFromUser is not a function. It is an instruction to computer. Think of IO as a form of writing instructions to some worker (essentially, the kernel, which in its turn uses processor's io ports). You are asking this “worker” to change some global state. Thus, your function “f” is a function indeed, which generates a list of instructions to kernel, according to given number.

On Fri, 2011-12-30 at 23:16 +0200, Artyom Kazak wrote:
Thus, your function “f” is a function indeed, which generates a list of instructions to kernel, according to given number.
Not my function, but yes, f certainly appears to be a function. Conal's concern is that if there is no possible denotational meaning for values of IO types, then f can't be said to be a function, since its results are not well-defined, as values. This is a valid concern... assigning a meaning to values of IO types necessarily involves some very unsatisfying hand-waving about indeterminacy, since for example IO actions can distinguish between bottoms that are considered equivalent in the denotational semantics of pure values (you can catch a use of 'error', but you can't catch non-termination). Nevertheless, I'm satisfied that to the extent that any such meaning can be assigned, f will be a valid function on non-bottom values. Not perfect, but close. -- Chris Smith

Chris Smith
This is a valid concern... assigning a meaning to values of IO types necessarily involves some very unsatisfying hand-waving about indeterminacy, since for example IO actions can distinguish between bottoms that are considered equivalent in the denotational semantics of pure values (you can catch a use of 'error', but you can't catch non-termination). Nevertheless, I'm satisfied that to the extent that any such meaning can be assigned, f will be a valid function on non-bottom values. Not perfect, but close.
Agree. The fact that IO actions can distinguish between bottoms, self-modify code, terminate non-terminable computations by rebooting the system, send killbots to the programmer's house and so on are extremely unsatisfying. That's IO for you. The dirty impure bottom comparison which uses IO, though, is available only to already impure functions.

time t: f 42 (computational process implementing func application begins…) t+1: <keystroke> = 1 t+2: 43 (… and ends)
time t+3: f 42 t+4: <keystroke> = 2 t+5: 44
Conclusion: f 42 != f 42
That conclusion would only follow if the same IO action always produced the same result when performed twice in a row. That's obviously untrue, so the conclusion doesn't follow. What you've done is entirely consistent with the fact that f 42 = f 42... it just demonstrates that whatever f 42 is, it doesn't always produce the same result when you o it twice. What Conal is getting at is that we don't have a formal model of what an IO action means. Nevertheless, we know because f is a function, that when it is applied twice to the same argument, the values we get back (which are IO actions, NOT integers) are the same. -- Chris Smith

On Fri, Dec 30, 2011 at 9:11 AM, Chris Smith
time t: f 42 (computational process implementing func application begins…) t+1: <keystroke> = 1 t+2: 43 (… and ends)
time t+3: f 42 t+4: <keystroke> = 2 t+5: 44
Conclusion: f 42 != f 42
That conclusion would only follow if the same IO action always produced the same result when performed twice in a row. That's obviously untrue, so the conclusion doesn't follow. What you've done is entirely consistent with the fact that f 42 = f 42... it just demonstrates that whatever f 42 is, it doesn't always produce the same result when you o it twice.
Exactly. Gregg threw in two different executions, which of course can produce two different values, whether or not the IOs are equal.
What Conal is getting at is that we don't have a formal model of what an IO action means. Nevertheless, we know because f is a function, that when it is applied twice to the same argument, the values we get back (which are IO actions, NOT integers) are the same.
And I also raised a more fundamental question than whether this claim of sameness is true, namely what is equality on IO? Without a precise & consistent definition of equality, the claims like "f 42 == f (43 - 1)" are even defined, let alone true. And since the conversation is about Haskell IO, I'm looking for a definition that applies to all of IO, not just some relatively well-behaved subset like putchar/getchar+IORefs+threads. - Conal - Conal

On Dec 30, 2011, at 11:21 AM, Conal Elliott wrote:
And I also raised a more fundamental question than whether this claim of sameness is true, namely what is equality on IO? Without a precise & consistent definition of equality, the claims like "f 42 == f (43 - 1)" are even defined, let alone true. And since the conversation is about Haskell IO, I'm looking for a definition that applies to all of IO, not just some relatively well-behaved subset like putchar/getchar+IORefs+threads.
Well, you'll no doubt be glad to know I think I've said about all I need to say on this topic, but I'll add one more thing. Threads like this I often find useful even when I disagree vehemently with various parties. In this case an old idea I'd forgotten about was suddenly dislodged by the discussion. A few years ago - the last time I got involved in a discussion on Haskell semantics - I spent some time sketching out ideas for using random variables to provide definitions (or at least notation) for stuff like IO. I'm not sure I could even find the notes now, but my recollection is that it seemed like a promising approach. One advantage is that this eliminates the kind of informal language (like "user input") that seems unavoidable in talking about IO. Instead of defining e.g. readChar or the like as an "action" that does something and returns an char (or however standard Haskell idiom puts it), you can just say that readChar is a random char variable and be done with it. The notion of "doing an action" goes away. The side-effect of actually reading the input or the like can be defined generically by saying that evaluating a random variable always has some side-effect; what specifically the side effect is does not matter. I mention this as a possible approach for anybody looking for a better way of accounting for IO in Haskell. Cheers, Gregg

On Fri, Dec 30, 2011 at 10:45 AM, Gregg Reynolds
On Dec 30, 2011, at 11:21 AM, Conal Elliott wrote:
And I also raised a more fundamental question than whether this claim of
sameness is true, namely what is equality on IO? Without a precise & consistent definition of equality, the claims like "f 42 == f (43 - 1)" are even defined, let alone true. And since the conversation is about Haskell IO, I'm looking for a definition that applies to all of IO, not just some relatively well-behaved subset like putchar/getchar+IORefs+threads.
Well, you'll no doubt be glad to know I think I've said about all I need to say on this topic, [...]
Honestly, I'm not trying to get you to speak less, but rather to share your perspective more clearly. I've have more than my fill of circular arguments and ill-defined claims. I'm reminded of a quote from David R. MacIver in “A problem of languagehttp://www.drmaciver.com/2009/05/a-problem-of-language/", Of course, once you start defining the term people will start arguing about
the definitions. This is pretty tedious, I know. But as tedious as arguing about definitions is, it can’t hold a candle to arguing without definitions.
- Conal

On Fri, 2011-12-30 at 12:45 -0600, Gregg Reynolds wrote:
I spent some time sketching out ideas for using random variables to provide definitions (or at least notation) for stuff like IO. I'm not sure I could even find the notes now, but my recollection is that it seemed like a promising approach. One advantage is that this eliminates the kind of informal language (like "user input") that seems unavoidable in talking about IO. Instead of defining e.g. readChar or the like as an "action" that does something and returns an char (or however standard Haskell idiom puts it), you can just say that readChar is a random char variable and be done with it. The notion of "doing an action" goes away. The side-effect of actually reading the input or the like can be defined generically by saying that evaluating a random variable always has some side-effect; what specifically the side effect is does not matter.
Isn't this just another way of saying the same thing that's been said already? It's just that you're saying "random variable" instead of "I/O action". But you don't really mean random variable, because there's all this stuff about side effects thrown in which certainly isn't part of any idea of random variables that anyone else uses. What you really mean is, apparently, I/O action, and you're still left with all the actual issues that have been discussed here, such as when two I/O actions (aka random variables) are the same. There is one difference, and it's that you're still using the term "evaluation" to mean performing an action. That's still a mistake. Evaluation is an idea from operational semantics, and it has nothing to do with performing effects. The tying of effects to evaluation is precisely why it's so hard to reason about programs in, say, C denotationally, because once there is no such thing as an evaluation process, modeling the meaning of terms becomes much more complex and amounts to reinventing operational semantics in denotational clothing)\. I'd submit that it is NOT an advantage to any approach that the notion of doing an action goes away. That notion is *precisely* what programs are trying to accomplish, and obscuring it inside functions and evaluation rather than having a way to talk about it is handicapping yourself from a denotational perspective. Rather, what would be an advantage (but also rather hopeless) would be to define the notion of doing an action more precisely. -- Chris Smith

On Dec 30, 2011, at 11:11 AM, Chris Smith wrote:
time t: f 42 (computational process implementing func application begins…) t+1: <keystroke> = 1 t+2: 43 (… and ends)
time t+3: f 42 t+4: <keystroke> = 2 t+5: 44
Conclusion: f 42 != f 42
That conclusion would only follow if the same IO action always produced the same result when performed twice in a row. That's obviously untrue, so the conclusion doesn't follow. What you've done is entirely consistent with the fact that f 42 = f 42... it just demonstrates that whatever f 42 is, it doesn't always produce the same result when you o it twice.
What Conal is getting at is that we don't have a formal model of what an IO action means.
Right, and my little counter-example is intended to support that.
Nevertheless, we know because f is a function
We do?

Conal Elliott wrote:
Heinrich Apfelmus wrote:
The function
f :: Int -> IO Int f x = getAnIntFromTheUser >>= \i -> return (i+x)
is pure according to the common definition of "pure" in the context of purely functional programming. That's because
f 42 = f (43-1) = etc.
Put differently, the function always returns the same IO action, i.e. the same value (of type IO Int) when given the same parameter.
Two questions trouble me:
How can we know whether this claim is true or not?
What does the claim even mean, i.e., what does "the same IO action" mean, considering that we lack a denotational model of IO?
I think you can put at least these troubles to rest by noting that f 42 and f (43-1) are intentionally equal, even though you're not confident on their extensional meaning. The idea is to represent IO as an abstract data type type IO' a = Program IOInstr a data Program instr a where Return :: a -> Program instr a Then :: instr a -> (a -> Program instr b) -> Program instr b instance Monad (Program instr) where return = Return (Return a) >>= g = g a (i `Then` f) >>= g = i `Then` (\x -> f x >>= g) date IOInstr a where PutChar :: Char -> IOInstr () GetChar :: IOInstr Char etc... So, two values of type IO' a are equal iff their "program codes" are equal (= intensional equality), and this is indeed the case for f 42 and f (43-1) . Therefore, the (extensional) interpretations of these values by GHC are equal, too, even though you don't think we know what these interpretations are. (Of course, programs with different source code may be extensionally equal, i.e. have the same effects. That's something we would need a semantics of IO for.) Best regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

On Fri, Dec 30, 2011 at 9:19 AM, Heinrich Apfelmus < apfelmus@quantentunnel.de> wrote:
Conal Elliott wrote:
Heinrich Apfelmus wrote:
The function
f :: Int -> IO Int f x = getAnIntFromTheUser >>= \i -> return (i+x)
is pure according to the common definition of "pure" in the context of purely functional programming. That's because
f 42 = f (43-1) = etc.
Put differently, the function always returns the same IO action, i.e. the same value (of type IO Int) when given the same parameter.
Two questions trouble me:
How can we know whether this claim is true or not?
What does the claim even mean, i.e., what does "the same IO action" mean, considering that we lack a denotational model of IO?
I think you can put at least these troubles to rest by noting that f 42 and f (43-1) are intentionally equal, even though you're not confident on their extensional meaning.
The idea is to represent IO as an abstract data type
type IO' a = Program IOInstr a
data Program instr a where Return :: a -> Program instr a Then :: instr a -> (a -> Program instr b) -> Program instr b
instance Monad (Program instr) where return = Return (Return a) >>= g = g a (i `Then` f) >>= g = i `Then` (\x -> f x >>= g)
date IOInstr a where PutChar :: Char -> IOInstr () GetChar :: IOInstr Char etc...
So, two values of type IO' a are equal iff their "program codes" are equal (= intensional equality), and this is indeed the case for f 42 and f (43-1) . Therefore, the (extensional) interpretations of these values by GHC are equal, too, even though you don't think we know what these interpretations are.
(Of course, programs with different source code may be extensionally equal, i.e. have the same effects. That's something we would need a semantics of IO for.)
How do you know that GHC's (or YHC's, etc) interpretation of IO is a composition of this program code interpretation with some other (more extensional) interpretation? In particular, how do you know that no IO primitive can ever distinguish between 42 and 43-1. - Conal

On Dec 30, 2011, at 11:19 AM, Heinrich Apfelmus wrote:
Conal Elliott wrote:
Heinrich Apfelmus wrote:
The function
f :: Int -> IO Int f x = getAnIntFromTheUser >>= \i -> return (i+x)
is pure according to the common definition of "pure" in the context of purely functional programming. That's because
f 42 = f (43-1) = etc.
Put differently, the function always returns the same IO action, i.e. the same value (of type IO Int) when given the same parameter.
Two questions trouble me: How can we know whether this claim is true or not? What does the claim even mean, i.e., what does "the same IO action" mean, considering that we lack a denotational model of IO?
I think you can put at least these troubles to rest by noting that f 42 and f (43-1) are intentionally equal, even though you're not confident on their extensional meaning.
(I think you meant "intensionally"). Ok, I think I can go with that, something like "f 42 means the sum of 42 and the user input". And I suppose one could argue that the extension of f is well-defined as the set of integer pairs. But that does not make f a (computable) function, because the mapping from domain to co-domain remains undefined, dependent as it is on IO. -Gregg

On Dec 29, 2011, at 2:16 PM, Steve Horne wrote:
Of course you can extract values out of IO actions to work with them - the bind operator does this for you nicely, providing the value as an argument to the function you pass to the right-hand argument of the bind. But that function returns another IO action anyway - although you've extracted a value out and the value affects a computation, all you can do with it in the long run is return another IO action.
Even so, that value can only be extracted out at run-time, after the action is executed.
So, consider the following...
getAnIntFromTheUser :: IO Int
From a pure functional point of view, that should return the same action every time. Well, the partially evaluated getAnIntFromTheUser has the same structure each time - but the actual Int packaged inside the action isn't decided until runtime, when the action is executed. At compile-time, that action can only be partially evaluated - the final value OF THE ACTION depends on what Int the user chooses to give because that Int is a part of the action value.
Howdy Steve, You are correct that Haskell is not, strictly speaking "pure" - no language that does anything useful (e.g. IO) can possibly be purely functional. But there seems to be a certain amount of language policing in the "Haskell community" - "pure" means what we mean when we use it to describe Haskell, and don't you dare use it otherwise. Ok, but that just leads to riddles like "when is a pure language impure?" A: when it isn't pure. Several posts to this thread have insisted that IO values are really values like any other values, can be reasoned about, etc. and that the process yielding the value (including possible side-effects) is therefore irrelevant or secondary or etc.. Well, you can reason about them indirectly, by virtue of their types, but you can't reason about the values themselves, because they are non-deterministic and undecidable. And the process clearly is relevant, since it motivates the use of the value in the first place. Not much point in a pure IO value that does not cause IO, and if the side effects were truly irrelevant to the use of such values then we would not need monads to order their evaluation. So the argument that all of Haskell is immaculately, purely functional is pure hooey, for me at least. I completely understand what people mean when they talk like this; I just think it's a misuse of English. Now one way of understanding all this is to say that it implicates the static/dynamic (compile-time/run-time) distinction: you don't know what e.g. IO values are until runtime, so this distinction is critical to distinguishing between pure and impure. I gather this is your view. I think that is reasonable, but with the caveat that it must be at the right level of abstraction. I don't think ASTs etc. enter into it - those are implementation techniques, and the only generalization we can apply to compilers is that they do implement the language definition, not how they do it (not all C compilers use ASTs). The right level of abstraction (IMHO) is the distinction between atemporality and temporality. The functional stuff is atemporal, which means among other things that evaluation is unordered (evaluation being a temporal process). Adding IO etc. capabilities to the purely functional fragment of a language infects it with temporality. But we can model temporality using order, so we can dispense with the notion of run-time and say that IO etc. stuff adds an ordered fragment to the unordered fragment. One goal of the language is then to enforce a strict correspondence between the order of events outside the program (e.g. keystrokes) and "events" inside the program (getchar). The beauty of the monad solution is not that it magically transforms non-functional stuff like IO into functional stuff, but that it exploits type discipline to make such operations *mimic* purely functional stuff in a sense - but only at the level of typing. Impure operations then have purely functional type discipline while remaining essentially non-functional. So I think of Haskell as a quasi-pure or hybrid language. C on the other hand is totally impure (except for predefined constants like '1'). For totally pure languages you have to look elsewhere, e.g. logics - there are no pure programming languages. It's fairly easy to grasp the point by going back to Turing's original insight. The cornerstone of his ideas was not the machine but the human calculator working with pencil and paper, finite memory, etc. So to see the diff all you have to do is think about what a human does with a problem (program) written on paper. Give the human calculator a computable task - add 2+2 - and you can be confident you will receive a definite answer in a finite amount of time. Lard this with a non-computable step - add 2 + 2 + getInt - and all bets are off. In this case, the calculator must pick up a phone and listen for an integer, or (avoiding machine metaphors) go to the window and look for a sign. There are two problems: we don't know which sign may appear, and worse, we don't even know *if* a sign will appear. Our poor hack may remain at the window waiting for Godot to appear with a sign for the rest of time. So the problem we have given the calculator is not a purely functional one, and the text that expresses the problem (the program) cannot be written in a purely functional language. More to the point with respect to the "Haskell is immaculate" argument, even if the calculator does receive a sign, this does not change the nature of the problem text - it still contains a non-computable step. Regarding side-effects, they can be (informally) defined pretty simply: any non-computational effect caused by a computation is a side-effect. Such effects can be designed and exploited, as when a bit (voltage?) pattern is used to drive output display, but the fundamental distinction is computational cause v. non-computational effect. This excludes inefficient computation, which is not distinguished by a definition in terms of the goal of the computation. If you define side-effect as anything not contributing to the final result of the computation then only perfectly efficient algorithms would be free of side-effects. But that clashes with intuition - you could insert code to compute pi to the 100th place in a a simple Fibonnaci number generator; that would be inefficient but I doubt many would call it a side-effect. On the other hand, every real-world computation has at least two side effects: consumption of energy and production of heat. Intentional side effects like IO are no different - they are parasitical on primitive side-effects of computation, such as the energizing of a bit pattern somewhere on a chip detected and translated to a light pattern on a screen. The interesting thing (to me) is that these days chip designers are using the heat produced by computation something like the way they treat the bit patterns produced by computation - both may be treated as by-products of computation and put to use (or controlled) by design. (Conspiracy nuts should be all over sided-effects; in principle you could design a chip such that produces some kind of side effect that could be detected and "read", exposing the hidden computation.) Cheers, -Gregg

Gregg Reynolds
Regarding side-effects, they can be (informally) defined pretty simply: any non-computational effect caused by a computation is a side-effect.
I wonder: can writing to memory be called a “computational effect”? If yes, then every computation is impure. If no, then what’s the difference between memory and hard drive? By the way, the Data.HashTable is in IO monad. Is it impure? Would it be pure if designers had chosen to use ST instead?

On Dec 30, 2011, at 10:34 AM, Artyom Kazak wrote:
Gregg Reynolds
писал(а) в своём письме Fri, 30 Dec 2011 17:23:20 +0200: Regarding side-effects, they can be (informally) defined pretty simply: any non-computational effect caused by a computation is a side-effect.
I wonder: can writing to memory be called a “computational effect”? If yes, then every computation is impure. If no, then what’s the difference between memory and hard drive?
Great question! It suggests that the line between computation and its side effects is not as clear-cut as we (well, I) thought. If computations are Platonistic, mathematico-logical "things", then is actual computation a side-effect of the Platonic Idea? Heh heh.
By the way, the Data.HashTable is in IO monad. Is it impure? Would it be pure if designers had chosen to use ST instead?
Dunno, somebody else will have to answer that one. -Gregg

On Dec 30, 2011, at 10:34 AM, Artyom Kazak wrote:
Gregg Reynolds
писал(а) в своём письме Fri, 30 Dec 2011 17:23:20 +0200: Regarding side-effects, they can be (informally) defined pretty simply: any non-computational effect caused by a computation is a side-effect. I wonder: can writing to memory be called a “computational effect”? If yes, then every computation is impure. If no, then what’s the difference between memory and hard drive?
Great question! It suggests that the line between computation and its side effects is not as clear-cut as we (well, I) thought. It relates to that while loop thing in my last reply to you, I think -
On 30/12/2011 15:50, Gregg Reynolds wrote: the computational effect dressed up as non-computational. We can do some work in Haskell using a temporary file on disk as a pragmatic solution to a space issue. We can feed that composed IO action to unsafePerformIO without breaking referential transparency, at least if we choose to ignore issues like running out of disk space (we ignore similar memory issues all the time). And really, it's just explicit virtual memory - it's implicitly happening in the background anyway. Or - it's layers of abstraction. The implementation of a function that uses explicit virtual memory is impure, but the abstraction it provides is pure. At least in principle (hand-waving away possible disk errors etc), the abstraction doesn't leak impurity.

On Fri, 2011-12-30 at 18:34 +0200, Artyom Kazak wrote:
I wonder: can writing to memory be called a “computational effect”? If yes, then every computation is impure. If no, then what’s the difference between memory and hard drive?
The difference is that our operating systems draw an abstraction boundary such that memory is private to a single program, while the hard drive is shared between independent entities. It's not the physical distinction (which has long been blurred by virtual memory and caches anyway), but the fact that they are on different sides of that abstraction boundary. -- Chris Smith

Chris Smith
I wonder: can writing to memory be called a “computational effect”? If yes, then every computation is impure.
I wonder if not the important bit is that pure computations are unaffected by other computations (and not whether they can affect other computations). Many pure computations have side effects (increases temperature, modifies hardware registers and memory, etc), but their effect can only be observed in IO. (E.g. Debug.Trace.trace provides a non-IO interface by use of unsafePerformIO which is often considered cheating, but in this view it really is pure.) -k -- If I haven't seen further, it is by standing in the footprints of giants

On Sun, Jan 1, 2012 at 3:26 PM, Ketil Malde
Chris Smith
writes: I wonder: can writing to memory be called a “computational effect”? If yes, then every computation is impure.
I wonder if not the important bit is that pure computations are unaffected by other computations (and not whether they can affect other computations). Many pure computations have side effects (increases temperature, modifies hardware registers and memory, etc), but their effect can only be observed in IO.
(E.g. Debug.Trace.trace provides a non-IO interface by use of unsafePerformIO which is often considered cheating, but in this view it really is pure.)
The point of purity (and related concepts) is to have useful tools for working with and reasoning about your code. Lambda calculi can be seen as the prototypical functional languages, and the standard ones have the following nice property: The only difference between reduction strategies is termination. Non-strict strategies will terminate for more expressions than strict ones, but that is the only difference. This property is often taken to be the nub of what it means to be a pure functional language. If the language is an extension of the lambda calculus that preserves this property, then it is a pure functional language. Haskell with the 'unsafe' stuff removed is such a language by this definition, and most GHC additions are too, depending on how you want to argue. It is even true with respect to the output of programs, but not when you're using Debug.Trace, because: flip (+) ("foo" `trace` 1) ("bar" `trace` 1) will print different things with different evaluation orders. A similar property is referential transparency, which allows you to factor your program however you want without changing its denotation. So: (\x -> x + x) e is the same as: e + e This actually fails for strict evaluation strategies unless you relax it to be 'same denotation up to bottoms' or some such. But not having to worry about whether you're changing the definedness of your programs by factoring/inlining is actually a useful property that strict languages lack. Also, the embedded IO language does not have this property. do x <- m ; f x x is different from do x <- m ; y <- m ; f x y and so on. This is why you shouldn't write your whole program with IO functions; it lacks nice properties for working with your code. But the embedded IO language lacking this property should not be confused with Haskell lacking this property. Anyhow, here's my point: these properties can be grounded in useful features of the language. However, for the vast majority of people, being able to factor their code differently and have it appear exactly the same to someone with a memory sniffer isn't useful. And unless you're doing serious crypto or something, there is no correct amount of heat for a program to produce. So if we're wondering about whether we should define purity or referential transparency to incorporate these things, the answer is an easy, "no." We throw out the possibility that 'e + e' may do more work than '(\x -> x + x) e' for the same reason (indeed, we often want to factor it so that it performs better, while still being confident that it is in some sense the same program, despite the fact that performing better might by some definitions mean that it isn't the same program). But the stuff that shows up on stdout/stderr typically is something we care about, so it's sensible to include that. If you don't care what happens there, go ahead and use Debug.Trace. It's pure/referentially transparent modulo stuff you don't care about. -- Dan

Dan Doel : ...
Also, the embedded IO language does not have this property.
do x<- m ; f x x
is different from
do x<- m ; y<- m ; f x y
and so on. This is why you shouldn't write your whole program with IO functions; it lacks nice properties for working with your code. Sorry, what are you trying to suggest?
You show two OBVIOUSLY different pieces of code, and you say that they are different. If, by chance, some newbie reads that and gets the impression that (<-) is something equivalent to (=), you are serving the devil. Jerzy Karczmarczuk

On 01/01/2012 22:57, Jerzy Karczmarczuk wrote:
Dan Doel : ...
Also, the embedded IO language does not have this property.
do x<- m ; f x x
is different from
do x<- m ; y<- m ; f x y
and so on. This is why you shouldn't write your whole program with IO functions; it lacks nice properties for working with your code. Sorry, what are you trying to suggest?
You show two OBVIOUSLY different pieces of code, and you say that they are different. If, by chance, some newbie reads that and gets the impression that (<-) is something equivalent to (=), you are serving the devil.
Speaking as the devil... The do-notation sugar may confuse the issue - the <- looks like an operator, but translating to binds-and-lambdas form suggests otherwise. Quick translations (I hope no mistakes) with lots of parens... m >>= (\x -> (f x x)) m >>= (\x -> (m >>= (\y -> (f x y)))) At first sight, these two expressions can give different results for reasons other than evaluation order. In particular, there are two bind operators, not just one. That is, x and y could get different values for reasons other than the two m references referring to different things. So... is that true? Of course even the bind operator arguably isn't primitive. We could translate to get rid of those too, and see what lies underneath. This is where we start seeing functions of type... World -> (x, World) Problem - this level of abstraction is hypothetical. It is not part of the Haskell language. Haskell specifically defines the IO monad to be a black box. I look at this World parameter as purely hypothetical, a trick used to gain an intuition. Whereas Jerzy (I think) uses it to claim Haskell is referentially transparent - those differing x and y values come from different worlds, or different world-states. I'm not entirely sure, though, as we got sidetracked. If main returns a function of type "World -> (x, World)" wrapped in a monad context, then there is referential transparency as defined in computer science. But is that a fair claim? In this model, Haskell is an interpreted language for compositing functions. We can call those functions programs. The executable is a translation of the function returned by main, but *not* a translation of the source code. But GHC is called a compiler, and compilation is usually considered a kind of translation - the executable is a translation of the source code. GHCi is an interpreter, but it doesn't stop at returning a function of type World -> (x, World) - it does the I/O. And the reason we use these terms is because, as programmers, we think of the executable as the program - as a translation of the source code. So what main returns - that hypothetical function World -> (x, World) - isn't just a product of the program, it's also a representation of the program. I've made similar points before, but how do they work out this time... So... when evaluate what effects referentially transparent ------------- ------------------------ ------- ------------------------- compile-time main no yes run-time main someParticularWorld yes yes(?) I've proved effects at run-time, but in this model, the intermediate and final world-states are products of the evaluation of that "main someParticularWorld" expression. Even the results extracted from input actions are referentially transparent - or if not, we're dealing with the philosophy of determinism. It's probable that Jerzy told me this earlier and I wasn't ready to hear it then. However - we can say basically the same things about C. The World parameter is implicit in C but then it's implicit in Haskell too. Everything inside the IO monad black box is outside the scope of the Haskell language except in that semantics are defined for the primitive IO actions - basically what happens when a result is extracted out as part of evaluating a bind. That "(?)" in the "yes(?)" is because this is all contingent on that hypothetical World -> (x, World) function hidden inside the IO monad context, which is not specified in the Haskell language. When I say that Haskell lacks referential transparency because the execution of primitive IO actions is tied to the evaluation of the bind operators that extract out their results, and different executions of the same action yield different results, I'm only appealing to the defined semantics of the Haskell language. I'm not appealing to a hypothetical model where the world is passed as a parameter. OTOH, this World -> (x, World) model is much more appealing than my partially-evaluated-functions-as-AST-nodes model. So - the issue seems to be whether the IO monad is a context holding world-manipulating functions, or whether it's a black box with semantics specified at the bind level. And if referential transparency is decided at this level, what practical relevance does it have? It's probably better to stick with "the functional core is referentially transparent - IO actions break that, so don't overuse the IO monad". You can argue "may or may not break that depending on your viewpoint", but if you can't objectively decide which viewpoint is correct, then you haven't proven referential transparency.

... World -> (x, World) ...
I look at this World parameter as purely hypothetical, a trick used to gain
an intuition. Whereas Jerzy (I think) uses it to claim Haskell is referentially transparent - those differing x and y values come from different worlds, or different world-states.
I don't see this interpretation in Jerzy's words, and I'd be very surprised if he had that sort of argument in mind. If main returns a function of type "World -> (x, World)" wrapped in ...
Main does not return or denote such a thing. The idea that Haskell IO can
be accurately explained as (i.e., denotes) World -> (x,World) is a
persistent myth. That model cannot explain concurrency (even with the
outside world) or nondeterminism, both of which are part of Haskell IO. We
don't have an precise & accurate denotational model for IO, in contrast to
most other types in Haskell. Which is to say that while much of Haskell
programming is denotative, IO programming is not. Peter Landin, an
important figure in functional programming, proposed and defined this term
"denotative" as a substantive & precise replacement for the fuzzier notions
of "functional" and "declarative". He offered his definition and suggested
that "When faced with a new notation that borrows the functional appearance
of everyday algebra, it is (c) that gives us a test for whether the
notation is genuinely functional or merely masquerading."
Of course, various subsets of IO can be precisely and accurately modeled,
but so far not IO as we use it. It's very unlikely that we ever will have
such a (precise & accurate) model, and by design, as explained at
http://conal.net/blog/posts/notions-of-purity-in-haskell/#comment-22829 .
- Conal
On Sun, Jan 1, 2012 at 7:43 PM, Steve Horne
On 01/01/2012 22:57, Jerzy Karczmarczuk wrote:
Dan Doel : ...
Also, the embedded IO language does not have this property.
do x<- m ; f x x
is different from
do x<- m ; y<- m ; f x y
and so on. This is why you shouldn't write your whole program with IO functions; it lacks nice properties for working with your code.
Sorry, what are you trying to suggest?
You show two OBVIOUSLY different pieces of code, and you say that they are different. If, by chance, some newbie reads that and gets the impression that (<-) is something equivalent to (=), you are serving the devil.
Speaking as the devil...
The do-notation sugar may confuse the issue - the <- looks like an operator, but translating to binds-and-lambdas form suggests otherwise. Quick translations (I hope no mistakes) with lots of parens...
m >>= (\x -> (f x x))
m >>= (\x -> (m >>= (\y -> (f x y))))
At first sight, these two expressions can give different results for reasons other than evaluation order. In particular, there are two bind operators, not just one.
That is, x and y could get different values for reasons other than the two m references referring to different things. So... is that true?
Of course even the bind operator arguably isn't primitive. We could translate to get rid of those too, and see what lies underneath. This is where we start seeing functions of type...
World -> (x, World)
Problem - this level of abstraction is hypothetical. It is not part of the Haskell language. Haskell specifically defines the IO monad to be a black box.
I look at this World parameter as purely hypothetical, a trick used to gain an intuition. Whereas Jerzy (I think) uses it to claim Haskell is referentially transparent - those differing x and y values come from different worlds, or different world-states. I'm not entirely sure, though, as we got sidetracked.
If main returns a function of type "World -> (x, World)" wrapped in a monad context, then there is referential transparency as defined in computer science. But is that a fair claim?
In this model, Haskell is an interpreted language for compositing functions. We can call those functions programs. The executable is a translation of the function returned by main, but *not* a translation of the source code.
But GHC is called a compiler, and compilation is usually considered a kind of translation - the executable is a translation of the source code. GHCi is an interpreter, but it doesn't stop at returning a function of type World -> (x, World) - it does the I/O. And the reason we use these terms is because, as programmers, we think of the executable as the program - as a translation of the source code.
So what main returns - that hypothetical function World -> (x, World) - isn't just a product of the program, it's also a representation of the program.
I've made similar points before, but how do they work out this time...
So...
when evaluate what effects referentially transparent ------------- ------------------------ ------- ------------------------- compile-time main no yes run-time main someParticularWorld yes yes(?)
I've proved effects at run-time, but in this model, the intermediate and final world-states are products of the evaluation of that "main someParticularWorld" expression. Even the results extracted from input actions are referentially transparent - or if not, we're dealing with the philosophy of determinism.
It's probable that Jerzy told me this earlier and I wasn't ready to hear it then.
However - we can say basically the same things about C. The World parameter is implicit in C but then it's implicit in Haskell too. Everything inside the IO monad black box is outside the scope of the Haskell language except in that semantics are defined for the primitive IO actions - basically what happens when a result is extracted out as part of evaluating a bind. That "(?)" in the "yes(?)" is because this is all contingent on that hypothetical World -> (x, World) function hidden inside the IO monad context, which is not specified in the Haskell language.
When I say that Haskell lacks referential transparency because the execution of primitive IO actions is tied to the evaluation of the bind operators that extract out their results, and different executions of the same action yield different results, I'm only appealing to the defined semantics of the Haskell language. I'm not appealing to a hypothetical model where the world is passed as a parameter.
OTOH, this World -> (x, World) model is much more appealing than my partially-evaluated-functions-**as-AST-nodes model.
So - the issue seems to be whether the IO monad is a context holding world-manipulating functions, or whether it's a black box with semantics specified at the bind level. And if referential transparency is decided at this level, what practical relevance does it have?
It's probably better to stick with "the functional core is referentially transparent - IO actions break that, so don't overuse the IO monad". You can argue "may or may not break that depending on your viewpoint", but if you can't objectively decide which viewpoint is correct, then you haven't proven referential transparency.
______________________________**_________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe

Conal Elliott cites Steve Horne:
I look at this World parameter as purely hypothetical, a trick used to gain an intuition. Whereas Jerzy (I think) uses it to claim Haskell is referentially transparent - those differing x and y values come from different worlds, or different world-states.
I don't see this interpretation in Jerzy's words, and I'd be very surprised if he had that sort of argument in mind.
I don't think either having used the 'World' model as an argument of the referential transparency. The main reason is that I don't know what does it mean, the referential transparency of the real world. There is a philosophical issue involved: the problem of IDENTITY, which is as old as the humanity, and it will survive it... We simply don't know what does it mean: "the same"... But I disagree quite strongly with the idea of "/World parameter as purely hypothetical, a trick used to gain an intuition/". I mentioned the language Clean (no reaction, seems that Haskellians continue to ignore it...) In Clean this IS the IO model. You have such entities as FileSystem, which has the Unique Access property, etc. You can put all that in an equivalent of the IO Monad, constructed within Clean itself, not as a primitive. Jerzy

On 02/01/2012 10:03, Jerzy Karczmarczuk wrote:
But I disagree quite strongly with the idea of "/World parameter as purely hypothetical, a trick used to gain an intuition/". I mentioned the language Clean (no reaction, seems that Haskellians continue to ignore it...)
I don't know about others, but I intend to learn one language at a time. In any case, that's Clean, not Haskell.

Steve Horne
The do-notation sugar may confuse the issue - the <- looks like an operator, but translating to binds-and-lambdas form suggests otherwise. Quick translations (I hope no mistakes) with lots of parens...
m >>= (\x -> (f x x))
m >>= (\x -> (m >>= (\y -> (f x y))))
First of all, you can omit all parentheses, because the (>>=) operator is associative by definition (this is not checked by the compiler though).
At first sight, these two expressions can give different results for reasons other than evaluation order. In particular, there are two bind operators, not just one.
That is, x and y could get different values for reasons other than the two m references referring to different things. So... is that true?
Yes, that's correct. Remember that referential transparency does not say that you are not allowed to pass different values to the same function. It just forbids functions to return different results for different inputs, and this is true for both expressions you showed. Using a state monad to get more concrete, let's say that 'm' returns the current state and then increments it. If the start state is 3, then 'x' will become 3 on execution and 'y' will become 4. However, the result of the composition is /always/ the state computation that returns the result of 'f' applied to the current state and the incremented current state. Just like when you write "x = getLine", then you can safely replace any occurence of 'getLine' by 'x'.
Of course even the bind operator arguably isn't primitive. We could translate to get rid of those too, and see what lies underneath. This is where we start seeing functions of type...
World -> (x, World)
Problem - this level of abstraction is hypothetical. It is not part of the Haskell language. Haskell specifically defines the IO monad to be a black box.
And that's fine, because IO is an embedded DSL. A better view of IO is a GADT like: data IO :: * -> * where GetLine :: IO String PutStrLn :: String -> IO () ... This is still hypothetical, but it shows how even IO is easily referentially transparent (as long as you don't use unsafe* cheats). Furthermore you have to consider that /execution/ of IO actions is entirely outside the scope of the language itself. A compiler turns an expression of type "IO ()" into machine code that executes the encoded recipe. In any case, you have to differentiate between evaluation and IO execution.
If main returns a function of type "World -> (x, World)" wrapped in a monad context, then there is referential transparency as defined in computer science. But is that a fair claim?
Even though the World state monad is a bad intuition in my opinion, why not? Evaluation is referentially transparent, because you don't evaluate to results of IO actions. You evaluate to the IO actions themselves. This is not a hack, it is a great feature, because it's precisely what allows us to build real world actions using combinators.
In this model, Haskell is an interpreted language for compositing functions. We can call those functions programs. The executable is a translation of the function returned by main, but *not* a translation of the source code.
It is a translation of the source code, because evaluation happens at run-time, interleaved with the execution of 'main', as 'main' goes along forcing thunks (in a thunk-based implementation).
So what main returns - that hypothetical function World -> (x, World) - isn't just a product of the program, it's also a representation of the program.
And there comes the limitation of this intuition. It is so theoretical that you can't express a function of that type even as machine code. On the other hand, the GADT variant could indeed be turned into bytecode and then interpreted by a bytecode machine. But this is not how it works in, say, GHC. GHC compiles to native code using the thunk approach I mentioned earlier.
When I say that Haskell lacks referential transparency because the execution of primitive IO actions is tied to the evaluation of the bind operators that extract out their results, and different executions of the same action yield different results, I'm only appealing to the defined semantics of the Haskell language. I'm not appealing to a hypothetical model where the world is passed as a parameter.
This is where your mistake is again: execution vs. evaluation. The (>>=) operator does /not/ extract results. It doesn't have to. It just makes sure (abstractly!) that the second argument is applied to the result of the first argument at execution time. It builds a data dependency between monadic actions. (>>=) is composition, not execution. Execution is outside the scope of the monadic interface, and for the specific case of IO it's even outside the scope of the language. If you think about it, you will find that (>>=) can't even extract results. The only thing it can do with results is to make other things dependent on them. This is because the type of the result is fully polymorphic.
So - the issue seems to be whether the IO monad is a context holding world-manipulating functions, or whether it's a black box with semantics specified at the bind level. And if referential transparency is decided at this level, what practical relevance does it have?
It's a black box and that's fine. There is nothing impure about IO.
It's probably better to stick with "the functional core is referentially transparent - IO actions break that, so don't overuse the IO monad". You can argue "may or may not break that depending on your viewpoint", but if you can't objectively decide which viewpoint is correct, then you haven't proven referential transparency.
You can objectively decide. Referential transparency means that an expression cannot magically evaluate to something this time and to something other the next time, be it an Int value, a function or an IO action. 'getLine' will always be 'getLine', and 'putStrLn "abc"' will always be the action that prints "abc" with a line feed. If you /had/ a concrete representation of 'putStrLn "abc"' (like with the GADT), then you could safely replace 'putStrLn "abc"' in the code by this representation. This is what you can do with all monads and everything else in Haskell. Again, I'm assuming you don't cheat. If you do cheat, then you are turning execution into evaluation, thereby potentially breaking referential transparency. Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/

On 2012/1/1 Ertugrul Söylemez
Steve Horne
wrote: Of course even the bind operator arguably isn't primitive. We could translate to get rid of those too, and see what lies underneath. This is where we start seeing functions of type...
World -> (x, World)
Problem - this level of abstraction is hypothetical. It is not part of the Haskell language. Haskell specifically defines the IO monad to be a black box.
And that's fine, because IO is an embedded DSL. A better view of IO is a GADT like:
data IO :: * -> * where GetLine :: IO String PutStrLn :: String -> IO () ...
This is still hypothetical, but it shows how even IO is easily referentially transparent (as long as you don't use unsafe* cheats).
What?? I see how a definition like this one shows how something else that you call "IO" can be denotative & RT. I don't see how what that conclusion has to do with Haskell's IO. I also wonder whether you're assuming that all of the IO primitives we have in Haskell treat their non-IO arguments denotationally/extensionally, so that there cannot be operations like "isWHNF :: a -> IO Bool". - Conal

On Jan 2, 2012, at 1:30 PM, Conal Elliott wrote:
On 2012/1/1 Ertugrul Söylemez
wrote: And that's fine, because IO is an embedded DSL. A better view of IO is a GADT like:
data IO :: * -> * where GetLine :: IO String PutStrLn :: String -> IO () ...
This is still hypothetical, but it shows how even IO is easily referentially transparent (as long as you don't use unsafe* cheats).
What?? I see how a definition like this one shows how something else that you call "IO" can be denotative & RT. I don't see how what that conclusion has to do with Haskell's IO.
Whether you say such a beast "is" IO or "something else that you call 'IO'", I don't see the problem with positing an open GADT of this form, new constructors of which are introduced by built-in magic and/or by 'foreign import', and letting the denotation of IO be terms in the free algebraic theory on the resulting signature. It is then the job of the compiler, linker, et al, to implement a model of that algebraic theory in the machine language. Foreign imports introduce new "external names" - constructors of the GADT - and the linker connects those names to their "implementations" - giving them denotations as terms in the target machine's language. Maybe I'm missing something but, in the presence of FFI, how can the world-interfacing portion of a programming language possibly be any more denotative than that? Once you cross that threshold, I'd much rather have an operational semantics anyway. Ultimately, programming a computer is about making the computer _do_ things. No matter what sort of denotational semantics you come up with, I don't see any way to avoid it eventually "bottoming out" at some abstract representation which must then either have an operational semantics or an informal "everyone who matters knows what that means" semantics. Eventually, the denotation of anything that potentially involves interaction with the real world must be "a program" in some real or imaginary machine's language. This model chooses a very reasonable place to sever the infinite tower of turtles because it produces a language that is universal: it is the free algebra of the signature specified by the GADT. Incidentally, this model also addresses a concern I've heard voiced before that IO isn't demonstrably a monad. The whole point of IO is, as I understand it, that it is a monad _by construction_ - specifically, it is the monad whose Kleisli category is the category of contexts and substitutions in the free algebraic theory generated on this signature. There are even at least 2 published implementations of this construction in Haskell - the MonadPrompt and operational packages - and it has been shown that it does, in fact, form a monad. I would assert that if there is any sense in which the IO type _implementation_ fails to be a monad, it is a bug and not a flaw in the concept of an IO monad.
I also wonder whether you're assuming that all of the IO primitives we have in Haskell treat their non-IO arguments denotationally/extensionally, so that there cannot be operations like "isWHNF :: a -> IO Bool".
Correct me if I'm wrong, but it appears the implication here is that [[isWHNF x]] /= [[isWHNF]] [[x]]. I don't think this is necessarily true though. Somewhere in any formal model of any language which takes the real world into account, there must be some translation from a denotational semantics to an operational one. If the denotational semantics is not computable, that translation necessarily must introduce some kind of "accidental" extra state. The denotational semantics will generally include no concept of this state, so no denotation can mention it. But I see no problem in there being a value in the denotation which is translated to an operation which does make use of this state. In this model, [[isWHNF x]] is something like "IsWHNF [[x]]", which the compiler then translates into some code that, at run time, checks the progress of the attempt to compute the denotation of x. At no point is there a term whose denotation depends on that state; instead, there is a computation which chooses how to proceed to do based on that state. This does not infect the denotation with the forbidden knowledge, it only allows you to denote operations which are aware of the mechanism by which the denotation is computed. Similarly, the operations 'peek' and 'poke' allow you to denote operations which may do unspeakably evil things at runtime, including entirely subverting that mechanism. That doesn't mean the denotation is wrong, it means the machine has a back door. Certainly it would be better, all other things being equal, if the translation did not open the back door like that but, as is so often the case, all other things are not equal. The FFI and the occasional heinous performance hack are far too useful for most people to ever consider throwing out. This may mean that my concept of Haskell does not match your definition of denotational. But if that's the case, I'm perfectly OK with that. Furthermore, I'd like to know how any real programming language actually could be. In any case, the real power of Haskell's IO model is that it gives you first class procedures and treats them on an absolutely equal footing with numbers, functions, mutable references, data structures, etc. Whether you call that "purity", "referential transparency", "denotationality", or something else, the fact is that Haskell has it and very few other languages do. Personally, I call it "nifty". -- James

Le Sun, 1 Jan 2012 16:31:51 -0500,
Dan Doel
On Sun, Jan 1, 2012 at 3:26 PM, Ketil Malde
wrote: Chris Smith
writes: I wonder: can writing to memory be called a “computational effect”? If yes, then every computation is impure.
I wonder if not the important bit is that pure computations are unaffected by other computations (and not whether they can affect other computations). Many pure computations have side effects (increases temperature, modifies hardware registers and memory, etc), but their effect can only be observed in IO.
(E.g. Debug.Trace.trace provides a non-IO interface by use of unsafePerformIO which is often considered cheating, but in this view it really is pure.)
The point of purity (and related concepts) is to have useful tools for working with and reasoning about your code. Lambda calculi can be seen as the prototypical functional languages, and the standard ones have the following nice property:
The only difference between reduction strategies is termination.
Non-strict strategies will terminate for more expressions than strict ones, but that is the only difference.
This has nothing to do with purity (purity and strictness/lazyness are different).
This property is often taken to be the nub of what it means to be a pure functional language. If the language is an extension of the lambda calculus that preserves this property, then it is a pure functional language. Haskell with the 'unsafe' stuff removed is such a language by this definition, and most GHC additions are too, depending on how you want to argue. It is even true with respect to the output of programs, but not when you're using Debug.Trace, because:
flip (+) ("foo" `trace` 1) ("bar" `trace` 1)
will print different things with different evaluation orders.
A similar property is referential transparency, which allows you to factor your program however you want without changing its denotation. So:
(\x -> x + x) e
is the same as:
e + e
That is not really what I call referential transparency; for me this is rather β reduction… For me, referential transparency means that the same two closed expression in one context denote the same value. So that is rather: let x = e y = e in x + y is the same as: e + e
This actually fails for strict evaluation strategies unless you relax it to be 'same denotation up to bottoms' or some such. But not having to worry about whether you're changing the definedness of your programs by factoring/inlining is actually a useful property that strict languages lack.
In fact, strict language can be referentially transparent; it is the case in ML (in fact I only know of Ocaml minus impure features, but well…).
Also, the embedded IO language does not have this property.
do x <- m ; f x x
is different from
do x <- m ; y <- m ; f x y
In fact IO IS referentially transparent; do NOT FORGET that there is some syntactic sugar: do x <- m ; f x x = (>>=) m (\x -> f x x) do x <- m ; y <- m ; f x y = (>>=) m (\x -> (>>=) m (\y -> f x y)) So when we desugar it (and it is only desugaring, it is no optimization/reduction/whatEverElseYouWant; these two expressions have the same AST once parsed), where would you want to put referential transparency?
and so on. This is why you shouldn't write your whole program with IO functions; it lacks nice properties for working with your code. But the embedded IO language lacking this property should not be confused with Haskell lacking this property.
It is not an "embedded IO language", it is just some sugar for monads; you can as well do: maybePlus :: (Mabe Int) -> (Maybe Int) -> Maybe Int maybePlus mx my = do x <- mx y <- my return $ x+y and there is absolutely no IO.
Anyhow, here's my point: these properties can be grounded in useful features of the language. However, for the vast majority of people, being able to factor their code differently and have it appear exactly the same to someone with a memory sniffer isn't useful. And unless you're doing serious crypto or something, there is no correct amount of heat for a program to produce. So if we're wondering about whether we should define purity or referential transparency to incorporate these things, the answer is an easy, "no." We throw out the possibility that 'e + e' may do more work than '(\x -> x + x) e' for the same reason (indeed, we often want to factor it so that it performs better, while still being confident that it is in some sense the same program, despite the fact that performing better might by some definitions mean that it isn't the same program).
But the stuff that shows up on stdout/stderr typically is something we care about, so it's sensible to include that. If you don't care what happens there, go ahead and use Debug.Trace. It's pure/referentially transparent modulo stuff you don't care about.
-- Dan
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

This thread pretty much exemplifies why many people don't bother with this
mailing list anymore.
On Sun, Jan 1, 2012 at 7:00 PM, AUGER Cédric
Le Sun, 1 Jan 2012 16:31:51 -0500, Dan Doel
a écrit : On Sun, Jan 1, 2012 at 3:26 PM, Ketil Malde
wrote: Chris Smith
writes: I wonder: can writing to memory be called a “computational effect”? If yes, then every computation is impure.
I wonder if not the important bit is that pure computations are unaffected by other computations (and not whether they can affect other computations). Many pure computations have side effects (increases temperature, modifies hardware registers and memory, etc), but their effect can only be observed in IO.
(E.g. Debug.Trace.trace provides a non-IO interface by use of unsafePerformIO which is often considered cheating, but in this view it really is pure.)
The point of purity (and related concepts) is to have useful tools for working with and reasoning about your code. Lambda calculi can be seen as the prototypical functional languages, and the standard ones have the following nice property:
The only difference between reduction strategies is termination.
Non-strict strategies will terminate for more expressions than strict ones, but that is the only difference.
This has nothing to do with purity (purity and strictness/lazyness are different).
This property is often taken to be the nub of what it means to be a pure functional language. If the language is an extension of the lambda calculus that preserves this property, then it is a pure functional language. Haskell with the 'unsafe' stuff removed is such a language by this definition, and most GHC additions are too, depending on how you want to argue. It is even true with respect to the output of programs, but not when you're using Debug.Trace, because:
flip (+) ("foo" `trace` 1) ("bar" `trace` 1)
will print different things with different evaluation orders.
A similar property is referential transparency, which allows you to factor your program however you want without changing its denotation. So:
(\x -> x + x) e
is the same as:
e + e
That is not really what I call referential transparency; for me this is rather β reduction…
For me, referential transparency means that the same two closed expression in one context denote the same value.
So that is rather:
let x = e y = e in x + y
is the same as:
e + e
This actually fails for strict evaluation strategies unless you relax it to be 'same denotation up to bottoms' or some such. But not having to worry about whether you're changing the definedness of your programs by factoring/inlining is actually a useful property that strict languages lack.
In fact, strict language can be referentially transparent; it is the case in ML (in fact I only know of Ocaml minus impure features, but well…).
Also, the embedded IO language does not have this property.
do x <- m ; f x x
is different from
do x <- m ; y <- m ; f x y
In fact IO IS referentially transparent; do NOT FORGET that there is some syntactic sugar:
do x <- m ; f x x = (>>=) m (\x -> f x x)
do x <- m ; y <- m ; f x y = (>>=) m (\x -> (>>=) m (\y -> f x y))
So when we desugar it (and it is only desugaring, it is no optimization/reduction/whatEverElseYouWant; these two expressions have the same AST once parsed), where would you want to put referential transparency?
and so on. This is why you shouldn't write your whole program with IO functions; it lacks nice properties for working with your code. But the embedded IO language lacking this property should not be confused with Haskell lacking this property.
It is not an "embedded IO language", it is just some sugar for monads; you can as well do:
maybePlus :: (Mabe Int) -> (Maybe Int) -> Maybe Int maybePlus mx my = do x <- mx y <- my return $ x+y
and there is absolutely no IO.
Anyhow, here's my point: these properties can be grounded in useful features of the language. However, for the vast majority of people, being able to factor their code differently and have it appear exactly the same to someone with a memory sniffer isn't useful. And unless you're doing serious crypto or something, there is no correct amount of heat for a program to produce. So if we're wondering about whether we should define purity or referential transparency to incorporate these things, the answer is an easy, "no." We throw out the possibility that 'e + e' may do more work than '(\x -> x + x) e' for the same reason (indeed, we often want to factor it so that it performs better, while still being confident that it is in some sense the same program, despite the fact that performing better might by some definitions mean that it isn't the same program).
But the stuff that shows up on stdout/stderr typically is something we care about, so it's sensible to include that. If you don't care what happens there, go ahead and use Debug.Trace. It's pure/referentially transparent modulo stuff you don't care about.
-- Dan
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 30/12/2011 15:23, Gregg Reynolds wrote:
Now one way of understanding all this is to say that it implicates the static/dynamic (compile-time/run-time) distinction: you don't know what e.g. IO values are until runtime, so this distinction is critical to distinguishing between pure and impure. I gather this is your view. Yes. I think that is reasonable, but with the caveat that it must be at the right level of abstraction. I don't think ASTs etc. enter into it - those are implementation techniques, and the only generalization we can apply to compilers is that they do implement the language definition, not how they do it (not all C compilers use ASTs). I would argue that AST is more an analogy than an implementation - I don't really care if a person dry-runs the code by reading and rewriting fragments of the source code in notepad - there is still something that represents an unevaluated function but which is itself being treated as a value - the fallback result in this model.
A possible way to implement a Haskell program would be... 1. Apply rewrite rules to evaluate everything possible without executing primitive IO actions. 2. Wait until you need to run the program. 3. Continue applying rewrite rules to evaluate everything possible, but this time executing primitive IO actions (and substituting run-time inputs into the model) as and when necessary so that the rewriting can eliminate them. The model correctly describes how the program should behave. It requires no metaphors, only a very careful person to do the re-writing and (unavoidably) to execute the primitive IO actions.
The right level of abstraction (IMHO) is the distinction between atemporality and temporality. The functional stuff is atemporal, which means among other things that evaluation is unordered (evaluation being a temporal process). Adding IO etc. capabilities to the purely functional fragment of a language infects it with temporality. But we can model temporality using order, so we can dispense with the notion of run-time and say that IO etc. stuff adds an ordered fragment to the unordered fragment. One goal of the language is then to enforce a strict correspondence between the order of events outside the program (e.g. keystrokes) and "events" inside the program (getchar). Nice way to put it. The beauty of the monad solution is not that it magically transforms non-functional stuff like IO into functional stuff, but that it exploits type discipline to make such operations *mimic* purely functional stuff in a sense - but only at the level of typing. Impure operations then have purely functional type discipline while remaining essentially non-functional. So I think of Haskell as a quasi-pure or hybrid language. C on the other hand is totally impure (except for predefined constants like '1'). For totally pure languages you have to look elsewhere, e.g. logics - there are no pure programming languages. Well - on C is impure, it depends how you look at that. If it's valid to say that your home-grown "while" loop is a function that accepts two actions as parameters, well, C has an equivalent function built into the compiler. Again you can separate the pure from the impure, and the impurity is only realized when the program is executed. The correspondence between orderings arises in different ways, but even C only demands that results are "as if" the standards-defined evaluation order were followed - partial-evaluation and other optimisations during compilation are done in whatever order the C compiler finds convenient, exploiting associativity and commutativity where those are guaranteed etc.
It's fairly easy to grasp the point by going back to Turing's original insight. The cornerstone of his ideas was not the machine but the human calculator working with pencil and paper, finite memory, etc. So to see the diff all you have to do is think about what a human does with a problem (program) written on paper. Give the human calculator a computable task - add 2+2 - and you can be confident you will receive a definite answer in a finite amount of time. Lard this with a non-computable step - add 2 + 2 + getInt - and all bets are off. Precisely my point with my bind example - in the expression "getAnIntFromTheUser >>= \i -> return (i+1)" you cannot know the value of i at compile-time, or within the realm of the atemporal. But even if at one level you consider that expression still to be evaluated within
It doesn't make Haskell and C the same thing, of course. the atemporal realm, it is still evaluated also (in translated/rewritten/whatever form) in the temporal realm - at run-time. If the user happens to enter the value 1, at some point, the expression i+1 is conceptually rewritten to 1+1 and then to 2. Arguably everything that can be evaluated at compile-time - everything in the atemporal realm - is just optimisation. That's a narrow view, and not one that I (now) agree with. The distinction is useful for understanding the program - probably even more so calling it temporal vs. atemporal because that removes the issue of how much partial evaluation will the compiler choose to do, or for that matter am I running an interpreter.
Regarding side-effects, they can be (informally) defined pretty simply: any non-computational effect caused by a computation is a side-effect. Well, pedanting, there are computation effects that we pretend are non-computational. The trivial case is using return. Another case might be an overliteral translation of...
int i = 0; int j = 0; while (i < 10) { j += i; i++; } If you literally translate this to Haskell using a hand-rolled while-loop, that condition is sensitive to effects of the loop body. The variable i must be implemented as an IORef. You have a computational effect treated as a non-computational effect. You can feed the composed IO action to unsafePerformIO to do all this in a non-IO context, and you won't violate referential transparency - but it's ugly and klunky, and something that should be in the atemporal realm has been artificially moved into the temporal realm. Practically, that's a good reason to use recursion or a fold or whatever instead of a hand-rolled while loop. In this case, idiomatic Haskell would be sum [0..9] - a clear win for Haskell, I think. Different languages have different idioms - no biggie. I'm just saying that a non-trivial computational effect may be dressed up as a non-computational effect, and most functional programmers in my experience would call each mutation of i a side-effect - or else would refuse to call the corresponding C mutations side-effects.

On 2011-12-30 14:32, Steve Horne wrote:
A possible way to implement a Haskell program would be...
1. Apply rewrite rules to evaluate everything possible without executing primitive IO actions. 2. Wait until you need to run the program. 3. Continue applying rewrite rules to evaluate everything possible, but this time executing primitive IO actions (and substituting run-time inputs into the model) as and when necessary so that the rewriting can eliminate them.
This is inadequate, because it is does not specify when the program's various IO actions are executed, or even which of them are executed. Try print "first" `seq` print "second" or let x = print "x" in print "value" Also, "evaluate everything possible" is strangely hard to match up with the concepts involved in Haskell's non-strict evaluation. An accurate description of how an IO expression is executed would be: Evaluate the expression. There are three possible results. 1. If it is a 'return' operation, the result is the operand. 2. If it is a bind (>>=) operation, a. Execute the left operand, obtaining a result expression. b. The right operand is a function. Apply it to the returned expression, obtaining an IO expression. c. Execute the IO expression. 3. If it is a primitive, execute it, obtaining an expression. A Haskell program is an IO expression, and is executed as above. Notice that when a program is executed, its IO actions are not performed as a result of being evaluated. Rather, they are evaluated (down to values) in order to be performed. Every evaluation in the above procedure is pure, with no IO effects. The concept of AST is no more helpful in explaining IO than it is in explaining foldr (*) 1 [1..5] IMO it's no help at all.

On 30/12/2011 20:38, Scott Turner wrote:
On 2011-12-30 14:32, Steve Horne wrote:
A possible way to implement a Haskell program would be...
1. Apply rewrite rules to evaluate everything possible without executing primitive IO actions. 2. Wait until you need to run the program. 3. Continue applying rewrite rules to evaluate everything possible, but this time executing primitive IO actions (and substituting run-time inputs into the model) as and when necessary so that the rewriting can eliminate them. This is inadequate, because it is does not specify when the program's various IO actions are executed, or even which of them are executed. Yes it does. Specifying when all the various IO actions are executed relative to each other is what the IO *monad* is for.
IIRC, there is a little hand-waving that SPJ confesses to about that - basically that each term will only be reduced once.
Try print "first" `seq` print "second" or let x = print "x" in print "value" Also, "evaluate everything possible" is strangely hard to match up with the concepts involved in Haskell's non-strict evaluation. I didn't say what order to evaluate it in. For example, in this expression...
let a = (2*2) in (a+a) One valid next evaluation (rewriting) set would give... (2*2)+(2*2) Another would give... let a = 4 in (a+a) I don't care which you choose. I don't demand that only concrete arithmetic steps count. I don't demand that evaluation must be bottom-up or top-down or left-to-right. Only that as many evaluation steps as possible are applied. The hand-waving there - the infinity issue. For a lazy list, we need a very careful definition of "possible". That's one reason why even lazy evaluation implies at least a particular preferred evaluation order - just not the same order as for strict evaluation. Anyway, you cannot use rewriting to extract a result out of a primitive IO action without executing the IO action. Even if every IO action was of type IO () this still applies by the rules of the Haskell language - you cannot extract that () out of a (putStrLn "Hello") until you execute that action.

On Wed, Dec 28, 2011 at 2:44 PM, Heinrich Apfelmus
The beauty of the IO monad is that it doesn't change anything about purity. Applying the function
bar :: Int -> IO Int
to the value 2 will always give the same result:
bar 2 = bar (1+1) = bar (5-3)
Strictly speaking, that doesn't sound right. The "result" of an IO operation is outside of the control (and semantics) of the Haskell program, so Haskell has no idea what it will be. Within the program, there is no result. So Int -> IO Int is not really a function - it does not map a determinate input to a determinate output. The IO monad just makes it look and act like a function, sort of, but what it really does is provide reliable ordering of non-functional operations - invariant order, not invariant results. To respond to original post: no language that supports IO can be purely functional in fact, but with clever design it can mimic a purely functional language. Cheers Gregg

On Thu, Dec 29, 2011 at 07:19:17AM -0600, Gregg Reynolds wrote:
On Wed, Dec 28, 2011 at 2:44 PM, Heinrich Apfelmus
wrote: The beauty of the IO monad is that it doesn't change anything about purity. Applying the function
bar :: Int -> IO Int
to the value 2 will always give the same result:
bar 2 = bar (1+1) = bar (5-3)
Strictly speaking, that doesn't sound right. The "result" of an IO operation is outside of the control (and semantics) of the Haskell program, so Haskell has no idea what it will be. Within the program, there is no result. So Int -> IO Int is not really a function - it does not map a determinate input to a determinate output. The IO monad just makes it look and act like a function, sort of, but what it really does is provide reliable ordering of non-functional operations - invariant order, not invariant results.
Not only strictly speaking. In practice too: bar _ = do s <- readFile "/tmp/x.txt" return (read s) Once you're in a monad that has 'state', the return value doesn't strictly depend anymore on the function arguments. At least that's my understanding. regards, iustin

Iustin Pop::
In practice too:
bar _ = do s<- readFile "/tmp/x.txt" return (read s)
Once you're in a monad that has 'state', the return value doesn't strictly depend anymore on the function arguments. Nice example. PLEASE, show us the trace of its execution. Then, the discussion might be more fruitful
Jerzy Karczmarczuk

On Thu, Dec 29, 2011 at 05:51:57PM +0100, Jerzy Karczmarczuk wrote:
Iustin Pop::
In practice too:
bar _ = do s<- readFile "/tmp/x.txt" return (read s)
Once you're in a monad that has 'state', the return value doesn't strictly depend anymore on the function arguments. Nice example. PLEASE, show us the trace of its execution. Then, the discussion might be more fruitful
Sorry? I did the same mistake of misreading the grand-parent's "IO Int" vs. "Int", if that's what you're referring to. Otherwise, I'm confused as what you mean. iustin

On Thu, Dec 29, 2011 at 05:55:24PM +0100, Iustin Pop wrote:
On Thu, Dec 29, 2011 at 05:51:57PM +0100, Jerzy Karczmarczuk wrote:
Iustin Pop::
In practice too:
bar _ = do s<- readFile "/tmp/x.txt" return (read s)
Once you're in a monad that has 'state', the return value doesn't strictly depend anymore on the function arguments. Nice example. PLEASE, show us the trace of its execution. Then, the discussion might be more fruitful
Sorry?
I did the same mistake of misreading the grand-parent's "IO Int" vs. "Int", if that's what you're referring to.
Otherwise, I'm confused as what you mean.
And to clarify better my original email: yes, (bar x) always gives you back the same IO action; but the results of said IO action are/can be different when executed. iustin

On Dec 29, 2011, at 11:01 AM, Iustin Pop wrote:
On Thu, Dec 29, 2011 at 05:55:24PM +0100, Iustin Pop wrote:
On Thu, Dec 29, 2011 at 05:51:57PM +0100, Jerzy Karczmarczuk wrote:
Iustin Pop::
In practice too:
bar _ = do s<- readFile "/tmp/x.txt" return (read s)
Once you're in a monad that has 'state', the return value doesn't strictly depend anymore on the function arguments. Nice example. PLEASE, show us the trace of its execution. Then, the discussion might be more fruitful
Sorry?
I did the same mistake of misreading the grand-parent's "IO Int" vs. "Int", if that's what you're referring to.
Otherwise, I'm confused as what you mean.
And to clarify better my original email: yes, (bar x) always gives you back the same IO action;
More precisely: the same *type*.
but the results of said IO action are/can be different when executed.
-Gregg

On Thu, Dec 29, 2011 at 11:14 AM, Gregg Reynolds
On Dec 29, 2011, at 11:01 AM, Iustin Pop wrote:
And to clarify better my original email: yes, (bar x) always gives you back the same IO action;
More precisely: the same *type*.
I'm confused - what do you mean by "type"? I don't think that Iustin's statement needs any sort of qualifier - (bar x) always returns the same IO action when called with the same value for x, no matter how many times you call it. Antoine

On Dec 29, 2011, at 11:29 AM, Antoine Latter wrote:
On Thu, Dec 29, 2011 at 11:14 AM, Gregg Reynolds
wrote: On Dec 29, 2011, at 11:01 AM, Iustin Pop wrote:
And to clarify better my original email: yes, (bar x) always gives you back the same IO action;
More precisely: the same *type*.
I'm confused - what do you mean by "type"? I don't think that Iustin's statement needs any sort of qualifier - (bar x) always returns the same IO action when called with the same value for x, no matter how many times you call it.
Maybe it doesn't need qualification, but my guess is that most people read "IO Int" to mean something like "IO action of type int". But computation does not involve "action". Action is just an explanatory device - a kind of macguffin - to help explain what's going on with IO, which is non-computational. But it is a type, and in Haskell it's all about the types. "IO Int" is a type designator, not an action designator. A minor point maybe, but germane to the original post (I hope). -Gregg

Quoth Gregg Reynolds
A minor point maybe, but germane to the original post (I hope).
It isn't - I mean, I'm not really sure what your point is, but the example really returns the same IO value, not just one of the same type. Consider an example with implementation: wint :: Int -> IO Int wint a = let s = show a in do putStr s return (length s) Now the expression "wint 994" is a value of type IO Int, and any instance of that expression is the same value - an action is not the same as the action's result. You can use this value in pure Haskell expressions with confidence. Donn

On Dec 29, 2011, at 12:33 PM, Donn Cave wrote:
Quoth Gregg Reynolds
, .. A minor point maybe, but germane to the original post (I hope).
It isn't - I mean, I'm not really sure what your point is, but the example really returns the same IO value, not just one of the same type.
Consider an example with implementation:
wint :: Int -> IO Int wint a = let s = show a in do putStr s return (length s)
Now the expression "wint 994" is a value of type IO Int, and any instance of that expression is the same value
Ok, but if that were all there is to it we would not need monads. I guess it may boil down to a matter of taste in definition and exposition - to me any account of stuff like IO Int that omits mention of the fact that, well, IO is involved, is incomplete. But then I like the theoretical and even philosophical side of things where others tend to want to get on with writing useful code. ;) And the original post was if I remember about purity/impurity etc.
- an action is not the same as the action's result.
Nor is a computation the same as the computation's result. The critical difference is that computations are deterministic processes, and "actions" (IO, rand, etc.) are not. Therefore they are not functions, their evaluation must be ordered, and they cannot even in principle be fully modeled in purely functional terms. At least I don't see how they can.
You can use this value in pure Haskell expressions with confidence.
Because they are monadic, not because they are values like other values. -Gregg

Le 29/12/2011 18:01, Iustin Pop a écrit :
I'm confused as what you mean. And to clarify better my original email: yes, (bar x) always gives you back the same IO action; but the results of said IO action are/can be different when executed. The whole of my point is that it DOESN'T MATTER. (And I believe that Heinrich A. meant the same thing). I asked for the execution trace in order that you see what your function does to the programme itself, not that it attempts to contact the external world, and explode it. You discovered it yourself. The result is an object of type Read a => IO a and this is all. (Well, in order to really execute it, you have to specify the type a anyway).
/if you're using IO actions, your code is not referentially
I think that nobody will convince anybody here. Steve Horne continues with his own visions : transparent and is therefore impure/ I believe that this statement is doubly erroneous, but I give up. I won't even ask to show me WHERE the ref. transparence is broken. This discussion is a dead loop... Jerzy

Quoth Gregg Reynolds
On Wed, Dec 28, 2011 at 2:44 PM, Heinrich Apfelmus
wrote: The beauty of the IO monad is that it doesn't change anything about purity. Applying the function
bar :: Int -> IO Int
to the value 2 will always give the same result:
bar 2 = bar (1+1) = bar (5-3)
Strictly speaking, that doesn't sound right.
Look again at the sentence you trimmed off the end:
Of course, the point is that this result is an *IO action* of type IO Int, it's not the Int you would get "when executing this action".
I believe that more or less points to the key to this discussion. If it didn't make sense to you, or didn't seem relevant to the question of pure functions, then it would be worth while to think more about it. Donn

On Dec 29, 2011, at 9:16 AM, Donn Cave wrote:
Quoth Gregg Reynolds
, On Wed, Dec 28, 2011 at 2:44 PM, Heinrich Apfelmus
wrote: The beauty of the IO monad is that it doesn't change anything about purity. Applying the function
bar :: Int -> IO Int
to the value 2 will always give the same result:
bar 2 = bar (1+1) = bar (5-3)
Strictly speaking, that doesn't sound right.
Look again at the sentence you trimmed off the end:
Of course, the point is that this result is an *IO action* of type IO Int, it's not the Int you would get "when executing this action".
I believe that more or less points to the key to this discussion. If it didn't make sense to you, or didn't seem relevant to the question of pure functions, then it would be worth while to think more about it.
Ok, let's parse it out. "…it's not the int you would get 'when executing this action". Close, but no cooky: it's not any kind of int at all (try doing arithmetic with it). "IO Int" is a piece of rhetoric for the mental convenience of the user; Haskell does not and cannot know what the result of an IO action is, because it's outside the scope of the language (and computation). (The "Int" part of "IO Int" refers to the input, not the output; it's just a sort of type annotation.) It's not even a computation, unless you want to take a broad view and include oracles, interaction, etc. in your definition of computation. -Gregg

29.12.2011, 23:55, "Gregg Reynolds"
Haskell does not and cannot know what the result of an IO action is, because it's outside the scope of the language (and computation). (The "Int" part of "IO Int" refers to the input, not the output; it's just a sort of type annotation.) It's not even a computation, unless you want to take a broad view and include oracles, interaction, etc. in your definition of computation.
Yes, purity is a property of language. It's matter to thinking of algorithms and expressing these algorithms in computer language. It's not matter (in general) for programmers what PC would be do with IO computation. We want to have an expressive instrument and want to have a robust language. We want to have a language that can give us possibility to express our algorithms in clear, easy to understand, proven ways. And purity property of language is about it. It's not interesting to programmers what means purity to compile or to runtime system. It maybe interesting if we can realize effective compiler form language with purity property to machine codes. But haskell shows us than it's possible. Isn't it? ------- PS sorry for my not good French

Gregg Reynolds wrote:
Donn Cave wrote:
Quoth Gregg Reynolds wrote:
Look again at the sentence you trimmed off the end:
Of course, the point is that this result is an *IO action* of type IO Int, it's not the Int you would get "when executing this action".
I believe that more or less points to the key to this discussion. If it didn't make sense to you, or didn't seem relevant to the question of pure functions, then it would be worth while to think more about it.
Ok, let's parse it out. "…it's not the int you would get 'when executing this action". Close, but no cooky: it's not any kind of int at all (try doing arithmetic with it). "IO Int" is a piece of rhetoric for the mental convenience of the user; Haskell does not and cannot know what the result of an IO action is, because it's outside the scope of the language (and computation). (The "Int" part of "IO Int" refers to the input, not the output; it's just a sort of type annotation.) It's not even a computation, unless you want to take a broad view and include oracles, interaction, etc. in your definition of computation.
Why would IO Int be something special or mysterious? It's an ordinary value like everything else; it's on the same footing as [Char], Maybe Int, Int -> String, Bool, and so on. I see no difference between the list [1,2,3] :: [Int] and the action "pick a random number between 1 and 6" :: IO Int . Best regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

On 29/12/2011 19:21, Heinrich Apfelmus wrote:
Why would IO Int be something special or mysterious? It's an ordinary value like everything else; it's on the same footing as [Char], Maybe Int, Int -> String, Bool, and so on. I see no difference between the list [1,2,3] :: [Int] and the action "pick a random number between 1 and 6" :: IO Int .
Because performing the action (as part of extracting the result out of it) is relevant to the semantics of the language too, whether an IO monadic random generator or an an interaction with the user via a GUI or whatever. BTW - why use an IO action for random number generation? There's a perfectly good pure generator. It's probably handy to treat it monadically to sequence the generator state/seed/whatever but random number generation can be completely pure.

On 12/29/2011 08:47 PM, Steve Horne wrote:
On 29/12/2011 19:21, Heinrich Apfelmus wrote:
BTW - why use an IO action for random number generation? There's a perfectly good pure generator. It's probably handy to treat it monadically to sequence the generator state/seed/whatever but random number generation can be completely pure.
*Pseudo* random number generation can of course be pure (though threading the state would be tedious and error-prone). If you want truly random numbers you cannot avoid IO (the monad).

On 29/12/2011 19:55, Bardur Arantsson wrote:
On 12/29/2011 08:47 PM, Steve Horne wrote:
On 29/12/2011 19:21, Heinrich Apfelmus wrote:
BTW - why use an IO action for random number generation? There's a perfectly good pure generator. It's probably handy to treat it monadically to sequence the generator state/seed/whatever but random number generation can be completely pure.
*Pseudo* random number generation can of course be pure (though threading the state would be tedious and error-prone). If you want truly random numbers you cannot avoid IO (the monad). On the threading the state thing - it doesn't matter whether it's the IO monad or the State monad (a perfect wrapper for the seed).
For where-does-the-entropy-come-from, though, yes - I guess you're right.

If seed depends of psudo random event, for example of current systime,
we must use IO action.
30.12.2011, 02:47, "Steve Horne"
BTW - why use an IO action for random number generation? There's a perfectly good pure generator. It's probably handy to treat it monadically to sequence the generator state/seed/whatever but random number generation can be completely pure.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

The story begins here: Steve Horne: /BTW - why use an IO action for random number generation? There's a perfectly good pure generator. It's probably handy to treat it monadically to sequence the generator state/seed/whatever but random number generation can be completely pure. / =================== Bardur Arantsson: /*Pseudo* random number generation can of course be pure (though threading the state would be tedious and error-prone). If you want truly random numbers you cannot avoid IO (the monad). / ??? ??????? :
If seed depends of psudo random event, for example of current systime, we must use IO action. Bardur, Lev, of course you try to be helpful, but you are answering wrong questions.
"Truly random" numbers are very rarely used, forget about them. "Standard" r. generators (pseudo-random) in Haskell are monadic, because the relevant algorithms are stateful. Congruential, Fibonacci, Mersenne Twister, whatever, is a function, more or less: (newValue,newSeed) = rgen seed The monadic approach serves mainly to hide the seed. Some people prefer to use random streams, no monads, so the question of Steve Horne is not universal. But anyway, even without bind, the user will have to chain the seeds in some way. Still, I dont understand what does S.H. mean by a "perfectly good pure generator". Tell more please (unless you just mean a stream, say: str = map fst (iterate (\(v,sd) -> rgen sd) (v0,sd0)) ) Jerzy

On 29/12/2011 20:39, Jerzy Karczmarczuk wrote:
Still, I dont understand what does S.H. mean by a "perfectly good pure generator". Tell more please (unless you just mean a stream, say:
Probably bad wording, to be honest. I only meant that there's random number handling support in the Haskell library and, and least judging by type signatures, it's pure functional code with no hint of the IO monad. AFAIK there's no hidden unsafePerformIO sneaking any entropy in behind the scenes. Even if there was, it might be a legitimate reason for unsafePerformIO - random numbers are in principle non-deterministic, not determined by the current state of the outside world and which-you-evaluate-first should be irrelevant. If you have a quantum genuine-random-numbers gadget, the IO monad might be considered redundant for functions that get values from it - though it still isn't referentially transparent as it returns a different value each time even with the same parameters.

On Thu, 2011-12-29 at 21:04 +0000, Steve Horne wrote:
AFAIK there's no hidden unsafePerformIO sneaking any entropy in behind the scenes. Even if there was, it might be a legitimate reason for unsafePerformIO - random numbers are in principle non-deterministic, not determined by the current state of the outside world and which-you-evaluate-first should be irrelevant.
This is certainly not legitimate. Anything that can't be memoized has no business advertising itself as a function in Haskell. This matters quite a lot... programs might change from working to broken due to something as trivial as inlining by the compiler (see the ugly NOINLINE annotations often used with unsafePerformIO tricks for initialization code for an example). -- Chris Smith

Steve Horne :
I only meant that there's random number handling support in the Haskell library and, and least judging by type signatures, it's pure functional code with no hint of the IO monad. Look well at those functions, please.
Within the RandomGen class you have pure members, such as next (an Int instance of what I called rgen in my previous message. It propagates the seed "g" ). The algorithmics of the random generation has no particular "monadicity" in it, as I said, the IO (or State) monad serves to hide the seed. The generator itself should not be confounded with its iterative, sequential usage. If people wanted to do in their programmes just *one* read or write, never repeated, no IO Monad would be necessary. On the other hand, for the IO, you can sequence the World instances explicitly, without any Monads in a pure functional language, this is the style used in Clean. == I am strongly convinced that ALL people who want to understand the functional IO, refs, etc. should learn both, Haskell and Clean. Il might help them to see better the relation between the programme, and its environment. ========== You say: /random numbers are in principle non-deterministic, not determined by the current state of the outside world/ Sorry, but I haven't a slightest idea what you are talking about. Dybbuks? Jerzy

Steve Horne :
I only meant that there's random number handling support in the Haskell library and, and least judging by type signatures, it's pure functional code with no hint of the IO monad. Look well at those functions, please. Challenge accepted. Some code (intended to be loaded into GHCi and
On 29/12/2011 21:51, Jerzy Karczmarczuk wrote: played with) that I once wrote when doing the ninety-nine problems thing (the one that doesn't have ninety-nine problems - originally based on a Prolog tutorial IIRC)... -- Randomly select the specified number of items from the list -- -- Usage in GHCi... -- -- import System.Random -- randSelect "this is a list" 5 (mkStdGen 9877087) -- -- This will give the same results each time (for the same seed given to mkStdGen) -- -- randSelect' does the real work, but needs to know the length of the remaining -- list and doesn't do error checks (for efficiency reasons). module P23 (randSelect) where import System.Random randSelect' :: RandomGen g => [x] -> Int -> Int -> g -> ([x], g) randSelect' [] n l g = ([], g) -- n and l should be == 0, but no need for run-time check -- optimisation cases - no choice left randSelect' xs n l g | (n == l) = (xs, g) | (n == 0) = ([], g) randSelect' (x:xs) n l g = let xsLen = (l - 1) (rnd, g') = randomR (0, xsLen) g (keep, n') = if (rnd < n) then (True, (n-1)) else (False, n) (xs', g'') = randSelect' xs n' xsLen g' in ((if keep then (x:xs') else xs'), g'') randSelect :: RandomGen g => [x] -> Int -> g -> ([x], g) randSelect xs n g = let len = (length xs) in if (n > len) then error "Not enough items in the list!" else randSelect' xs n len g I see no IO monad anywhere in there. Of course I'm cheating - providing a constant seed at runtime. It's a bit like the classic "chosen by a throw of a fair die" joke in a way. But the functions I'm using are pure. I don't claim to know every Haskell library function, of course. If there's further functions for that, all well and good - but there's still a perfectly adequate pure functional subset.

Steve Horne :
Some code (intended to be loaded into GHCi and played with)
-- import System.Random -- randSelect "this is a list" 5 (mkStdGen 9877087) -- ... module P23 (randSelect) where -- ... randSelect' (x:xs) n l g = let xsLen = (l - 1) (rnd, g') = randomR (0, xsLen) g -- ...
I see no IO monad anywhere in there. Of course I'm cheating - providing a constant seed at runtime.
The last remark is irrelevant. Normally the seed IS constant, injected once, then updated by the generator iself. I don't know what you are trying to prove. That you don't need monads? Everybody knows this. Look at your own code. In randSelect' you write (rnd, g') = randomR (0, xsLen) g **You don't need monads, because you do your own sequencing and propagating the seed*, g -> g'.* Your library internal: randomR :: RandomGen g => (a, a) -> g -> (a, g) does the same thing, choosing a number within a range, *and propagating g*. (I call it a "seed", but it is a Int seed wrapped within a StdGen...) OK, I repeat once more... Monads are useful ONLY to iterate the primitive generator, hiding the seed. The generator itself (the algorithm of Pierre L'Ecuyer or any other comparable) is obviously pure. The monadisation was a design choice of Lennart Augustson, who decided to dump (hide) (StdGen s1 s2) inside an IORef, but nobody is obliged to use it. There are alternatives, such as generating first an infinite random stream, or your own manufacture. So, OK, you have your "pure" generator. I explain why your question is based on some misunderstanding. All this has NOTHING to do whatsoever with the question of purity or not. Haskell code is pure if you propagate the StdGen yourself, it remains pure when the sequencing uses (>>=). Here this "mythical" World which visibly frightens you, reduces to two integers32. Either they propagate in your code, or through the "iterate" functional, or through the "bind". In the last case it is hidden, so it may "change", since only ONE instance is accessible. [[Actually, one exercice I gave to my students was to implement an iterable random generator using the State monad. Of course, there were numerous suicides, and the survivors have been isolated in the Arkham asylum, but the world is still there]]. Clean uses "unique access variables" for the same purpose, and the Clean users usually live normally with them. Jerzy

On 30/12/2011 00:22, Jerzy Karczmarczuk wrote:
Steve Horne :
Some code (intended to be loaded into GHCi and played with)
-- import System.Random -- randSelect "this is a list" 5 (mkStdGen 9877087) -- ... module P23 (randSelect) where -- ... randSelect' (x:xs) n l g = let xsLen = (l - 1) (rnd, g') = randomR (0, xsLen) g -- ...
I see no IO monad anywhere in there. Of course I'm cheating - providing a constant seed at runtime.
The last remark is irrelevant. Normally the seed IS constant, injected once, then updated by the generator iself.
I don't know what you are trying to prove. I don't know why you think I'm trying to prove something here.
Earlier, I mentioned that Haskell provides pure functional random number support in the library - as part of going off on a tangent and, as it happens, of making a mistake. I specifically said something like "with no mention of the IO monad" with respect to type signatures. You said "Look well at those functions, please". I accepted your challenge. I looked well. I still say that Haskell provides pure functional random number support in the library. My "last remark" was there basically because of the earlier mistake - acknowledging that I've bypassed the whole issue of where the seed comes from, which may for all I know be supported by a library IO action, and which would be relevant given how this randomness thread started. That was my first mistake in this randomness thread - another mistake I made was saying unsafePerformIO might reasonably be used to sneak in entropy. Basically, I replied to your challenge - nothing more. I really don't even care much about random numbers - that's why my easiest reference was from back when I was doing those tutorials. There is no deep point here unless you're making one I haven't understood yet. As for whether or not Haskell is pure - this randomness thread isn't relevant to that any more. If you see my reference to purity as a weasel way of insinuating that there's also impurity in Haskell - I don't need to insinuate that, I've openly stated my view and explained my reasoning as well as I'm able. What point is there in being a cowardly weasel if you also paint a bullseye on your head and shout "Here I am!"?

On 12/29/2011 09:39 PM, Jerzy Karczmarczuk wrote:
"Truly random" numbers are very rarely used, forget about them.
Well, obviously, but why should we forget about them? The usual approach(*) is to gather entropy from a truly(**) random source and use that to seed (and perhaps periodically re-seed) a PRNG. (*) At least as far as I understand it. (**) At least one believed to be truly random. My point was simply to make clear the distinction between RNG vs. PRNG.
"Standard" r. generators (pseudo-random) in Haskell are monadic, because the relevant algorithms are stateful. Congruential, Fibonacci, Mersenne Twister, whatever, is a function, more or less: (newValue,newSeed) = rgen seed
The monadic approach serves mainly to hide the seed. Some people prefer to use random streams, no monads, so the question of Steve Horne is not universal.
Random streams are not referentially transparent, though, AFAICT...? Either way this thread has gone on long enough, let's not prolong it needlessly with this side discussion.

Bardur Arantsson:
Random streams are not referentially transparent, though, AFAICT...?
Either way this thread has gone on long enough, let's not prolong it needlessly with this side discussion.
but why should we forget about them? The usual approach(*) is to gather entropy from a truly(**) random source and use that to seed (and perhaps periodically re-seed) a PRNG. So, sorry, I didn't mean really "forget", only to change the subject which was irrelevant for the purity (but somehow has shown once more
Sure. But the discussion on randomness is /per se/ interesting, especially in a functional setting. Anyway, nobody can convince Steve Horne. Perhaps as an "unintentional" side-effect... But random streams, or rather pseudo-random streals (infinite lazy lists, as the example I gave, the `iterate` of `next`) are as referentially transparent as any Haskell data. Really. What I find really amazing, since I converted my soul from physics to computer since (many, many years ago...) is that most comments about random number generators come from people who don't need them, don't use them, and usually don't care about them... I taught random numbers, and I did some Monte-Carlo calculation in High Energy Physics, when many people here were not born. I *NEVER* used "true" random numbers, even to initialize a generator, since in the simulation business it is essential that you can repeat the sequence on some other platform, with some other parameters, etc. Of course, they are useful (don't need to convince an ancien physicist... And I lied. I used them, e.g. when I programmed some games for my children.) -- that Steve Horne had strange ideas about random generators). The generator of L'Ecuyer, or Mersenne Twister, or anything, don't care about the entropy. For a typical user, the only interesting thing is that the "random" streams pass the usual statistical tests : moments, correlation, spectrum... Otherwise it is as deterministic as 1 2 3 4. (For a typical user from my mafia. The mafia of cryptographists has different criteria ; from time to time we shoot ourselves in the coffee-machine corner of our dept.) Thank you for the discussion. You are right, I brake. Jerzy

On 12/30/2011 04:38 PM, Jerzy Karczmarczuk wrote:
Bardur Arantsson:
Random streams are not referentially transparent, though, AFAICT...?
Either way this thread has gone on long enough, let's not prolong it needlessly with this side discussion.
Sure. But the discussion on randomness is /per se/ interesting, especially in a functional setting.
Anyway, nobody can convince Steve Horne. Perhaps as an "unintentional" side-effect...
But random streams, or rather pseudo-random streals (infinite lazy lists, as the example I gave, the `iterate` of `next`) are as referentially transparent as any Haskell data. Really.
Of course -- if you just have a starting seed and the rest of the sequence is known from there. I was thinking of e.g. those "periodic re-initialization" ways of doing RNG.
I *NEVER* used "true" random numbers, even to initialize a generator, since in the simulation business it is essential that you can repeat the sequence on some other platform, with some other parameters, etc.
I've heard this a lot from physicists -- of course if you run a simulation reproducibility can be extremely important (e.g. for double-checking computations across different machines). However, if you're doing crypto it may not be so desirable :). Anyway, I'm out of this thread too :). Cheers,

On Dec 29, 2011, at 1:21 PM, Heinrich Apfelmus wrote:
Why would IO Int be something special or mysterious?
I don't know if it is special or mysterious, but I'm pretty sure IO is non-deterministic, non-computable, etc. In other words not the same as computation.
It's an ordinary value like everything else; it's on the same footing as [Char], Maybe Int, Int -> String, Bool, and so on. I see no difference between the list [1,2,3] :: [Int] and the action "pick a random number between 1 and 6" :: IO Int .
We'll have to agree to disagree - I see a fundamental difference. But that's ok, nothing says everybody has to agree on the One True Way to think about computing. Cheers, Gregg

On 2011-12-29 15:23, Gregg Reynolds wrote:
On Dec 29, 2011, at 1:21 PM, Heinrich Apfelmus wrote:
Why would IO Int be something special or mysterious?
I'm pretty sure IO is non-deterministic, non-computable, etc. In other words not the same as computation.
It's an ordinary value like everything else; it's on the same footing as [Char], Maybe Int, Int -> String, Bool, and so on. I see no difference between the list [1,2,3] :: [Int] and the action "pick a random number between 1 and 6" :: IO Int .
We'll have to agree to disagree - I see a fundamental difference.
You're misunderstanding the location of disagreement. We all know very well how IO Int is special. The example "pick a random number between 1 and 6" was unfortunate. I hope fmap read getLine :: IO Int serves better. The Haskell community says this expression indicates a "value". To be clear, fmap read getline has the same value wherever it is written in a program or however many times it is called, or however many different Int values it produces. This definition of 'value' is at the heart of how we understand Haskell to be referentially transparent and pure. You can disagree, but if you hold that this expression does not have a value until at execution time it produces an Int, then your unconventional terminology will lead to confusion. So what is the benefit of using Haskell? Isn't fmap read getline just as problematic as the C function gets() regardless of whether you call it pure? In Haskell, the type of fmap read getline prevents it from being used in arbitrary parts of the program, so the programmer or compiler can use the type to know whether a function is performing I/O or other effects.

Here's an alternative perspective to consider: consider some data structure, such as a queue. There are two ways you can implement this, one the imperative way, with mutators, and the other the purely functional way, with no destructive updates. The question then, I ask, is how easy does a programming language make it to write the data structure in the latter fashion? How easy is it for you to cheat? Edward Excerpts from Steve Horne's message of Wed Dec 28 12:39:52 -0500 2011:
This is just my view on whether Haskell is pure, being offered up for criticism. I haven't seen this view explicitly articulated anywhere before, but it does seem to be implicit in a lot of explanations - in particular the description of Monads in SBCs "Tackling the Awkward Squad". I'm entirely focused on the IO monad here, but aware that it's just one concrete case of an abstraction.
Warning - it may look like trolling at various points. Please keep going to the end before making a judgement.
To make the context explicit, there are two apparently conflicting viewpoints on Haskell...
1. The whole point of the IO monad is to support programming with side-effecting actions - ie impurity. 2. The IO monad is just a monad - a generic type (IO actions), a couple of operators (primarily return and bind) and some rules - within a pure functional language. You can't create impurity by taking a subset of a pure language.
My view is that both of these are correct, each from a particular point of view. Furthermore, by essentially the same arguments, C is also both an impure language and a pure one.
See what I mean about the trolling thing? I'm actually quite serious about this, though - and by the end I think Haskell advocates will generally approve.
First assertion... Haskell is a pure functional language, but only from the compile-time point of view. The compiler manipulates and composes IO actions (among other things). The final resulting IO actions are finally swallowed by unsafePerformIO or returned from main. However, Haskell is an impure side-effecting language from the run-time point of view - when the composed actions are executed. Impurity doesn't magically spring from the ether - it results from the translation by the compiler of IO actions to executable code and the execution of that code.
In this sense, IO actions are directly equivalent to the AST nodes in a C compiler. A C compiler can be written in a purely functional way - in principle it's just a pure function that accepts a string (source code) and returns another string (executable code). I'm fudging issues like separate compilation and #include, but all of these can be resolved in principle in a pure functional way. Everything a C compiler does at compile time is therefore, in principle, purely functional.
In fact, in the implementation of Haskell compilers, IO actions almost certainly *are* ASTs. Obviously there's some interesting aspects to that such as all the partially evaluated and unevaluated functions. But even a partially evaluated function has a representation within a compiler that can be considered an AST node, and even AST nodes within a C compiler may represent partially evaluated functions.
Even the return and bind operators are there within the C compiler in a sense, similar to the do notation in Haskell. Values are converted into actions. Actions are sequenced. Though the more primitive form isn't directly available to the programmer, it could easily be explicitly present within the compiler.
What about variables? What about referential transparency?
Well, to a compiler writer (and equally for this argument) an identifier is not the same thing as the variable it references.
One way to model the situation is that for every function in a C program, all explicit parameters are implicitly within the IO monad. There is one implicit parameter too - a kind of IORef to the whole system memory. Identifiers have values which identify where the variable is within the big implicit IORef. So all the manipulation of identifiers and their reference-like values is purely functional. Actual handling of variables stored within the big implicit IORef is deferred until run-time.
So once you accept that there's an implicit big IORef parameter to every function, by the usual definition of referential transparency, C is as transparent as Haskell. The compile-time result of each function is completely determined by its (implicit and explicit) parameters - it's just that that result is typically a way to look up the run-time result within the big IORef later.
What's different about Haskell relative to C therefore...
1. The style of the "AST" is different. It still amounts to the same thing in this argument, but the fact that most AST nodes are simply partially-evaluated functions has significant practical consequences, especially with laziness mixed in too. There's a deep connection between the compile-time and run-time models (contrast C++ templates). 2. The IO monad is explicit in Haskell - side-effects are only permitted (even at run-time) where the programmer has explicitly opted to allow them. 3. IORefs are explicit in Haskell - instead of always having one you can have none, one or many. This is relevant to an alternative definition of referential transparency. Politicians aren't considered transparent when they bury the relevant in a mass of the irrelevant, and even pure functions can be considered to lack transparency in that sense. Haskell allows (and encourages) you to focus in on the relevant - to reference an IORef Bool or an IORef Int rather than dealing with an IORef Everything.
That last sentence of the third point is my most recent eureka - not so long ago I posted a "Haskell is just using misleading definitions - it's no more transparent than C" rant, possibly on Stack Overflow. Wrong again :-(
So - what do you think?

Steve Horne wrote:
I haven't seen this view explicitly articulated anywhere before
See Conal Elliott's blog post The C language is purely functionalhttp://conal.net/blog/posts/the-c-language-is-purely-functional .

On 30/12/2011 00:16, Sebastien Zany wrote:
Steve Horne wrote:
I haven't seen this view explicitly articulated anywhere before
See Conal Elliott's blog post The C language is purely functional http://conal.net/blog/posts/the-c-language-is-purely-functional. Thanks - yes, that's basically the same point. More concise - so clearer, but not going into all the same issues - but still the same theme.

I wrote that post to point out the fuzziness that fuels many discussion
threads like this one. See also
http://conal.net/blog/posts/notions-of-purity-in-haskell/ and the comments.
I almost never find value in discussion about whether language X is
"functional", "pure", or even "referentially transparent", mainly because
those terms are used so imprecisely. In the notions-of-purity post, I
suggest another framing, as whether or not a language and/or collection of
data types is/are "denotative", to use Peter Landin's recommended
replacement for "functional", "declarative", etc. I included some quotes
and a link in that post. so people can track down what "denotative" means.
In my understanding, Haskell-with-IO is not denotative, simply because we
do not have a (precise/mathematical) model for IO. And this lack is by
design, as explained in the "toxic avenger" remarks in a comment on that
post.
I often hear explanations of what IO means (world-passing etc), but I don't
hear any consistent with Haskell's actual IO, which includes
nondeterministic concurrency. Perhaps the difficulties could be addressed,
but I doubt it, and I haven't seen claims pursued far enough to find out.
- Conal
On Thu, Dec 29, 2011 at 4:42 PM, Steve Horne
On 30/12/2011 00:16, Sebastien Zany wrote:
Steve Horne wrote:
I haven't seen this view explicitly articulated anywhere before
See Conal Elliott's blog post The C language is purely functionalhttp://conal.net/blog/posts/the-c-language-is-purely-functional .
Thanks - yes, that's basically the same point. More concise - so clearer, but not going into all the same issues - but still the same theme.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Conal Elliott wrote:
I wrote that post to point out the fuzziness that fuels many discussion threads like this one. See also http://conal.net/blog/posts/notions-of-purity-in-haskell/ and the comments.
I almost never find value in discussion about whether language X is "functional", "pure", or even "referentially transparent", mainly because those terms are used so imprecisely. In the notions-of-purity post, I suggest another framing, as whether or not a language and/or collection of data types is/are "denotative", to use Peter Landin's recommended replacement for "functional", "declarative", etc. I included some quotes and a link in that post. so people can track down what "denotative" means. In my understanding, Haskell-with-IO is not denotative, simply because we do not have a (precise/mathematical) model for IO. And this lack is by design, as explained in the "toxic avenger" remarks in a comment on that post.
I often hear explanations of what IO means (world-passing etc), but I don't hear any consistent with Haskell's actual IO, which includes nondeterministic concurrency. Perhaps the difficulties could be addressed, but I doubt it, and I haven't seen claims pursued far enough to find out.
Personally, the operational semantics given in SPJ's "Tackling the Awkward Squad" always struck me as an accurate model of how GHC performs IO. Best regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

On Fri, Dec 30, 2011 at 12:52 AM, Heinrich Apfelmus < apfelmus@quantentunnel.de> wrote:
Conal Elliott wrote:
I wrote that post to point out the fuzziness that fuels many discussion threads like this one. See also http://conal.net/blog/posts/** notions-of-purity-in-haskell/http://conal.net/blog/posts/notions-of-purity-in-haskell/and the comments.
I almost never find value in discussion about whether language X is "functional", "pure", or even "referentially transparent", mainly because those terms are used so imprecisely. In the notions-of-purity post, I suggest another framing, as whether or not a language and/or collection of data types is/are "denotative", to use Peter Landin's recommended replacement for "functional", "declarative", etc. I included some quotes and a link in that post. so people can track down what "denotative" means. In my understanding, Haskell-with-IO is not denotative, simply because we do not have a (precise/mathematical) model for IO. And this lack is by design, as explained in the "toxic avenger" remarks in a comment on that post.
I often hear explanations of what IO means (world-passing etc), but I don't hear any consistent with Haskell's actual IO, which includes nondeterministic concurrency. Perhaps the difficulties could be addressed, but I doubt it, and I haven't seen claims pursued far enough to find out.
Personally, the operational semantics given in SPJ's "Tackling the Awkward Squad" always struck me as an accurate model of how GHC performs IO.
Best regards, Heinrich Apfelmus
It might be accurate, but it's not denotational. - Conal

On Fri, Dec 30, 2011 at 8:12 AM, Conal Elliott
On Fri, Dec 30, 2011 at 12:52 AM, Heinrich Apfelmus < apfelmus@quantentunnel.de> wrote:
Conal Elliott wrote:
I wrote that post to point out the fuzziness that fuels many discussion threads like this one. See also http://conal.net/blog/posts/* *notions-of-purity-in-haskell/http://conal.net/blog/posts/notions-of-purity-in-haskell/and the comments.
I almost never find value in discussion about whether language X is "functional", "pure", or even "referentially transparent", mainly because those terms are used so imprecisely. In the notions-of-purity post, I suggest another framing, as whether or not a language and/or collection of data types is/are "denotative", to use Peter Landin's recommended replacement for "functional", "declarative", etc. I included some quotes and a link in that post. so people can track down what "denotative" means. In my understanding, Haskell-with-IO is not denotative, simply because we do not have a (precise/mathematical) model for IO. And this lack is by design, as explained in the "toxic avenger" remarks in a comment on that post.
I often hear explanations of what IO means (world-passing etc), but I don't hear any consistent with Haskell's actual IO, which includes nondeterministic concurrency. Perhaps the difficulties could be addressed, but I doubt it, and I haven't seen claims pursued far enough to find out.
Personally, the operational semantics given in SPJ's "Tackling the Awkward Squad" always struck me as an accurate model of how GHC performs IO.
It might be accurate, but it's not denotational. - Conal
Moreover, afaict, the "Awkward Squad" operational semantics tackles only a tiny fraction of the IO type. One of the strengths of Haskell IO is that it can be extended easily via the FFI. And I guess that strength is also a theoretical weakness in the sense that only a tiny fraction of the IO interface has even an operational semantics. - Conal

A perhaps acceptable notion of the property we want (purity etc.) is that all the extensions of the purely functional core language of Haskell (say the lazy lambda calculus extended with data constructors, etc) are _conservative_, that is all the equations that hold in the pure core language still hold in the extended language. For a part of Concurrent Haskell such a conservativity result is shown in D.Sabel , M. Schmidt-Schauß. On conservativity of Concurrent Haskell. Frank report 47, 2011. http://www.ki.informatik.uni-frankfurt.de/papers/frank/frank-47.pdf It also shows that with arbitrary use of unsafeInterleaveIO conservativity does not hold. And of course the result does not capture any IO-operation (only takeMVar, putMVar and spawning threads are considered), but it may be extended to more operations ... Just my two cents, David On 30.12.2011 02:07, Conal Elliott wrote:
I wrote that post to point out the fuzziness that fuels many discussion threads like this one. See also http://conal.net/blog/posts/notions-of-purity-in-haskell/ and the comments.
I almost never find value in discussion about whether language X is "functional", "pure", or even "referentially transparent", mainly because those terms are used so imprecisely. In the notions-of-purity post, I suggest another framing, as whether or not a language and/or collection of data types is/are "denotative", to use Peter Landin's recommended replacement for "functional", "declarative", etc. I included some quotes and a link in that post. so people can track down what "denotative" means. In my understanding, Haskell-with-IO is not denotative, simply because we do not have a (precise/mathematical) model for IO. And this lack is by design, as explained in the "toxic avenger" remarks in a comment on that post.
I often hear explanations of what IO means (world-passing etc), but I don't hear any consistent with Haskell's actual IO, which includes nondeterministic concurrency. Perhaps the difficulties could be addressed, but I doubt it, and I haven't seen claims pursued far enough to find out.
- Conal
On Thu, Dec 29, 2011 at 4:42 PM, Steve Horne
mailto:sh006d3592@blueyonder.co.uk> wrote: On 30/12/2011 00:16, Sebastien Zany wrote:
Steve Horne wrote:
I haven't seen this view explicitly articulated anywhere before
See Conal Elliott's blog post The C language is purely functional http://conal.net/blog/posts/the-c-language-is-purely-functional.
Thanks - yes, that's basically the same point. More concise - so clearer, but not going into all the same issues - but still the same theme.
_______________________________________________________
participants (25)
-
Antoine Latter
-
Artyom Kazak
-
AUGER Cédric
-
Bardur Arantsson
-
Bernie Pope
-
Chris Smith
-
Colin Adams
-
Conal Elliott
-
Dan Doel
-
Daniel Peebles
-
David Sabel
-
Donn Cave
-
Edward Z. Yang
-
Ertugrul Söylemez
-
Gregg Reynolds
-
Heinrich Apfelmus
-
Iustin Pop
-
James Cook
-
Jerzy Karczmarczuk
-
Ketil Malde
-
Scott Turner
-
Sebastien Zany
-
Steve Horne
-
Thiago Negri
-
Никитин Лев