
What I should have been told about upfront: - the syntax for an expression - the syntax for a block
Don't see your point.
- the adhoc syntax rules (how to distinguish among a tuple and a pharanthesized expression and how to find the start and end of a block for example )
Oh, that's pretty easy, parenthesized expression is not divided by a comma.
- what guarantees are made by the LANGUAGE that an IO action (such as do putStrLn "Hello world" ) is not performed twice
There are no such guarantees. If you write a = putStrLn "Hello world" main = do {a; a;} then your putStrLn would be performed twice. IO actions are first-class values, that's a feature, not a bug.
- the lambda expressions can be written (input) but cannot be printed (output)
Yes, since two different lambda expressions can denote the same function.
Here is some strange example: module Hugs where aa::Int aa=7 cc:: (Int->Int)->(Int->Int->Int)->Int->(Int->Int) cc a op b = \x-> case x of { _ | x==aa -> x+1 ; _-> a x `op` b } f::Int->Int f(1)=1 f(2)=2 f(_)=3 g::Int->Int g(1)=13 g(2)=23 g(_)=33 h::[Int->Int] -> Int ->Int h [] x = x h [rr] x = let { u=Hugs.f ; v=Hugs.g } in case rr of { u -> Hugs.g(x)+aa ; v -> Hugs.f(x)+aa ; _ ->rr (x) + aa } h (rr:ll) x = h [rr] x + h (ll) x What I don't understand is why I'm forced to use guards like x==aa in cc, when aa is clearly bounded (is 7) and why in function h, the bounded u and v become free variables in the case expression.
No, pattern matching bounds variables; if you write "case x of {aa -> ...} then aa becomes a LOCAL variable for the case statement, and shadows the global definition. The same applies to u and v in h, except that in this case local variables shadow upper-level local variables.

On Tue, 18 Dec 2007 10:29:43 +0200, Miguel Mitrofanov
What I should have been told about upfront: - the syntax for an expression - the syntax for a block
Don't see your point.
The point is the syntax is introduced as transformation of layout form to non layout form. As a user, I just want to be able to spot the basic components of a source file without thinking about transformation rules.
- the adhoc syntax rules (how to distinguish among a tuple and a pharanthesized expression and how to find the start and end of a block for example )
Oh, that's pretty easy, parenthesized expression is not divided by a comma.
Thanks! What is the end of a block ? What introduce new blocks ? Is this legal (`plus`) x y ? It's this a tuple ? ([a,b,c,d ]) ? etc.
- what guarantees are made by the LANGUAGE that an IO action (such as do putStrLn "Hello world" ) is not performed twice
There are no such guarantees. If you write
a = putStrLn "Hello world" main = do {a; a;}
then your putStrLn would be performed twice. IO actions are first-class values, that's a feature, not a bug.
What guarantees that by running the main, the string "Hello world" will be printed exactly twice ?
- the lambda expressions can be written (input) but cannot be printed (output)
Yes, since two different lambda expressions can denote the same function. I just want the sistem to be able to print one of these expressions !
Its this too much to ask ? I find it very strange that I can write a lambda expresion, but the system cannot.
No, pattern matching bounds variables; if you write "case x of {aa -> ...} then aa becomes a LOCAL variable for the case statement, and shadows the global definition. The same applies to u and v in h, except that in this case local variables shadow upper-level local variables.
Ok. ________ Information from NOD32 ________ This message was checked by NOD32 Antivirus System for Linux Mail Servers. part000.txt - is OK http://www.eset.com

Hi Cristian,
On Dec 18, 2007 10:53 AM, Cristian Baboi
- the lambda expressions can be written (input) but cannot be printed (output)
Yes, since two different lambda expressions can denote the same function. I just want the sistem to be able to print one of these expressions !
Its this too much to ask ? I find it very strange that I can write a lambda expresion, but the system cannot.
It's a trade-off. Haskell has as a design goal that you can use equational reasoning everywhere -- that if you have two ways of writing the same function, you can substitute one for the other in any expression, without changing the result of that expression. For example, since you can prove sum = foldl (+) 0 = foldr (+) 0 = last . scanl (+) 0 you can, in any place you use 'sum,' substitute any of these expressions without changing the result. You couldn't do this if you could write (show sum) and (show $ foldl (+) 0) and they would return different values. You could design the language differently, of course, but the Haskell designers want you -- and the compiler -- to be able to use equational reasoning everywhere -- so they disallow printing functions. - Benja

On Tue, 18 Dec 2007, Benja Fallenstein wrote:
Hi Cristian,
On Dec 18, 2007 10:53 AM, Cristian Baboi
wrote: - the lambda expressions can be written (input) but cannot be printed (output)
Yes, since two different lambda expressions can denote the same function. I just want the sistem to be able to print one of these expressions !
Its this too much to ask ? I find it very strange that I can write a lambda expresion, but the system cannot.
It's a trade-off. Haskell has as a design goal that you can use equational reasoning everywhere -- that if you have two ways of writing the same function, you can substitute one for the other in any expression, without changing the result of that expression. For example, since you can prove
sum = foldl (+) 0 = foldr (+) 0 = last . scanl (+) 0
Since this was discussed already here, I summed it up in: http://www.haskell.org/haskellwiki/Show_instance_for_functions

Hi Henning,
On Dec 18, 2007 3:53 PM, Henning Thielemann
Since this was discussed already here, I summed it up in: http://www.haskell.org/haskellwiki/Show_instance_for_functions
I find the discussion under "theoretical answer" unsatisfying. The property that a Show instance for functions would break is extensionality, and while extensionality is a desirable trait and matches the common mathematical intuitions, a system with intensional functions certainly isn't "unmathematical" or impure. Further, even with extensionality, we can (with compiler support) in principle have Show instances other than enumerating the graph. At least for simple non-recursive functions, showing the Böhm tree of the function could be useful (except that you loop forever if you encounter bottom somewhere, of course, instead of printing "bottom" as you would if you could print the actual Böhm tree). For example, id would be shown as "\a -> a," maybe would be shown as "\a b c -> case c of { Just d -> b d; Nothing -> a }," and all would be shown as "\a -> case a of { (b:c) -> case b of { False -> False; True -> case c of { (d:e) -> case d of { False -> False" et cetera ad infinitum. Of course, for functions on ints this would indeed reduce to enumerating the graph, printed as an infinite case expression. - Benja

On Dec 18, 2007 4:50 PM, Benja Fallenstein
Further, even with extensionality, we can (with compiler support) in principle have Show instances other than enumerating the graph.
Now that I said it, I'm starting to doubt we even need compiler support beyond what we have already. :-) I'm starting to think that a smattering of unsafePerformIO might be able to do the trick. I shall have to think on this :-) - Benja

On Tue, 18 Dec 2007, Benja Fallenstein wrote:
Hi Henning,
On Dec 18, 2007 3:53 PM, Henning Thielemann
wrote: Since this was discussed already here, I summed it up in: http://www.haskell.org/haskellwiki/Show_instance_for_functions
I find the discussion under "theoretical answer" unsatisfying. The property that a Show instance for functions would break is extensionality, and while extensionality is a desirable trait and matches the common mathematical intuitions, a system with intensional functions certainly isn't "unmathematical" or impure.
The mathematical definition of "function" I know of, says that functions are special relations, and relations are sets of pairs. Their is nothing about intension.

Hi Henning,
On Dec 18, 2007 5:17 PM, Henning Thielemann
The mathematical definition of "function" I know of, says that functions are special relations, and relations are sets of pairs. Their is nothing about intension.
That's the standard definition in set theory, but it's not the only mathematical definition of function. It also doesn't suffice for defining all Haskell functions-- consider data T = T (T -> Int) fn :: T -> Int fn _ = 7 We have (fn (T fn) == 7), so in the graph of 'fn' we must have a pair (T fn, 7). But if 'fn' is the same mathematical object as its graph, that would mean that the graph of 'fn' would have to contain a pair whose first element indirectly contains... the graph of fn! This sort of circularity is not allowed in standard ZFC set theory, so if we're going to be precise, we will have to choose a different representation for functions than their graphs. - Benja

On Tue, 18 Dec 2007, Benja Fallenstein wrote:
Hi Henning,
On Dec 18, 2007 5:17 PM, Henning Thielemann
wrote: The mathematical definition of "function" I know of, says that functions are special relations, and relations are sets of pairs. Their is nothing about intension.
That's the standard definition in set theory, but it's not the only mathematical definition of function. It also doesn't suffice for defining all Haskell functions-- consider
data T = T (T -> Int)
fn :: T -> Int fn _ = 7
We have (fn (T fn) == 7), so in the graph of 'fn' we must have a pair (T fn, 7). But if 'fn' is the same mathematical object as its graph, that would mean that the graph of 'fn' would have to contain a pair whose first element indirectly contains... the graph of fn!
This sort of circularity is not allowed in standard ZFC set theory, so if we're going to be precise, we will have to choose a different representation for functions than their graphs.
I see. I'm also wondering what 'total function' and 'partial function' might mean in Haskell, since values can be partially defined. Is Just undefined defined or undefined and is const (Just undefined) a total or a partial function?

Hi Paul,
On Dec 18, 2007 5:18 PM, Paul Hudak
If the semantics of a language says that a function f is equivalent to a function g, but there is a function h such that h(f) is not equivalent to h(g), then h cannot be a function.
Sure.
Therefore that language cannot be a (purely) functional language.
That is the pure and simple reason why functions are not Showable in Haskell.
Not so fast :-) Caveat one, there may be useful ways to for functions to implement Show that don't conflict with extensionality (i.e., the property that two functions are equal if they yield the same results for all inputs). Caveat two, we generally assume extensionality when reasoning about Haskell, but it's entirely possible to give a semantics for Haskell that doesn't assume extensionality. IMHO, a good answer to the question why functions aren't showable in Haskell needs to explain why we prefer our semantics to be extensional, not say that by god-given fiat, Haskell is extensional, so we can't show functions. - Benja

Benja Fallenstein wrote:
Not so fast :-)
Caveat one, there may be useful ways to for functions to implement Show that don't conflict with extensionality (i.e., the property that two functions are equal if they yield the same results for all inputs).
Sure, and I suppose one way to do this is to put the show function for functions into the IO monad -- then you can't inspect the results. But if you want to inspect the result, then I have no idea how to do this.
Caveat two, we generally assume extensionality when reasoning about Haskell, but it's entirely possible to give a semantics for Haskell that doesn't assume extensionality. IMHO, a good answer to the question why functions aren't showable in Haskell needs to explain why we prefer our semantics to be extensional, not say that by god-given fiat, Haskell is extensional, so we can't show functions.
Well, my caveat was that the Haskell designers wanted it this way. So you are essentially rejecting my caveat, rather than creating a new one. :-) -Paul

On Dec 18, 2007 6:01 PM, Paul Hudak
Well, my caveat was that the Haskell designers wanted it this way. So you are essentially rejecting my caveat, rather than creating a new one. :-)
I mean, I reject the answer "They wanted it this way" because I think the answer should be, "They wanted it this way because They looked at substituting equals under a lambda, and They saw it was good" ;-)
Caveat one, there may be useful ways to for functions to implement Show that don't conflict with extensionality (i.e., the property that two functions are equal if they yield the same results for all inputs).
Sure, and I suppose one way to do this is to put the show function for functions into the IO monad -- then you can't inspect the results. But if you want to inspect the result, then I have no idea how to do this.
If you can show and enumerate the argument type and show the result type of a function, one way is to enumerate the graph of the function. The wiki page gives the example, Prelude> \x -> x+x functionFromGraph [(0,0), (1,2), (2,4), (3,6), Interrupted. If you have special compiler support, and consider a fragment of Haskell that contains only functions -- i.e., no algebraic data types, no Ints etc. (it's kind of a boring fragment!, but you can have Church numbers) --, you can reduce the function to head normal form. Head normal form looks like this: \VAR1 VAR2 ... VARm -> VARi EXPR1 ... EXPRn and there is a reduction strategy that finds the head normal form of an arbitrary expression if there is one; a proof that if there isn't one, the expression denotes bottom; and a proof that if you have two HNFs, and they differ in the part before EXPR1 or differ in the number of EXPRjs, these HNFs denote different values. Therefore, when you have reduced the function to HNF, you can print "\VAR1 VAR2 ... VARm -> VARi " (or more precisely, you can write a lazy 'show' that yields the above characters as soon as it has computed the HNF). Then, you go on to recursively compute the HNF of EXPR1, and you show that inside parantheses. Some examples: show (\x -> x) == "\a -> a" show (.) == "\a b c -> a (b c)" (let fix f = f (fix f) in show fix) == "\a -> a (a (a (a (a................. [Unless I'm making some stupid mistake] It's well-established that this is computable and doesn't break extensionality (i.e., that applying this show to two functions with the same extension will give the same result -- or conversely, if show gives different results for two functions, there are arguments for which these functions yield different results). By itself, this isn't very interesting, but I *think* you should be able to add algebraic data types and case expressions to this fragment of Haskell and still do "essentially" the same thing. Then, you could show, for example, show either == "\a b c -> case c of { Left d -> a d; Right e -> b e }" - Benja

Hi Paul,
On Dec 19, 2007 6:54 AM, Paul Hudak
Your version of the answer is in fact correct, but is just an elaboration of the original one. So, I don't see what your point is...
Ok, sorry, I'll try again... I'm trying to say that in my opinion, it's important to include the elaboration if you want to give a *useful* answer to "why can't I print functions." :)
If you can show and enumerate the argument type and show the result type of a function, one way is to enumerate the graph of the function.
Yes, but this requires a STANDARD way to do this -- meaning that the underlying domains are enumerable in a standard way. I don't think that is always possible.
It isn't always, no; in Haskell, there's no way to enumerate the instances of (IO Int), for example. But of course, you can't show (IO Int) in the first place, so I guess there's no expectation that you should be able to show functions with (IO Int) arguments, either. Function domains also aren't enumerable in general, although you could simply enumerate all functions writable in Haskell, and not care about duplicates. But it seems very unlikely anyway that printing higher-order functions in this way would be *practical*.
And of course you may have an infinite graph, whereas the function itself is finite.
(you mean that the function term is finite, I suppose) Yes, but you can show infinite lists, too -- resulting in an infinite String being returned by 'show.'
Regarding the rest of your message: I don't see how this helps, since some terms do not have head-normal forms.
But these terms denote bottom. Compare (show (1:2:_|_)); the behavior would be similar.
Even in the pure lambda calculus there are terms that denote the same value but that are not convertible to one another.
Such terms would return the same *infinite* String in this approach. You couldn't write a program to test whether they're equal; but you can't write a program that tests whether two arbitrary infinite lists are equal, either.
It seems that at best this approach would yield only partial success.
Oh, that's certainly true, in the sense that showing functions in this way would often not be as practical as one might hope for -- the worst problem being that recursive functions will often have infinite representations. Still, in my opinion, there is a difference between "the theory says you can't show functions" and "from the theoretical perspective, there is an elegant way to show functions, but it would be a lot of work to implement and the result wouldn't be as practical as you're hoping for." Although I admit it's more of a theoretical difference than a practical one. :-) - Benja

Cristian Baboi wrote:
On Tue, 18 Dec 2007 10:29:43 +0200, Miguel Mitrofanov
wrote: What I should have been told about upfront: - the syntax for an expression - the syntax for a block
Don't see your point.
The point is the syntax is introduced as transformation of layout form to non layout form. As a user, I just want to be able to spot the basic components of a source file without thinking about transformation rules.
Well, a "block" isn't really a unified syntactic unit. The layout rule is used for do {} expressions, which context they are expression syntax, but also in module, let, and where declarations in which context they are declaration syntax, and case expressions in which case they are, well, case alternatives; a little like declarations, I suppose. Since layout is optional, it's often defined simply by the translation into explicit {} and ;. On the other hand, if there are specific areas of ambiguity which have confused you let us know, and we'll clarify.
- the adhoc syntax rules (how to distinguish among a tuple and a pharanthesized expression and how to find the start and end of a block for example )
Oh, that's pretty easy, parenthesized expression is not divided by a comma.
Thanks! What is the end of a block ? What introduce new blocks ?
I'm not sure what you mean by a block here, so I find it hard to answer that. The end of a layout block is when a line is indented less than the first line of the layout.
Is this legal (`plus`) x y ?
No.
It's this a tuple ? ([a,b,c,d ]) ?
No, that's a list of four elements, in some parentheses which, in this context, make no semantic difference. An expression in parentheses is one of two things: (a) a tuple, if it is of the form (X,Y,Z,...) where the , are understood to be at the "top level" syntactically (b) a simple expression which has been parenthesised just to aid clarity or achieve correct precedence.
- what guarantees are made by the LANGUAGE that an IO action (such as do putStrLn "Hello world" ) is not performed twice
There are no such guarantees. If you write
a = putStrLn "Hello world" main = do {a; a;}
then your putStrLn would be performed twice. IO actions are first-class values, that's a feature, not a bug.
What guarantees that by running the main, the string "Hello world" will be printed exactly twice ?
The semantics of IO, and the guarantees of the runtime. IO specifies that (>>) means "compose two actions to make a larger action which does the first actions, then the second action". [do {a; a;} is notation for a >> a] The RTS specifies that the "main" action is performed exactly once.
- the lambda expressions can be written (input) but cannot be printed (output)
Yes, since two different lambda expressions can denote the same function. I just want the sistem to be able to print one of these expressions !
Its this too much to ask ? I find it very strange that I can write a lambda expresion, but the system cannot.
Haskell doesn't contain a code representation natively. It is not a "homoiconic" language. Just like C, C++, Java, Python, Perl, and Ruby, the compiler/interpreter is free to transform code into some more efficient form for running (including transformation all the way to native code, which is what ghc does) and once it has done so, it retains no information about the "shape of" the source code which yielded the function. Jules

Thank you very much!
On Tue, 18 Dec 2007 12:17:54 +0200, Jules Bean
Cristian Baboi wrote:
On Tue, 18 Dec 2007 10:29:43 +0200, Miguel Mitrofanov
wrote:
- what guarantees are made by the LANGUAGE that an IO action (such as do putStrLn "Hello world" ) is not performed twice
There are no such guarantees. If you write
a = putStrLn "Hello world" main = do {a; a;}
then your putStrLn would be performed twice. IO actions are first-class values, that's a feature, not a bug. What guarantees that by running the main, the string "Hello world" will be printed exactly twice ?
The semantics of IO, and the guarantees of the runtime.
IO specifies that (>>) means "compose two actions to make a larger action which does the first actions, then the second action".
[do {a; a;} is notation for a >> a]
The RTS specifies that the "main" action is performed exactly once.
Is this dependent on the implementation (if I use GHC or Hugs) or is something that the language say ? Aside: I tried something like this in WinHugs: do { xxx<-getLine ; putStrLn xxx } and pressed two keys at once for the "getLine" action. The result I've got was an "infinite" loop !!!
- the lambda expressions can be written (input) but cannot be printed (output)
Yes, since two different lambda expressions can denote the same function. I just want the sistem to be able to print one of these expressions ! Its this too much to ask ? I find it very strange that I can write a lambda expresion, but the system cannot.
Haskell doesn't contain a code representation natively. It is not a "homoiconic" language. Just like C, C++, Java, Python, Perl, and Ruby, the compiler/interpreter is free to transform code into some more efficient form for running (including transformation all the way to native code, which is what ghc does) and once it has done so, it retains no information about the "shape of" the source code which yielded the function.
Thank you. ________ Information from NOD32 ________ This message was checked by NOD32 Antivirus System for Linux Mail Servers. part000.txt - is OK http://www.eset.com

Cristian Baboi wrote: What guarantees that by running the main, the string "Hello world"
will be printed exactly twice ?
The semantics of IO, and the guarantees of the runtime.
IO specifies that (>>) means "compose two actions to make a larger action which does the first actions, then the second action".
[do {a; a;} is notation for a >> a]
The RTS specifies that the "main" action is performed exactly once.
Is this dependent on the implementation (if I use GHC or Hugs) or is something that the language say ?
It's something the language says. IO is part of the runtime, its semantics are defined.
Aside: I tried something like this in WinHugs:
do { xxx<-getLine ; putStrLn xxx }
and pressed two keys at once for the "getLine" action.
The result I've got was an "infinite" loop !!!
If that code loops you have a bug (in hugs?) it certainly shouldn't. It will wait until you press return before it prints anything, though. Jules

On Tue, 2007-12-18 at 12:53 +0200, Cristian Baboi wrote:
The semantics of IO, and the guarantees of the runtime.
IO specifies that (>>) means "compose two actions to make a larger action which does the first actions, then the second action".
[do {a; a;} is notation for a >> a]
The RTS specifies that the "main" action is performed exactly once.
Is this dependent on the implementation (if I use GHC or Hugs) or is something that the language say ?
Part of the language. You do get your guarantee written in blood. -Peter
participants (7)
-
Benja Fallenstein
-
Cristian Baboi
-
Henning Thielemann
-
Jules Bean
-
Miguel Mitrofanov
-
Paul Hudak
-
Peter Lund