
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

Brandon Allbery
On Sat, Dec 1, 2012 at 5:30 AM, Roman Cheplyaka
wrote: 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'.
I’m not quite sure what treating “of” as lambda means, and \of raises the some of the same objections as \case. Up until the introduction of “lambda-case”, \ was a clear indication that what was coming next was a pattern that would bind variables (except in degenerate cases, but anyone who writes something like \Nothing -> e should be taken out and sho- wn why it’s a bad idea).
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.
Of the available alternatives, it makes the most linguistic sense. If you can’t read the subtext for that sentence, try again :-) In the design I was suggesting, “of” is in no sense a lambda, it simply introduces a list of alternative patterns exactly as it does in the original design of case … of {alts}. Arguing about whether “of” is the right keyword here without arguing that case… of… should have different keywords is inconsistent, and arguing for a change of those keywords really would be fussing about the colour of the bikeshed after it was painted. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

Brent Yorgey
Oh, PLEASE people. Let's not have another round of bikeshedding about this AFTER the feature is already implemented!
This is not an argument about the colour of the bikeshed. In terms of that analogy, this has gone something like this: Someone says the bikeshed doorknob is hard to turn and we should have a handle. There’s some discussion, I say maybe, but lets not do it unless we have a good design. Someone else comes up with the beginnings of a good design for a handle, but there’s no consensus about that and it all goes quiet. Some time later a voice says that if nobody does anything it’ll get forgotten (which is what I was hoping would happen). I repeat that it’s better not to do it without a good design and nod off. When I wake up, a handle has been installed by hot-melt glueing a bit of rough sawn timber to the doorknob. I complain. Another voice tells me to shut up, we’ve done it now. — Jón
participants (5)
-
Brandon Allbery
-
Brent Yorgey
-
Herbert Valerio Riedel
-
Jon Fairbairn
-
Roman Cheplyaka