Indentation of If-Then-Else

I object strongly to the proposal http://hackage.haskell.org/trac/haskell-prime/wiki/DoAndIfThenElse because it solves problems with syntactic sugar with even more sugar, where no sugar is needed at all. In order to solve the trouble I propose enhancements to teachers, compilers and standard libraries: 1. 'if' syntax should be teached as if a then b else c This indentation makes pretty clear, what is condition, and what is the result in both cases. It just resembles case a of True -> b False -> c . 2. Add 'if :: Bool -> a -> a -> a' or '(?) :: Bool -> (a,a) -> a' or both to the standard library, as discussed in the thread starting with http://www.haskell.org/pipermail/haskell-cafe/2006-July/016914.html 3. If a compiler suspects that a parsing problem is related to 'do' and 'if' it should suggest indentation if a then b else c or even better, the usage of if- or (?)-function. So, please add this to the 'Cons' list.

Hi
In order to solve the trouble I propose enhancements to teachers, compilers and standard libraries: 1. 'if' syntax should be teached as if a then b else c
I love being able to ident if however I like: if a then b else c Where b is a trivial case, and c is the hard one. if a then b else c Exactly like C. Clearly delimiting the b and teh c, by putting space between them. if a then b else c Short one if a then b else c I also occasionally use this. It seems better to change the language so it works like _everyone_ expects it does, rather than become syntax dictators. It's hard enough persuading people to move from C, but when you tell someone that their perfectly unambiguous sytnax is "wrong", they aren't going to be amused. Thanks Neil

On Sun, 22 Oct 2006, Neil Mitchell wrote:
It seems better to change the language so it works like _everyone_ expects it does, rather than become syntax dictators. It's hard enough persuading people to move from C, but when you tell someone that their perfectly unambiguous sytnax is "wrong", they aren't going to be amused.
I don't know why it is so important to convince every C programmers of Haskell. Making a language fit to everyone's taste eventually led to what is today known as Perl.

It seems better to change the language so it works like _everyone_ expects it does, rather than become syntax dictators. It's hard enough persuading people to move from C, but when you tell someone that their perfectly unambiguous sytnax is "wrong", they aren't going to be amused.
I don't know why it is so important to convince every C programmers of Haskell. Making a language fit to everyone's taste eventually led to what is today known as Perl.
Ok, a more personal argument. I hate that this language won't allow _me_ to lay out _my_ if's as _I_ want them! Especially as the rest of Haskell lets the programmer choose the best layout, and just keeps hands off. I can be convinced through logical arguments that all the other restrictions/features of Haskell are a good idea, but this one doesn't have a good reason associated with it. Thanks Neil

On 10/22/06, Neil Mitchell
Hi
In order to solve the trouble I propose enhancements to teachers, compilers and standard libraries: 1. 'if' syntax should be teached as if a then b else c
I love being able to ident if however I like:
I agree with Henning. Reserved syntax for "if" is totally unnecessary in Haskell. It requires three keywords. Its costs (syntax wise) seem much greater than its benefits (which are practically zero). I don't think that it makes sense to make further complicate this unnecessary syntax. Instead, why not work on eliminating the special syntax altogether? For example, make the "then" and "else" keywords optional and schedule them for removal in the next revision. Hennings suggestion that implementations suggest the correct indention is a good one. The existing Haskell implementations do not do a good job diagnosing layout problems. As far as I know, they don't even try to recover from syntax errors at all. I would like to change both of these problems. The proposed layout changes (NondecreasingIndention and DoAndifThenElse and the one for case) should be postponed until more work on error diangosis and recovery has been done. Regards, Brian

These suggestions would, firstly, break lots of code for little
benefit, and secondly, make code harder to read.
The 'then' and 'else' visually separate the parts of the
if-expression, and serve to guide one's eyes when reading code
silently, and one's words when speaking it aloud. Certainly, one can
define a conditional function if' and decide to use that everywhere to
avoid typing 'then' and 'else', but how many people do this? My guess
is that almost nobody does this because it only serves to make code
harder to read. Also, one could simply use case-expressions, but
people still use if-expressions not just for compactness (the
difference there is rather slight), but because they don't read the
same way.
Haskell is not some minimal programming language core intended to be
optimised for the simplest possible machine parsing and fewest
desugaring steps. It's optimised for human readability and
convenience. We have things like do-notation, which while they are not
strictly necessary, serve to filter repetitious noise, while
delimiting things clearly for the reader, and present an expression in
a form which is (often) closer to one's mental model of the meaning.
If-expressions match very closely with the way in which one reads
their meaning in natural language, are not so difficult for machines
to handle, (the current implementations seem to be having no trouble
with them) and don't really complicate the language definition all
that much. Please don't attack non-problems.
On the other hand, I agree that this is usually the "correct" way to
layout an if-expression which does not neatly fit on to one line, or
where the results are at all lengthy. However, given the fact that
there's no chance of ambiguity anyway, I don't consider this to be
something for the language itself to enforce. *That* would be
needlessly overcomplicating the language definition. It's something
for editors to help the user with, perhaps, and it's something for
teachers of the language to point out. Otherwise, it's just not all
that important, let people use whatever style they like best in
whatever circumstance. Neil pointed out lots of reasonable
possibilities, here's another:
if long && complicated condition
then 0 else 42
I don't use that form all that often myself, but it looks reasonable,
and I certainly wouldn't want the compiler to reject it.
- Cale
On 22/10/06, Brian Smith
I agree with Henning. Reserved syntax for "if" is totally unnecessary in Haskell. It requires three keywords. Its costs (syntax wise) seem much greater than its benefits (which are practically zero). I don't think that it makes sense to make further complicate this unnecessary syntax. Instead, why not work on eliminating the special syntax altogether? For example, make the "then" and "else" keywords optional and schedule them for removal in the next revision.
Hennings suggestion that implementations suggest the correct indention is a good one. The existing Haskell implementations do not do a good job diagnosing layout problems. As far as I know, they don't even try to recover from syntax errors at all. I would like to change both of these problems. The proposed layout changes (NondecreasingIndention and DoAndifThenElse and the one for case) should be postponed until more work on error diangosis and recovery has been done.
Regards, Brian
_______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime

Henning Thielemann wrote:
1. 'if' syntax should be teached as if a then b else c This indentation makes pretty clear, what is condition, and what is the result in both cases. It just resembles case a of True -> b False -> c .
The problem with this is that in a do block it forces me to use /two/ indentation levels, instead of one, e.g.
if test then do something more else do anotherthing stillmore
versus
if test then do something more else do anotherthing stillmore
Ben

On 10/22/06, Benjamin Franksen
The problem with this is that in a do block it forces me to use /two/ indentation levels, instead of one, e.g.
+1. This is also my primary reason for wanting the sugar. In some
code, indentation is at a premium. Forcing the extra indentation does
nothing to improve readability, and is a common frustration. The point
of all sugar is to reduce frustration, so I am strongly in favor of
the new syntax.
--
Taral

Dear All, Henning Thielmann wrote:
I object strongly to the proposal http://hackage.haskell.org/trac/haskell-prime/wiki/DoAndIfThenElse because it solves problems with syntactic sugar with even more sugar, where no sugar is needed at all.
In order to solve the trouble I propose enhancements to teachers, compilers and standard libraries: 1. 'if' syntax should be teached as if a then b else c This indentation makes pretty clear, what is condition, and what is the result in both cases.
People obviously have different opinions here, and I'd say there are perfectly reasonable arguments for a number of different styles of indentation. As the discussion following Henning's mail has demonstrated. The background to the proposal was that Haskell 98 prevents an arguably reasonable style of indentation, and that this has turned out to be a problem in practice: i.e. it tends to trip up a lot of unsuspecting people, in particular beginners. Yes, one can argue that they should learn "the right way", but this is really a very minor detail that many think would be best if people didn't have to worry about in the first place. The proposal is actually very lightweight (just allow an optional ";" in the appropriate place), and thus it is not even a question about new "syntactic sugar". At least not according to my understanding of the term. Also, it does not complicate the (already complicated) layout rules further, which is quite important. If I recall correctly, the proposal was implemented in GHC (and JHC?) shortly after it had been put forward, with very little effort indeed, and has not caused any ill side effects that I'm aware of.
3. If a compiler suspects that a parsing problem is related to 'do' and 'if' it should suggest indentation if a then b else c or even better, the usage of if- or (?)-function.
As a matter of principle, I don't think a language standard should say much if anything about how a conforming compiler or interpreter should report errors. We can argue the pros and cons of the existing "if" syntax, but I don't think anyone is seriously proposing that it be dropped from Haskell' (that would break an awful lot of code for very little gain). Having additional functions that accomplish the same thing as "if" does not seem all that appealing to me at least.
So, please add this to the 'Cons' list.
Henning, I'm afraid I don't quite understand what the conses are? Could you clarify the concrete ill effects of the proposal, please? Best, /Henrik -- Henrik Nilsson School of Computer Science and Information Technology The University of Nottingham nhn@cs.nott.ac.uk This message has been checked for viruses but the contents of an attachment may still contain software viruses, which could damage your computer system: you are advised to perform your own checks. Email communications with the University of Nottingham may be monitored as permitted by UK legislation.

On Mon, Oct 23, 2006 at 01:36:41PM +0100, Henrik Nilsson wrote:
The background to the proposal was that Haskell 98 prevents an arguably reasonable style of indentation, and that this has turned out to be a problem in practice: i.e. it tends to trip up a lot of unsuspecting people, in particular beginners.
Yes, one can argue that they should learn "the right way", but this is really a very minor detail that many think would be best if people didn't have to worry about in the first place.
It is not even clear to me that there is a single right way. the proper indentation style for if statements depends on both context, the subexpressions and the structure of the term you want to emphasize/subdue.
The proposal is actually very lightweight (just allow an optional ";" in the appropriate place), and thus it is not even a question about new "syntactic sugar". At least not according to my understanding of the term. Also, it does not complicate the (already complicated) layout rules further, which is quite important.
If I recall correctly, the proposal was implemented in GHC (and JHC?) shortly after it had been put forward, with very little effort indeed, and has not caused any ill side effects that I'm aware of.
Yes. It was implemented in jhc within a couple hours of the idea being proposed (the implementation itself taking a couple minutes). all of jhc's standard libraries compliled without problem with the extension enabled and no issues have arisen from it always being enabled. John -- John Meacham - ⑆repetae.net⑆john⑈

On Mon, 23 Oct 2006, Henrik Nilsson wrote:
The background to the proposal was that Haskell 98 prevents an arguably reasonable style of indentation, and that this has turned out to be a problem in practice: i.e. it tends to trip up a lot of unsuspecting people, in particular beginners.
I like to convince other programmers of Haskell by telling them, that Haskell can abstract so powerful, that you can define your own control structures, and consequently most control structures are actually library functions. Two people who I explained it this way asked me, why Haskell needs the special if-then-else syntax although an equivalent function can be provided in an obvious way. "if-then-else" syntax is an exception from a simple concept (functions!), which confuses people. They think there must be something special in "if-then-else", because it is not just a function from the standard libraries. In contrast to that, 'case' is something special because of its pattern matching.
Yes, one can argue that they should learn "the right way", but this is really a very minor detail that many think would be best if people didn't have to worry about in the first place.
There are too much of these minor details.
If I recall correctly, the proposal was implemented in GHC (and JHC?) shortly after it had been put forward, with very little effort indeed, and has not caused any ill side effects that I'm aware of.
... still not. What about other compiler writers, text editor developers, language tool writers? They all have to respect every small exception. I'm currently concerned with HTML - much more exceptions than rules. This is no fun, and Haskell's syntax will go the same way. Let if-then-else in Haskell for compatibility reasons, and try to get rid of it until Haskell-2. But do not endorse its use by new extensions.
3. If a compiler suspects that a parsing problem is related to 'do' and 'if' it should suggest indentation if a then b else c or even better, the usage of if- or (?)-function.
As a matter of principle, I don't think a language standard should say much if anything about how a conforming compiler or interpreter should report errors.
I only want to point out how to solve the initial problem. I make suggestions about compiler messages, because I want to show, that the problems can be solved without adding more syntax exceptions.
So, please add this to the 'Cons' list.
Henning, I'm afraid I don't quite understand what the conses are? Could you clarify the concrete ill effects of the proposal, please?
Cons are: The sketched problem with indentation can be solved without touching the language. The syntax extension is unnecessary, thus complicates all language tools without need.

On 23/10/06, Henning Thielemann
I like to convince other programmers of Haskell by telling them, that Haskell can abstract so powerful, that you can define your own control structures, and consequently most control structures are actually library functions. Two people who I explained it this way asked me, why Haskell needs the special if-then-else syntax although an equivalent function can be provided in an obvious way. "if-then-else" syntax is an exception from a simple concept (functions!), which confuses people. They think there must be something special in "if-then-else", because it is not just a function from the standard libraries. In contrast to that, 'case' is something special because of its pattern matching.
Just tell them that the special thing about it is purely syntactical: you get to delimit the 'then' and 'else' parts more clearly. [...snip...]
... still not. What about other compiler writers, text editor developers, language tool writers? They all have to respect every small exception. I'm currently concerned with HTML - much more exceptions than rules. This is no fun, and Haskell's syntax will go the same way. Let if-then-else in Haskell for compatibility reasons, and try to get rid of it until Haskell-2. But do not endorse its use by new extensions.
Of course I disagree with this course for all the reasons I stated above. The whole point of having high level programming languages is so that you can put more work into the tools so that the end user doesn't have to work as hard. One shouldn't ask "What's easiest to parse?" but "What's easiest to read and write?". [...snip...]
Cons are: The sketched problem with indentation can be solved without touching the language.
The problem was that something with indentation that worked in one context, when placed in the context of a do-block, stopped working. I don't tend to have that problem myself, as I follow a different custom for indentation, but when newcomers to the language run into such things, it can be annoying for them, and it looks like something that ought to work anyway.
The syntax extension is unnecessary, thus complicates all language tools without need.
Complicates? It's two optional semicolons. This should really add _at worst_ a few lines of code to anything parsing Haskell properly, it's an absolutely trivial change.

On Mon, 23 Oct 2006, Cale Gibbard wrote:
Of course I disagree with this course for all the reasons I stated above. The whole point of having high level programming languages is so that you can put more work into the tools so that the end user doesn't have to work as hard. One shouldn't ask "What's easiest to parse?" but "What's easiest to read and write?".
A good many tools can, of course, get by on a reversible desugaring. It seems to me that this'd be a sensible candidate for a library. -- flippa@flippac.org 'In Ankh-Morpork even the shit have a street to itself... Truly this is a land of opportunity.' - Detritus, Men at Arms

On Mon, 23 Oct 2006, Philippa Cowderoy wrote:
On Mon, 23 Oct 2006, Cale Gibbard wrote:
Of course I disagree with this course for all the reasons I stated above. The whole point of having high level programming languages is so that you can put more work into the tools so that the end user doesn't have to work as hard. One shouldn't ask "What's easiest to parse?" but "What's easiest to read and write?".
A good many tools can, of course, get by on a reversible desugaring. It seems to me that this'd be a sensible candidate for a library.
I have tried to sum up my points about if-then-else syntax and answer some question that were arised by others. Even if it doesn't influence the decision about the optional semicolon, it will well become of interest once HaskellTwo design procedure starts. http://haskell.org/haskellwiki/If-then-else ======================================================================= Replace syntactic sugar by a function For processing conditions, the if-then-else syntax was defined in Haskell98. However it could be simply replaced by the function if' with if' :: Bool -> a -> a -> a if' True x _ = x if' False _ y = y Unfortunately there is no such function in the Prelude. Advocacy Advantages The advantages of the function if' over the syntax if-then-else are the same like for all such alternatives. So let me repeat two important non-syntactic strengths of Haskell: types: classification, documentation higher order functions: combinators If if' would be a regular function, each language tool can process it without hassle. Haddock can generate documentation for it, a text editor can make suggestions for values to insert, Hoogle can retrieve that function. For example, the Hoogle query [Bool] -> [a] -> [a] -> [a] may return zipWith3 if' Use cases Each of the following functions could be defined in terms of if'. Actually, they do not even need to be in Prelude because they can be constructed so easily. That function is harder to explain in English, than by its implementation. :-) zipIf :: [Bool] -> [a] -> [a] -> [a] zipIf = zipWith3 if' Select a member of a pair. This resembles the cond?x:y operation of the C language. infixr 1 ?: (?:) :: Bool -> (a,a) -> a (?:) = uncurry . if'
From a list of expressions choose the one, whose condition is true. The first parameter is the default value. It is returned if no condition applies.
select :: a -> [(Bool, a)] -> a select = foldr (uncurry if') See Case. Why add this function to Prelude? Actually people could define if' in each module, where they need it, or import it from a Utility module, that must be provided in each project. Both solutions are tedious and contradict to modularization and software re-usage. The central question is, whether if' is an idiom, that is so general that it should be in the Prelude, or not. I think it is, otherwise it wouldn't have get a special syntax. If-Then-Else vs. guards Actually if-then-else isn't used that often today. Most programmers gave it up in favor of guards. This practice has its own drawbacks, see Syntactic sugar/Cons and Things to avoid. Is If-Then-Else so important? Counting if-then-else or if' in today's Haskell programs isn't a good measure for the importance a if' function, because frequently guards are used instead of if-then-else there is no standard function, and this let people stick to work-arounds. What is so bad about the if-then-else sugar? Since syntactic sugar introduces its own syntactic rules, it is hard to predict how it interferes with other syntactic constructs. This special syntax for instance led to conflicts with do notation. A syntactic extension to solve this problem is proposed for Haskell'. It is not known what conflicts this extension might cause in future. Why breaking lots of old and unmaintained code? Haskell without if-then-else syntax makes Haskell more logical and consistent. There is no longer confusion to beginners like: "What is so special about if-then-else, that it needs a separate syntax? I though it could be simply replaced by a function. Maybe there is some subtlety that I'm not able to see right now." There is no longer confusion with the interference of if-then-else syntax with do notation. Removing if-then-else simplifies every language tool, say compiler, text editor, analyzer and so on. If we arrive at Haskell two some day, (http://haskell.org/hawiki/HaskellTwo) it will certainly be incompatible to former Haskell versions. This does not mean, that old code must be thrown away. There should be one tool, that converts Haskell 98 and Haskell' to Haskell-2. Having one tool for this purpose is better than blowing all language tools with legacy code. Syntactic replacements like if-then-else syntax to if' function should be especially simple. Summary Light proposal, compatible with Haskell 98: Add if' to the Prelude, maybe with a different name. Full proposal, incompatible with Haskell 98 and Haskell': Additionally remove if-then-else syntax See also Syntactic sugar/Cons Things to avoid/Discussion Objections Haskell is not intended to be a minimalistic language, but to be one, that is easy to read. if-then-else resembles a phrase from English language. It shows clearly which expression is returned on a fulfilled condition, and which one is returned for an unsatisfied condition. It is thus easier to read. The special syntax saves parentheses around its arguments. If properly indented, like if a then b else c or if a then b else c then there is no conflict with the do-notation.

Henning Thielemann writes:
Actually if-then-else isn't used that often today. Most programmers gave it up in favor of guards.
I question both these statements. Can you cite some evidence here?
--
David Menendez

On Tue, 24 Oct 2006, Dave Menendez wrote:
Henning Thielemann writes:
Actually if-then-else isn't used that often today. Most programmers gave it up in favor of guards.
I question both these statements. Can you cite some evidence here?
I have not made statistics. My subjective impression from reading programs of others is that there are many guards, and only few if-then-elses. If you are one of the if-users, then hi, I'm the other one! ;-)

On 10/24/06, Henning Thielemann
For processing conditions, the if-then-else syntax was defined in Haskell98. However it could be simply replaced by the function if' with
if' :: Bool -> a -> a -> a if' True x _ = x if' False _ y = y
I support the inclusion of if' because it is the Bool catamorphism,
but I would structure its arguments as (a -> a -> Bool -> a) because
that facilitates use of the currying.
I don't think it's an effective replacement for if/then/else because
using if' usually requires a bunch of harder-to-read () instead of
nice delimiting reserved words.
--
Taral

Hello Taral, Tuesday, October 24, 2006, 8:52:47 PM, you wrote:
if' :: Bool -> a -> a -> a if' True x _ = x if' False _ y = y
I support the inclusion of if' because it is the Bool catamorphism, but I would structure its arguments as (a -> a -> Bool -> a) because that facilitates use of the currying.
i has such function in my program. it just like 'either' and 'maybe' functions, so i named it 'bool'. of course, it's used for partial applications only -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Yes, one can argue that they should learn "the right way", but this is really a very minor detail that many think would be best if people didn't have to worry about in the first place.
There are too much of these minor details.
Yes! Which is why this fix is good, as it means people don't have to worry about that particular detail!
I'm currently concerned with HTML - much more exceptions than rules. This is no fun, and Haskell's syntax will go the same way. Let if-then-else in Haskell for compatibility reasons,
Many would agree that Haskell is getting large and complicated, but I suspect most people would not blame if-then-else. It is true, of course, that special syntax for if-then-else is not needed. But the same can be said for most of Haskell. One could argue that all you really need is a very small core language. So it boils down to finding the right balance between convenience, readability, size of the language, and many other things. And inevitably, there are going to be very different opinions about what the right balance is. Lisp/Scheme are languages with very little special syntax. I used to use Lisp quite a lot. But I'm not sure the lack of e.g. predefined control structures made Lisp code that much easier to write and understand, to be honest. On the contrary, in fact, as one had to learn libraries of (basic) control-structures on top of the base language. Nor did it necessarily make the life easier for people who built the tools, as e.g. Pretty Printers were expected to identify applications of "special" functions and lay them out in a different way for the sake of readability. (And probably just by looking at the name of the function, and hoping that it meant what it usually meant ...) But I digress.
and try to get rid of it until Haskell-2. But do not endorse its use by new extensions.
I don't think an optional semicolon or two counts as an extension. It really just is a trivial fix. Nor do I think leaving things as they are would do anything in itself to deprecate the use of if-then-else, if that indeed turns out to be where we'd like to go.
Cons are: The sketched problem with indentation can be solved without touching the language.
Well, only if one agrees that a particular style of indenting if-then-else is necessary in the context of a do, but not elsewhere.
The syntax extension is unnecessary, thus complicates all language tools without need.
I'll add that a recommendation for improved error messages has been suggested as an alternative remedy. /Henrik -- Henrik Nilsson School of Computer Science and Information Technology The University of Nottingham nhn@cs.nott.ac.uk This message has been checked for viruses but the contents of an attachment may still contain software viruses, which could damage your computer system: you are advised to perform your own checks. Email communications with the University of Nottingham may be monitored as permitted by UK legislation.

Cale Gibbard cgibbard at gmail.com, Sun Oct 22 12:23:18 EDT 2006
The 'then' and 'else' visually separate the parts of the if-expression, and serve to guide one's eyes when reading code silently, and one's words when speaking it aloud.
This argument is true for every function. I don't see why if test then a else b is necessary, but foldr with_function f initial_state i on_list xs not. If you really need "then" and "else" we could certainly construct some library functions, to let if test `then` a `else` b work, or if (test expression) then (a expression) else (b expression) Say infixr 0 then, else data Else a = Else a a else = Else and so on ...

Henning Thielemann (haskell at henning-thielemann dot de) wrote:
Cale Gibbard cgibbard at gmail.com, Sun Oct 22 12:23:18 EDT 2006
The 'then' and 'else' visually separate the parts of the if-expression, and serve to guide one's eyes when reading code silently, and one's words when speaking it aloud.
This argument is true for every function. I don't see why if test then a else b is necessary, but foldr with_function f initial_state i on_list xs not.
That's why OCaml version 3 merged in Jacques Garrigue's labelised arguments: ListLabels.fold_right : f:('a -> 'b -> 'b) -> 'a list -> init:'b -> 'b This gives you even argument permutation: let sum = fold_right ~init:0 ~f:(fun x y -> x + y) This is a huge readability and maintainability win for twenty-argument functions, e.g. in GUIs! It also is a hassle to have to eta-expand pretty often (in the presence of optional arguments, which are syntactic susgar for Maybe arguments)... Wolfram

On 23/10/06, Henning Thielemann
Cale Gibbard cgibbard at gmail.com, Sun Oct 22 12:23:18 EDT 2006
The 'then' and 'else' visually separate the parts of the if-expression, and serve to guide one's eyes when reading code silently, and one's words when speaking it aloud.
This argument is true for every function. I don't see why if test then a else b is necessary, but foldr with_function f initial_state i on_list xs not.
If-then-else corresponds to a structural part of the English language. Right folding doesn't. Besides, those are awful names for the parts of a foldr. The first parameter is the cons replacement and the second the nil replacement. Having a general syntax for standard catamorphisms on an algebraic datatype might not be an altogether terrible idea.
If you really need "then" and "else" we could certainly construct some library functions, to let if test `then` a `else` b work, or if (test expression) then (a expression) else (b expression)
Say infixr 0 then, else
data Else a = Else a a
else = Else
and so on ...
That seems fairly weak. Why do you want to break all the Haskell code ever written? Yes, you're proposing to phase it out, but there's a lot of code which isn't actively being maintained that would break, and what you're proposing looks a whole lot worse to (I don't think I'm assuming much) most Haskell programmers. The changes that you've been proposing to Haskell make me wonder why it is that you're interested in working with Haskell in the first place -- it's just not the sort of minimal language you're looking for. Why do we allow multiple function equations when case could be used? Why do we allow guards? Why do we have both let and where? The thing is, if you want to create a function which does the same thing as if-then-else, and use it, you're free to do so. By and large, I think that most people would agree that having the then and else parts clearly delimited in such a common form of expression helps a good deal with reading and writing the code. If using an if' function was beneficial, people would be doing it all the time by now. The syntactic form eliminates excess parentheses, and gives the eye an easy way to follow the logic, whereas with just a function, you have to work harder to match parens before you know what the parts of the expression are.

Bulat Ziganshin bulat.ziganshin at gmail.com, Sat Oct 14 11:19:32 EDT 2006 on three syntax-sugar proposals
1. allow to use '_' in number literals. its used in Ruby and i found that this makes long number literals much more readable. for example
maxint = 2_147_483_648
Sounds like something that can be solved with an infix operator: (~~) :: Integer -> Integer -> Integer a ~~ b = a*1000 + b 2~~147~~483~~648

Henning Thielemann
1. allow to use '_' in number literals. its used in Ruby and i found that this makes long number literals much more readable. for example
Sounds like something that can be solved with an infix operator:
(~~) :: Integer -> Integer -> Integer a ~~ b = a*1000 + b
Nice. Although the ~~ seems a bit intrusive. Since its use would be thouroughly optional, perhaps we could adopt an extended (A0-FF) character for this? Some candidates: 257 175 AF ¯ MACRON 267 183 B7 · MIDDLE DOT 270 184 B8 ¸ CEDILLA 260 176 B0 ° DEGREE SIGN Tempting to use B8 Cedilla, since it looks somewhat like a comma, and is less useful for other purposes -- but perhaps it would be to easily confused with a real comma? Ideally, one would also require a group of three digits to the right of such an operator. -k -- If I haven't seen further, it is by standing in the footprints of giants

Ketil Malde wrote:
Tempting to use B8 Cedilla, since it looks somewhat like a comma, and is less useful for other purposes -- but perhaps it would be to easily confused with a real comma?
I would advise against this until we have a bit more of a plan for extended characters in Haskell source. For instance, it might be sensible to use the Unicode "general category" property to decide what characters are allowed in identifiers, and so on. -- Ashley Yakeley

On 2006-10-24 at 12:43PDT Ashley Yakeley wrote:
Ketil Malde wrote:
Tempting to use B8 Cedilla, since it looks somewhat like a comma, and is less useful for other purposes -- but perhaps it would be to easily confused with a real comma?
I have some dim recollection that there is an ISO (or possibly some other standards body) standard that says that rather than commas or points, we should use narrow spaces between groups of digits in numbers. I can't find it now, though -- can anyone? If true, this would suggest the use of one of the SPACE unicodes 2006, 2009, 200a ... but this would of course be a bad idea in a language that uses space for application. Underline is much better.
I would advise against this until we have a bit more of a plan for extended characters in Haskell source. [...]
I think the original proposal -- of allowing underlines in lieu of spaces in numbers -- is far better than using an operator. This is a piece of light-weight convenience syntax at a purely lexical level, and is exactly the sort of thing that is easy to do in a language definition/compiler but thorny if done post-hoc. If an operator, what happens to hexadecimal numbers? 0xffff_3729 makes perfect sense as hex and the "_" does a nice job of separating the digits into readable groups. 0xffff~~3729 looks similar, but doesn't mean the same thing at all. 0xffff~~0x3729 is ugly and probably less readable than the unbroken form. There's also the (perhaps unlikely, but truly grotesque) possibility of wanting a number like 0x3864_face, entering 0x3864~~face and having face = 42 elsewhere in the code. Or, decimal 124~~l24 -- if you are lucky you'll get an undefined variable message, which would be the same as for 124l24, but if unlucky, you'll get no error message instead of "No instance for (Num (Integer -> a))" Furthermore, there's no way for an operator to distinguish between three and some other number of digits (at compile time!), leading to such misleading looking presentations as 22~~40~~65. No. A small alteration to the lexical syntax for the sake of improved readability seems perfectly justifiable as long as it doesn't make the lexical syntax /significantly/ more complicated or harder to learn. So in the simplest form, we would have decimal -> digit{[_]digit} octal -> octit{[_]octit} hexadecimal -> hexit{[_]hexit} integer -> decimal | 0o octal | 0O octal | 0x hexadecimal | 0X hexadecimal float -> decimal . decimal [exponent] | decimal exponent exponent -> (e | E) [+ | -] decimal although my preference would be something a bit more restrictive, requiring numbers to have groups of the same number of digits after each “_” and beginning with a shorter group (ie 12_000_000 and 1200_0000 would be valid but 1247_000 would not). I'm not wedded to this requirement (and it would take a more sophisticated grammar to formalise). I have another dim recollection that something like this was discussed (verbally) at one of the early Haskell meetings, but no idea what became of it. Does anyone remember? Jón -- Jón Fairbairn Jon.Fairbairn at cl.cam.ac.uk

Hello Jon, Wednesday, October 25, 2006, 6:37:33 PM, you wrote:
0xffff_3729 makes perfect sense as hex and the "_" does a nice job of separating the digits into readable groups.
0xffff~~3729 looks similar, but doesn't mean the same thing at all.
0xffff~~0x3729 is ugly and probably less readable than the unbroken form.
and it's again not the same - ~~ operator multiplies by 1000, not 65536 :)))
No. A small alteration to the lexical syntax for the sake of improved readability seems perfectly justifiable as long as it doesn't make the lexical syntax /significantly/ more complicated or harder to learn.
believe it or not, but i once implemented this as ghc patch and send to SPJ, who suggested me to postpone such micro-changes until new Haskell standard will be discussed :) afair, it was about 3 lines patch :) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Just to fill in a detail:
I
I have some dim recollection that there is an ISO [...] standard that says that rather than commas or points, we should use narrow spaces between groups of digits in numbers. I can't find it now, though -- can anyone?
After a bit more searching, I think it's ISO 31-0 part 3, but I'm not going to fork out CHF 102 to check! It is, however also specified for SI: http://www1.bipm.org/en/si/si_brochure/chapter5/5-3-2.html#5-3-4 -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

On 2006-10-25, Jon Fairbairn
No. A small alteration to the lexical syntax for the sake of improved readability seems perfectly justifiable as long as it doesn't make the lexical syntax /significantly/ more complicated or harder to learn.
Sure. But some of us don't find it terribly readable. I think the ~~ operator hack gets 90% of the "benefit" for those who want it.
although my preference would be something a bit more restrictive, requiring numbers to have groups of the same number of digits after each â_â and beginning with a shorter group (ie 12_000_000 and 1200_0000 would be valid but 1247_000 would not). I'm not wedded to this requirement (and it would take a more sophisticated grammar to formalise).
The only reason to put it in the lexer/parser is to avoid misleading cases, which needs thas additional restriction, or something similar, like always 3 for decimal, 4 for hex, 3 for oct, or whatever. -- Aaron Denney -><-

just for fun, I have implemented this for jhc. you can now write numbers like 10_000_000 if you choose. I have not decided whether I like the feature or not. but what the heck. John -- John Meacham - ⑆repetae.net⑆john⑈

Hello,
while people are discussing different notations for literals, I
thought I should mention that in my work I have found it useful to
write literals ending in K (kilo), M (mega) or G (giga) for large
numbers. For example, I can write 4K for (4 * 2^10), or 8M for (8 *
2^20) or 2G for (2 * 2^30). It is simple to implement because it only
requires a modification to the lexer. It is not really necessary
because we can achieve the same by defining:
kb,mg,gb :: Num a => a
kb = 1024
mb = 1024 * kb
gb = 1024 * mb
and now we can write (4 * kb) instead for 4096. I still think that
the literal notation
is nicer though.
-Iavor
On 10/25/06, John Meacham
just for fun, I have implemented this for jhc. you can now write numbers like 10_000_000 if you choose.
I have not decided whether I like the feature or not. but what the heck.
John
-- John Meacham - ⑆repetae.net⑆john⑈ _______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime

Hello Iavor, Thursday, October 26, 2006, 4:51:00 AM, you wrote:
kb,mg,gb :: Num a => a kb = 1024 mb = 1024 * kb gb = 1024 * mb
b :kb :mb :gb :_ = iterate (1024*) 1 :: [Int] b_:kb_:mb_:gb_:tb_:_ = iterate (1024*) 1 :: [Integer]
and now we can write (4 * kb) instead for 4096.
btw, your variant requires re-calculating values on each their use -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Hello Taral, Thursday, October 26, 2006, 6:33:44 PM, you wrote:
btw, your variant requires re-calculating values on each their use
That's what constant folding is for.
are c.f. should work for polymorhic values? afaiu, it's just the problem that leads to the famous monomorhism restriction. w/o type specifier your expressions will got monomorhic types -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On 10/26/06, Bulat Ziganshin
are c.f. should work for polymorhic values? afaiu, it's just the problem that leads to the famous monomorhism restriction. w/o type specifier your expressions will got monomorhic types
These are small enough to be inlined, and are almost certainly going
to be given monomorphic types after inlining, enabling constant
folding.
--
Taral

On 10/26/06, Bulat Ziganshin
wrote: are c.f. should work for polymorhic values? afaiu, it's just the problem that leads to the famous monomorhism restriction. w/o type specifier your expressions will got monomorhic types
These are small enough to be inlined, and are almost certainly going to be given monomorphic types after inlining, enabling constant folding.
Not on Yhc or in Hugs, which has neither constant folding or inlining (as far as I know, for Hugs). They may be free on GHC, but not in general. Thanks Neil

Hi,
On 10/25/06, Bulat Ziganshin
Hello Iavor,
Thursday, October 26, 2006, 4:51:00 AM, you wrote:
kb,mg,gb :: Num a => a kb = 1024 mb = 1024 * kb gb = 1024 * mb
b :kb :mb :gb :_ = iterate (1024*) 1 :: [Int] b_:kb_:mb_:gb_:tb_:_ = iterate (1024*) 1 :: [Integer]
and now we can write (4 * kb) instead for 4096.
btw, your variant requires re-calculating values on each their use
There are other integral types for which one might use these constants (e.g., Word16 and Word32), so the overloading is useful. The multiplications might be repeated depending on the compipler but, as other people pointed out, this is a fairly easy optimization to perform and GHC probably does it. The overloading might make things a little more tricky, but it should be still doable (it is the same problem as turning 1+2 into 3 at compiple time). On the other hand, none of these are important, if we were to use the literal notation that I suggested. Then, the multiplications would happen in the lexer when we compute the value for the literal. I think that the main advantage of the literals is that they are more readable. For example, an editor can color them in the same way as it colors other literals. -Iavor

On 2006-10-25 at 20:57-0000 Aaron Denney wrote:
On 2006-10-25, Jon Fairbairn
wrote: No. A small alteration to the lexical syntax for the sake of improved readability seems perfectly justifiable as long as it doesn't make the lexical syntax /significantly/ more complicated or harder to learn.
Sure. But some of us don't find it terribly readable.
I'm not sure what you are saying here. Assessing readability by introspection is terribly unreliable. Unfamiliarity with the presentation of numbers with underlines is likely to make them feel a bit awkward to begin with, but habituation is likely to change that. We do know from venerable experiments that humans can easily identify small groups of things without counting. Most people can recognise three easily, few people can recognise eight. So it's no surprise that the standard presentation of numbers groups digits in threes. If you were to conduct an experiment on yourself that presented you with numbers displayed in all three forms (ungrouped, thin spaced and with underlines) and timed how long it took you to read them out, I'd be surprised if the underline grouped form (even while still unfamiliar) didn't beat the ungrouped form. Quickly now, is 20000000000 tens of millions, tens or hundreds orthousands of millions? Now try the same for 2_000_000_000 or 20_000_000_000.
I think the ~~ operator hack gets 90% of the "benefit" for those who want it.
I thought my earlier message adequately demonstrated that it does /not/. Another case: if you change “square 123479010987” to “square 123_479_010_987” to improve readability it still means the same thing. If you change it to “square 123~~479~~010~~987” it doesn't.
although my preference would be something a bit more restrictive, requiring numbers to have groups of the same number of digits after each “_” and beginning with a shorter group (ie 12_000_000 and 1200_0000 would be valid but 1247_000 would not). I'm not wedded to this requirement (and it would take a more sophisticated grammar to formalise).
The only reason to put it in the lexer/parser is to avoid misleading cases,
yes
which needs thas additional restriction, or something similar, like always 3 for decimal, 4 for hex, 3 for oct, or whatever.
No. I certainly would prefer a requirement that the groups be the same length, but the intention is that the value would be got simply by stripping out the underlines. So while 19_00 would be an idiosyncratic way of writing 1_900 (intended to be read nineteen hundred, one would presume), it wouldn't be misleading in the way that 19~~00 (which would evaluate to 19_000) would be. -- Jón Fairbairn Jon.Fairbairn at cl.cam.ac.uk

On 2006-10-26, Jon Fairbairn
On 2006-10-25 at 20:57-0000 Aaron Denney wrote:
On 2006-10-25, Jon Fairbairn
wrote: No. A small alteration to the lexical syntax for the sake of improved readability seems perfectly justifiable as long as it doesn't make the lexical syntax /significantly/ more complicated or harder to learn.
Sure. But some of us don't find it terribly readable.
I'm not sure what you are saying here. Assessing readability by introspection is terribly unreliable. Unfamiliarity with the presentation of numbers with underlines is likely to make them feel a bit awkward to begin with, but habituation is likely to change that.
Fair enough, I don't actually find it less readable, merely quite ugly. I might indeed get used to it.
I think the ~~ operator hack gets 90% of the "benefit" for those who want it.
I thought my earlier message adequately demonstrated that it does /not/.
You demonstrated some corner cases that weren't convincing at all.
Another case: if you change âsquare 123479010987â to âsquare 123_479_010_987â to improve readability it still means the same thing. If you change it to âsquare 123~~479~~010~~987â it doesn't.
This is a bit more convincing. -- Aaron Denney -><-
participants (18)
-
Aaron Denney
-
Ashley Yakeley
-
Benjamin Franksen
-
Brian Smith
-
Bulat Ziganshin
-
Cale Gibbard
-
Dave Menendez
-
Henning Thielemann
-
Henrik Nilsson
-
Iavor Diatchki
-
John Meacham
-
Jon Fairbairn
-
Jón Fairbairn
-
kahl@cas.mcmaster.ca
-
Ketil Malde
-
Neil Mitchell
-
Philippa Cowderoy
-
Taral