A big hurray for lambda-case (and all the other good stuff)

Hi Everyone just wanted to drop by to say how much I like the new lambda case extension. I use it all the time and I just *love* how it relieves me from conjuring up dummy variables, which makes teh code not only esier to write but also to read. A big, huge thank you to the ghc developers. This has been sooooo long on my wish list. Also much appreciated and long awaited: tuple sections (though I use them not quite as often). Both should *definitely* go into Haskell'13. Of course, thank you also for all the other beautiful stuff in ghc-7.6.1, especially PolyKinds, DataKinds etc. GHC is just simply amazing. You guys RULE THE WORLD! Cheers -- Ben Franksen () ascii ribbon campaign - against html e-mail /\ www.asciiribbon.org - against proprietary attachments

Ben Franksen
just wanted to drop by to say how much I like the new lambda case extension. I use it all the time and I just *love* how it relieves me from conjuring up dummy variables, which makes teh code not only esier to write but also to read.
[…] should *definitely* go into Haskell'13.
As I was opposed to the suggestion for lambda case I didn’t really follow the discussion of the syntax, but I’m puzzled by the choice. To me it seems obvious that if we are going to do this (as opposed to something more decomposable like lambda-match), we should do it simply by making the “case exp” part of a case expression optional. So the syntax for lambda- case would be of {alts…} and we would then describe case e of {…} as syntactic sugar for (of {…}) (e) Doing it this way doesn’t introduce any new syntactic elements and has fewer tokens at the point of use. I don’t see any need for a \ in the syntax: this is a functional language we are talking about after all. Once we know that “of” introduces a function, that should be enough. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

I had been missing a pattern matching lambda in Haskell for a long time (SML had "fn" since ages) and my typical use will be monadic_expr >>= \case branches I think "\case" is not the worst choice, certainly better than "of" ... Thanks to the GHC 7.6 developers! Cheers, Andreas On 29.11.12 12:49 PM, Jon Fairbairn wrote:
Ben Franksen
writes: just wanted to drop by to say how much I like the new lambda case extension. I use it all the time and I just *love* how it relieves me from conjuring up dummy variables, which makes teh code not only esier to write but also to read.
[…] should *definitely* go into Haskell'13.
As I was opposed to the suggestion for lambda case I didn’t really follow the discussion of the syntax, but I’m puzzled by the choice. To me it seems obvious that if we are going to do this (as opposed to something more decomposable like lambda-match), we should do it simply by making the “case exp” part of a case expression optional. So the syntax for lambda- case would be
of {alts…}
and we would then describe
case e of {…}
as syntactic sugar for
(of {…}) (e)
Doing it this way doesn’t introduce any new syntactic elements and has fewer tokens at the point of use.
I don’t see any need for a \ in the syntax: this is a functional language we are talking about after all. Once we know that “of” introduces a function, that should be enough.
-- Andreas Abel <>< Du bist der geliebte Mensch. Theoretical Computer Science, University of Munich Oettingenstr. 67, D-80538 Munich, GERMANY andreas.abel@ifi.lmu.de http://www2.tcs.ifi.lmu.de/~abel/

Andreas Abel
I had been missing a pattern matching lambda in Haskell for a long time (SML had "fn" since ages) and my typical use will be
monadic_expr >>= \case branches
We’ve been through that. I want something similar, but would have preferred something more algebraic.
I think "\case" is not the worst choice, certainly better than "of" ...
What’s your argument? You’ll have to do better than blatant assertion to convince me. Making “case exp” optional builds on an existing expression syntax, giving an explicit meaning to a part of it, so a reader only has to know that “of {alts}” is a function and case does something specific with it. This “\case” takes the keyword from that expression syntax and makes it a special case of lambda, so a reader seeing a lambda now has to check for a keyword instead of knowing straight off that the next thing is going to be a variable. Back when we originally designed Haskell there were lots of things that people wanted to put in, and eventually we reached a point where we said that we would only put something new in if it allowed us to remove (or simplify) something else. “\case” complicates lambda, using “of” simply breaks “case … of …” into two easily understood parts. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

Jon Fairbairn
“\case” complicates lambda, using “of” simply breaks “case … of …” into two easily understood parts.
Just some observation (I'm rather late to the lambda-case discussion, so this might have been already pointed out previously): if the reserved keyword 'of' was to take the place of '\case', shouldn't then 'case' exp w/o the "'of' { alts }"-part become a separately valid expression (with 'case' essentially meaning 'flip ($)') to really break it up into two independent parts? Then 'case exp of { alts }' wouldn't be a special form anymore, but would just result from combining 'case' and 'of'; 'case' wouldn't even need to be a reserved keyword (and thus the grammar could be simplified), if it wasn't for the current grammar which requires to isolate a \case-expression by using () or $, consider e.g.: {-# LANGUAGE LambdaCase #-} import System.Environment case' :: b -> (b -> c) -> c case' = flip ($) main = do s <- getArgs case' s $ \case -- image '\case' was actually '\of' or 'of' [x] -> putStrLn ("Hello " ++ x) _ -> putStrLn "wrong number of arguments given" just my 2¢ cheers, hvr

Oh, PLEASE people. Let's not have another round of bikeshedding about this AFTER the feature is already implemented! -Brent On Fri, Nov 30, 2012 at 01:25:27PM +0100, Herbert Valerio Riedel wrote:
Jon Fairbairn
writes: [...]
“\case” complicates lambda, using “of” simply breaks “case … of …” into two easily understood parts.
Just some observation (I'm rather late to the lambda-case discussion, so this might have been already pointed out previously):
if the reserved keyword 'of' was to take the place of '\case', shouldn't then
'case' exp
w/o the "'of' { alts }"-part become a separately valid expression (with 'case' essentially meaning 'flip ($)') to really break it up into two independent parts? Then 'case exp of { alts }' wouldn't be a special form anymore, but would just result from combining 'case' and 'of';
'case' wouldn't even need to be a reserved keyword (and thus the grammar could be simplified), if it wasn't for the current grammar which requires to isolate a \case-expression by using () or $, consider e.g.:
{-# LANGUAGE LambdaCase #-}
import System.Environment
case' :: b -> (b -> c) -> c case' = flip ($)
main = do s <- getArgs
case' s $ \case -- image '\case' was actually '\of' or 'of' [x] -> putStrLn ("Hello " ++ x) _ -> putStrLn "wrong number of arguments given"
just my 2¢
cheers, hvr
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

It hasn't made it to the standard yet, though. If some experimental
feature is implemented in GHC, it doesn't mean it's set in stone.
I find this discussion useful — there are some interesting points
(splitting "case of" into two parts) that I don't remember reading in the
original thread (but maybe it's just me).
Roman
* Brent Yorgey
Oh, PLEASE people. Let's not have another round of bikeshedding about this AFTER the feature is already implemented!
-Brent
On Fri, Nov 30, 2012 at 01:25:27PM +0100, Herbert Valerio Riedel wrote:
Jon Fairbairn
writes: [...]
“\case” complicates lambda, using “of” simply breaks “case … of …” into two easily understood parts.
Just some observation (I'm rather late to the lambda-case discussion, so this might have been already pointed out previously):
if the reserved keyword 'of' was to take the place of '\case', shouldn't then
'case' exp
w/o the "'of' { alts }"-part become a separately valid expression (with 'case' essentially meaning 'flip ($)') to really break it up into two independent parts? Then 'case exp of { alts }' wouldn't be a special form anymore, but would just result from combining 'case' and 'of';
'case' wouldn't even need to be a reserved keyword (and thus the grammar could be simplified), if it wasn't for the current grammar which requires to isolate a \case-expression by using () or $, consider e.g.:
{-# LANGUAGE LambdaCase #-}
import System.Environment
case' :: b -> (b -> c) -> c case' = flip ($)
main = do s <- getArgs
case' s $ \case -- image '\case' was actually '\of' or 'of' [x] -> putStrLn ("Hello " ++ x) _ -> putStrLn "wrong number of arguments given"
just my 2¢
cheers, hvr
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Sat, Dec 1, 2012 at 5:30 AM, Roman Cheplyaka
I find this discussion useful — there are some interesting points (splitting "case of" into two parts) that I don't remember reading in the original thread (but maybe it's just me).
Mentioned twice that I recall, as treating 'of' as a lambda and as '\of'. It got somewhat short shrift, likely because while it makes sense from an existing language syntax viewpoint, it makes little to none from a readability standpoint. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

Right, case..of is superfluous, case e of branches can now be written as e |> \case branches with backwards application |> (or some prefer & --- sadly, the proposal to add backwards appliation to base did not make it to a consensus). This is in accordance to the monadic me >>= \case branches If there was an opportunity to make drastic language changes, case..of could be disposed of altogether. \case could become 'cases' or 'match' or 'fun' (rather not 'of', for my taste). The current compromise it not too bad, I think. Unfortunately, I have to wait for 7.6 to become the standard before using \case in Agda source... Cheers, Andreas On 30.11.12 7:25 AM, Herbert Valerio Riedel wrote:
Jon Fairbairn
writes: [...]
“\case” complicates lambda, using “of” simply breaks “case … of …” into two easily understood parts.
Just some observation (I'm rather late to the lambda-case discussion, so this might have been already pointed out previously):
if the reserved keyword 'of' was to take the place of '\case', shouldn't then
'case' exp
w/o the "'of' { alts }"-part become a separately valid expression (with 'case' essentially meaning 'flip ($)') to really break it up into two independent parts? Then 'case exp of { alts }' wouldn't be a special form anymore, but would just result from combining 'case' and 'of';
'case' wouldn't even need to be a reserved keyword (and thus the grammar could be simplified), if it wasn't for the current grammar which requires to isolate a \case-expression by using () or $, consider e.g.:
{-# LANGUAGE LambdaCase #-}
import System.Environment
case' :: b -> (b -> c) -> c case' = flip ($)
main = do s <- getArgs
case' s $ \case -- image '\case' was actually '\of' or 'of' [x] -> putStrLn ("Hello " ++ x) _ -> putStrLn "wrong number of arguments given"
just my 2¢
cheers, hvr
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Andreas Abel <>< Du bist der geliebte Mensch. Theoretical Computer Science, University of Munich Oettingenstr. 67, D-80538 Munich, GERMANY andreas.abel@ifi.lmu.de http://www2.tcs.ifi.lmu.de/~abel/

On Thu, Nov 29, 2012 at 05:49:53PM +0000, Jon Fairbairn wrote:
Ben Franksen
writes: just wanted to drop by to say how much I like the new lambda case extension. I use it all the time and I just *love* how it relieves me from conjuring up dummy variables, which makes teh code not only esier to write but also to read.
[...] should *definitely* go into Haskell'13. [...] To me it seems obvious that if we are going to do this [...] we should do it simply by making the "case exp" part of a case expression optional.
of {alts...}
and we would then describe
case e of {...}
as syntactic sugar for
(of {...}) (e)
My very belated and unsolicited layman's reply is that I am a strong supporter of Jon's position. His suggestion is parsimonious and natural. Without wishing to start the discussion again, I disagree that it is bikeshedding. One lesson I learned from Haskell is that syntax is much more important than I previously realised. Tom

Hi,
I also support Jon's proposal for standalone of { ... }. Seems to me
clearer and more useful than the special "\case" construct.
I suppose 'of { ... }' could be generalized to multiple arguments, so that
of (Just x) (Just y) -> x ++ y
would create an anonymous function of type 'Maybe String -> Maybe String ->
String'.
Considering the recent thread about partial functions:
http://www.haskell.org/pipermail/haskell-cafe/2012-December/105445.html
we could have variants of 'of' to distinguish partial functions. For
example, we could have something like 'ofFull' that would require an
exhaustive list of patterns, and something like 'ofPart' that would instead
produce results of type 'Maybe something'. (Most likely we'd have to think
of better names for them.) For example:
ofPart [x] [y] -> x ++ y
would be of type '[String] -> [String] -> Maybe String', returning
`Nothing` if one of the input isn't a 1-element list - an approach similar
to Scala's partial functions. <
http://www.scala-lang.org/api/current/scala/PartialFunction.html>
[Perhaps we could have 'of' to work both ways - if the list of patterns
would be exhaustive, the result would be pure. If it would be
non-exhaustive, the result would be 'Maybe something'. Of course 'case x of
...' would still work as now, not caring about exhaustiveness. But I'm not
sure if this wouldn't be too error prone.]
We could even generalize 'ofPart' to work with any Alternative instance so
that
ofPart [x] [y] -> x ++ y
would be of type '(Alternative f) => [String] -> [String] -> f String'.
Matching patterns would return results using 'pure', non-matching 'empty',
and they would be all combined combined using <|>. 'empty' would be
returned if nothing matched. (Among other things, this could have some
interesting consequences when overlapping patterns would be applied to
'Alternative []'.) For example
fn = ofPart (Right 0) -> 1
(Right x) -> x
would produce (using today's syntax):
fn :: (Alternative f) => Either Bool Int -> f Int
fn x = case x of { Right 0 -> pure 1 ; _ -> empty; } <|>
case x of { Right x -> pure x ; _ -> empty; } <|>
empty
Best regards,
Petr
2012/12/29 Tom Ellis
On Thu, Nov 29, 2012 at 05:49:53PM +0000, Jon Fairbairn wrote:
Ben Franksen
writes: just wanted to drop by to say how much I like the new lambda case extension. I use it all the time and I just *love* how it relieves me from conjuring up dummy variables, which makes teh code not only esier to write but also to read.
[...] should *definitely* go into Haskell'13. [...] To me it seems obvious that if we are going to do this [...] we should do it simply by making the "case exp" part of a case expression optional.
of {alts...}
and we would then describe
case e of {...}
as syntactic sugar for
(of {...}) (e)
My very belated and unsolicited layman's reply is that I am a strong supporter of Jon's position. His suggestion is parsimonious and natural. Without wishing to start the discussion again, I disagree that it is bikeshedding. One lesson I learned from Haskell is that syntax is much more important than I previously realised.
Tom
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Jon's suggestion sounds great.
The bike shed should be green.
That is all.
On Sun, Dec 30, 2012 at 4:44 PM, Petr P
Hi,
I also support Jon's proposal for standalone of { ... }. Seems to me clearer and more useful than the special "\case" construct.
I suppose 'of { ... }' could be generalized to multiple arguments, so that of (Just x) (Just y) -> x ++ y would create an anonymous function of type 'Maybe String -> Maybe String -> String'.
Considering the recent thread about partial functions: http://www.haskell.org/pipermail/haskell-cafe/2012-December/105445.html we could have variants of 'of' to distinguish partial functions. For example, we could have something like 'ofFull' that would require an exhaustive list of patterns, and something like 'ofPart' that would instead produce results of type 'Maybe something'. (Most likely we'd have to think of better names for them.) For example: ofPart [x] [y] -> x ++ y would be of type '[String] -> [String] -> Maybe String', returning `Nothing` if one of the input isn't a 1-element list - an approach similar to Scala's partial functions. < http://www.scala-lang.org/api/current/scala/PartialFunction.html>
[Perhaps we could have 'of' to work both ways - if the list of patterns would be exhaustive, the result would be pure. If it would be non-exhaustive, the result would be 'Maybe something'. Of course 'case x of ...' would still work as now, not caring about exhaustiveness. But I'm not sure if this wouldn't be too error prone.]
We could even generalize 'ofPart' to work with any Alternative instance so that ofPart [x] [y] -> x ++ y would be of type '(Alternative f) => [String] -> [String] -> f String'. Matching patterns would return results using 'pure', non-matching 'empty', and they would be all combined combined using <|>. 'empty' would be returned if nothing matched. (Among other things, this could have some interesting consequences when overlapping patterns would be applied to 'Alternative []'.) For example
fn = ofPart (Right 0) -> 1 (Right x) -> x
would produce (using today's syntax):
fn :: (Alternative f) => Either Bool Int -> f Int fn x = case x of { Right 0 -> pure 1 ; _ -> empty; } <|> case x of { Right x -> pure x ; _ -> empty; } <|> empty
Best regards, Petr
2012/12/29 Tom Ellis
On Thu, Nov 29, 2012 at 05:49:53PM +0000, Jon Fairbairn wrote:
Ben Franksen
writes: just wanted to drop by to say how much I like the new lambda case extension. I use it all the time and I just *love* how it relieves me from conjuring up dummy variables, which makes teh code not only esier to write but also to read.
[...] should *definitely* go into Haskell'13. [...] To me it seems obvious that if we are going to do this [...] we should do it simply by making the "case exp" part of a case expression optional.
of {alts...}
and we would then describe
case e of {...}
as syntactic sugar for
(of {...}) (e)
My very belated and unsolicited layman's reply is that I am a strong supporter of Jon's position. His suggestion is parsimonious and natural. Without wishing to start the discussion again, I disagree that it is bikeshedding. One lesson I learned from Haskell is that syntax is much more important than I previously realised.
Tom
_______________________________________________ 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 Sun, Dec 30, 2012 at 8:51 AM, David Thomas
Jon's suggestion sounds great.
The bike shed should be green.
There were plenty of proposals that would work fine. `case of` was great. `\ of` was great. It's less obvious to me that stand-alone `of` is never ambiguous... but if that's true, it's reasonable. Sadly, the option that was worse that doing nothing at all is what was implemented. The "bikeshedding" nonsense is frustrating. Bikeshedding is about wasting time debating the minutia of a significant improvement, when everyone agrees the improvement is a good idea. Here, what happened was that someone proposed a minor syntax tweak (from `\x -> case x of` to `case of`), other reasonable minor syntax tweaks were proposed instead to accomplish the same goal, and then in the end, out of the blue, it was decided to turn `case` into a layout-inducing keyword (or even worse, only sometimes but not always layout-inducing). There is no bike shed here. There are just colors (minor syntax tweaks). And I don't get the use of "bikeshedding" as basically just a rude comment to be made at people who don't like the same syntax others do. -- Chris

My 2 cents on the issue: We should have a better forms of meta-programming to solve this sort of issue generally. With the power of first-class functions and laziness, we can get away with a lot of things without meta-programming, but case expression syntax is not first class, so cannot benefit from the flexibility proffered to the rest of the language. tl;dr give me easily extensible syntax, rather than having to run to GHC devs every time I want a new or different flavor of sugar. -- Dan Burton

Syntax extensibility is usually too powerful, it surely would be abused extensively, which would make developer's life a nightmare, unless there is only one developer and whole development takes no more than a couple of months.
On Dec 31, 2012, at 1:09 AM, Dan Burton
My 2 cents on the issue:
We should have a better forms of meta-programming to solve this sort of issue generally. With the power of first-class functions and laziness, we can get away with a lot of things without meta-programming, but case expression syntax is not first class, so cannot benefit from the flexibility proffered to the rest of the language.
tl;dr give me easily extensible syntax, rather than having to run to GHC devs every time I want a new or different flavor of sugar.
-- Dan Burton _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[featureX] is usually too powerful, it surely would be abused extensively, which would make developer's life a nightmare, unless there is only one developer and whole development takes no more than a couple of months.
This doesn't say much about *why* syntax extension is too powerful, nor *how *that would lead to extensive abuse. Well, "too powerful" or not, meta-programming should be more easily available at least at *some *layer of language development without having to resort to hacking the compiler. -- Dan Burton

On Sun, Dec 30, 2012 at 8:42 PM, Dan Burton
[featureX] is usually too powerful, it surely would be abused extensively,
which would make developer's life a nightmare, unless there is only one developer and whole development takes no more than a couple of months.
This doesn't say much about *why* syntax extension is too powerful, nor *how *that would lead to extensive abuse. Well, "too powerful" or not, meta-programming should be more easily available at least at *some *layer of language development without having to resort to hacking the compiler.
I think someone's already working on this (SugarHaskell?). -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

On Sun, Dec 30, 2012 at 10:00 PM, Brandon Allbery
On Sun, Dec 30, 2012 at 8:42 PM, Dan Burton
wrote: [featureX] is usually too powerful, it surely would be abused extensively, which would make developer's life a nightmare, unless there is only one developer and whole development takes no more than a couple of months.
This doesn't say much about why syntax extension is too powerful, nor how that would lead to extensive abuse. Well, "too powerful" or not, meta-programming should be more easily available at least at some layer of language development without having to resort to hacking the compiler.
I think someone's already working on this (SugarHaskell?).
Hi All, Petr's suggestion has some similarities with this quasiquoter http://hackage.haskell.org/packages/archive/applicative-quoters/0.1.0.8/doc/..., at least as far as picking a different return type if some patterns can fail. If new syntax implemented by a quasiquoter is really that good, then these possible issues should be worth it: - have to type [| |] - haskell-src-exts parser called may not have the same extensions enabled as ghc - when other new syntax is added, template haskell (and haskell-src-meta) may not gain those features for a year or more Regards, Adam

Hi, Brandon Allbery wrote:
[...] syntax extension [...]
I think someone's already working on this (SugarHaskell?).
Yes, we are working on it. See our paper [1] and Sebastian's talk [2] at the Haskell Symposium. Our current prototype can be installed as an Eclipse plugin [3] or as a command-line tool [4]. [1] http://sugarj.org/sugarhaskell.pdf [2] http://www.youtube.com/watch?v=Kjm7bOLnuy0 [3] http://update.sugarj.org/ [4] http://hackage.haskell.org/package/sugarhaskell One use case we have in mind for SugarHaskell is prototyping of language extensions like the one discussed in this thread. Tillmann
participants (15)
-
adam vogt
-
Andreas Abel
-
Ben Franksen
-
Brandon Allbery
-
Brent Yorgey
-
Chris Smith
-
Dan Burton
-
David Thomas
-
Herbert Valerio Riedel
-
Jon Fairbairn
-
MigMit
-
Petr P
-
Roman Cheplyaka
-
Tillmann Rendel
-
Tom Ellis