Call to arms: lambda-case is stuck and needs your help

Hi. After 21 months of occasional arguing the lambda-case proposal(s) is in danger of being buried under its own trac ticket comments. We need fresh blood to finally reach an agreement on the syntax. Read the wiki page[1], take a look at the ticket[2], vote and comment on the proposals! P.S. I'm CC-ing Cafe to attract more people, but please keep the discussion to the GHC Users list. [1] http://hackage.haskell.org/trac/ghc/wiki/LambdasVsPatternMatching [2] http://hackage.haskell.org/trac/ghc/ticket/4359

I like \case as is proposed. It seems the least controversial one and there's curry (\case ) for two-args, but even that seems a rare case. For what it's worth, I like the idea of omission being partiality, as in case of and if then. It seems perfectly natural to me, I don't need a \ to tell me that an expression will result in a function. But some do. So I'll go along with and vote for \case. The lack of a lambda case is one of the few "legitimate" complaints I have about Haskell's syntax so it would be marvey to see it in GHC. P.S. \if then … else …?

On Thu, Jul 5, 2012 at 12:21 PM, Christopher Done
I like \case as is proposed. It seems the least controversial one and there's curry (\case ) for two-args, but even that seems a rare case.
For what it's worth, I like the idea of omission being partiality, as in case of and if then. It seems perfectly natural to me, I don't need a \ to tell me that an expression will result in a function. But some do. So I'll go along with and vote for \case. The lack of a lambda case is one of the few "legitimate" complaints I have about Haskell's syntax so it would be marvey to see it in GHC.
+1 for \case, I completely agree with Christopher Done. Cheers, -- Felipe.

On Thu, Jul 5, 2012 at 5:21 PM, Christopher Done
I like \case as is proposed. It seems the least controversial one and there's curry (\case ) for two-args, but even that seems a rare case.
For what it's worth, I like the idea of omission being partiality, as in case of and if then. It seems perfectly natural to me, I don't need a \ to tell me that an expression will result in a function. But some do. So I'll go along with and vote for \case. The lack of a lambda case is one of the few "legitimate" complaints I have about Haskell's syntax so it would be marvey to see it in GHC.
I agree. I think the partial application metaphor in "case of" is very nice, but \case is okay enough, so I'm voting for whatever is most popular as long as it does the job and doesn't break compatibility.
P.S. \if then … else …?
I'd prefer just getting a function of type a -> a -> Bool -> a and partially applying it. We need a language level solution for case because case of is fundamental and you can't do that. But if then else is just sugar. (That being said one of my principles is to trust people not to make their own code ugly on purpose, so if people really want partially applied if then else then I guess let them have it else who cares. But I don't really see the case for it.) -- Your ship was caught in a monadic eruption.

Christopher Done
P.S. \if then … else …?

Quoting Mikhail Vorozhtsov
After 21 months of occasional arguing the lambda-case proposal(s) is in danger of being buried under its own trac ticket comments. We need fresh blood to finally reach an agreement on the syntax. Read the wiki page[1], take a look at the ticket[2], vote and comment on the proposals!
P.S. I'm CC-ing Cafe to attract more people, but please keep the discussion to the GHC Users list.
[1] http://hackage.haskell.org/trac/ghc/wiki/LambdasVsPatternMatching [2] http://hackage.haskell.org/trac/ghc/ticket/4359
Well, for what it's worth, my vote goes for a multi-argument \case. I find the comment on the wiki page about mistyping "\case Just x" instead of "\case (Just x)" a lot a bit disingenuous, since you already need these parens with today's lambda. The complaint that multi-argument cases are unorthodox doesn't really hold a lot of weight with me -- much more serious things than syntax have changed in GHC compared to the Report! Is there a more formal way to cast votes...? ~d

On 05/07/12 17:22, wagnerdm@seas.upenn.edu wrote:
Well, for what it's worth, my vote goes for a multi-argument \case. I find the comment on the wiki page about mistyping "\case Just x" instead of "\case (Just x)" a lot a bit disingenuous, since you already need these parens with today's lambda.
But you don't need parentheses with today's case. I.e. you write \x -> case v of Just x -> y Nothing -> z then you would also expect to be able to write \case Just x -> y Nothing -> z And \case looks more like case than like lambda, particularly because it uses layout. As for single argument \case, I don't really see the need for it, but I am not against. So I'll abstain from voting. Twan

Quoting wagnerdm@seas.upenn.edu:
Well, for what it's worth, my vote goes for a multi-argument \case. I
Just saw a proposal for \of on the reddit post about this. That's even better, since: 1. it doesn't change the list of block heralds 2. it doesn't mention case, and therefore multi-arg \of is perhaps a bit less objectionable to those who expect "case" to be single-argument 3. 40% less typing! Can I change my vote? =) ~d

I really like the \of proposal! It is a clean elision with \x -> case x of becoming \of I still don't like it directly for multiple arguments. One possible approach to multiple arguments is what we use for multi-argument case/alt here in our little haskell-like language, Ermine, here at S&P CapitalIQ, we allow for ',' separated patterns, but without surrounding parens to be treated as a multi argument case and alt pair. Internally we desugar our usual top level bindings directly to this representation. When mixed with the \of extension, this would give you: foo :: Num a => Maybe a -> Maybe a -> Maybe a foo = \of Just x, Just y -> Just (x*y) _, _ -> Nothing but it wouldn't incur parens for the usual constructor pattern matches and it sits cleanly in another syntactic hole. A similar generalization can be applied to the expression between case and of to permit a , separated list of expressions so this becomes applicable to the usual case construct. A naked unparenthesized , is illegal there currently as well. That would effectively be constructing then matching on an unboxed tuple without the (#, #) noise, but that can be viewed as a separate proposal' then the above is just the elision of the case component of: foo mx my = case mx, my of Just x, Just y -> Just (x*y) _, _ -> Nothing On Jul 5, 2012, at 2:49 PM, wagnerdm@seas.upenn.edu wrote:
Quoting wagnerdm@seas.upenn.edu:
Well, for what it's worth, my vote goes for a multi-argument \case. I
Just saw a proposal for \of on the reddit post about this. That's even better, since:
1. it doesn't change the list of block heralds 2. it doesn't mention case, and therefore multi-arg \of is perhaps a bit less objectionable to those who expect "case" to be single-argument 3. 40% less typing!
Can I change my vote? =) ~d
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

On 2012-07-05 23:04, Edward Kmett wrote:
A similar generalization can be applied to the expression between case and of to permit a , separated list of expressions so this becomes applicable to the usual case construct. A naked unparenthesized , is illegal there currently as well. That would effectively be constructing then matching on an unboxed tuple without the (#, #) noise, but that can be viewed as a separate proposal' then the above is just the elision of the case component of:
Should that also generalize to nullarry 'case of'? As in foo = case of | guard1 -> bar | guard2 -> baz instead of foo = case () of () | guard1 -> bar | guard2 -> baz I realize this is getting off-topic, and has become orthogonal to the single argument λcase proposal. Twan

On 07/06/2012 04:33 AM, Twan van Laarhoven wrote:
On 2012-07-05 23:04, Edward Kmett wrote:
A similar generalization can be applied to the expression between case and of to permit a , separated list of expressions so this becomes applicable to the usual case construct. A naked unparenthesized , is illegal there currently as well. That would effectively be constructing then matching on an unboxed tuple without the (#, #) noise, but that can be viewed as a separate proposal' then the above is just the elision of the case component of:
Should that also generalize to nullarry 'case of'? As in
foo = case of | guard1 -> bar | guard2 -> baz
instead of
foo = case () of () | guard1 -> bar | guard2 -> baz
I realize this is getting off-topic, and has become orthogonal to the single argument λcase proposal. Yes, there is a separate proposal for that: http://hackage.haskell.org/trac/haskell-prime/wiki/MultiWayIf

Oh, neat. I guess it does. :) I'll hack that into my grammar when I get into work tomorrow.
My main point with that observation is it cleanly allows for multiple argument \of without breaking the intuition you get from how of already works/looks or requiring you to refactor subsequent lines, to cram parens or other odd bits of syntax in, but still lets the multi-argument crowd have a way to make multi-argument lambdas with all of the expected appropriate backtracking, if they want them. I definitely prefer \of to \case given its almost shocking brevity and the fact that the fact that it introduces a layout rule doesn't change any of the rules for when layout is introduced.
On Jul 5, 2012, at 5:33 PM, Twan van Laarhoven
On 2012-07-05 23:04, Edward Kmett wrote:
A similar generalization can be applied to the expression between case and of to permit a , separated list of expressions so this becomes applicable to the usual case construct. A naked unparenthesized , is illegal there currently as well. That would effectively be constructing then matching on an unboxed tuple without the (#, #) noise, but that can be viewed as a separate proposal' then the above is just the elision of the case component of:
Should that also generalize to nullarry 'case of'? As in
foo = case of | guard1 -> bar | guard2 -> baz
instead of
foo = case () of () | guard1 -> bar | guard2 -> baz
I realize this is getting off-topic, and has become orthogonal to the single argument λcase proposal.
Twan
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Twan,
The 0-ary version you proposed actually works even nicer with \of.
foo'' = case () of
() | quux -> ...
| quaffle -> ...
| otherwise -> ...
Starting from the above legal haskell multi-way if, we can, switch to
foo' = case of
| quux -> ...
| quaffle -> ...
| otherwise -> ...
using the 0-ary form of case as a multi-way if, but since the motivation
was to allow the min \of, we get the very terse
foo = \of | quux -> ...
| quaffle -> ...
| otherwise -> ...
and you get wind up with layout starting on the |'s so they line up
per-force.
baz = \of
Just x -> Just (x + 1)
Nothing -> Nothing
avoids an ugly temporary for
baz' mx = case mx of
Just x -> Just (x + 1)
Nothing -> Nothing
and in the multi-argument case, the resulting syntax is actually comparably
noisy to the direct declaration syntax. One , as opposed to two pairs of
parentheses in bar''' below.
bar = \of Just x, Just y -> Just (x + y)
_ , _ -> Nothing
bar' mx my = case mx, my of
Just x, Just y -> Just (x + y)
_ , _ -> Nothing
bar'' mx my = case (# mx, my #) of
(# Just x, Just y #) -> Just (x + y)
(# _ , _ #) -> Nothing
bar''' (Just x) (Just y) = Just (x + y)
bar''' _ _ = Nothing
-Edward
On Fri, Jul 6, 2012 at 3:12 AM, Edward Kmett
Oh, neat. I guess it does. :) I'll hack that into my grammar when I get into work tomorrow.
My main point with that observation is it cleanly allows for multiple argument \of without breaking the intuition you get from how of already works/looks or requiring you to refactor subsequent lines, to cram parens or other odd bits of syntax in, but still lets the multi-argument crowd have a way to make multi-argument lambdas with all of the expected appropriate backtracking, if they want them. I definitely prefer \of to \case given its almost shocking brevity and the fact that the fact that it introduces a layout rule doesn't change any of the rules for when layout is introduced.
On Jul 5, 2012, at 5:33 PM, Twan van Laarhoven
wrote: On 2012-07-05 23:04, Edward Kmett wrote:
A similar generalization can be applied to the expression between case and of to permit a , separated list of expressions so this becomes applicable to the usual case construct. A naked unparenthesized , is illegal there currently as well. That would effectively be constructing then matching on an unboxed tuple without the (#, #) noise, but that can be viewed as a separate proposal' then the above is just the elision of the case component of:
Should that also generalize to nullarry 'case of'? As in
foo = case of | guard1 -> bar | guard2 -> baz
instead of
foo = case () of () | guard1 -> bar | guard2 -> baz
I realize this is getting off-topic, and has become orthogonal to the single argument λcase proposal.
Twan
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

The `multi-clause lambda' seems more elegant, if the syntactical problems could be worked out. I mean, unnamed functions are thus just like named functions, something that you'd probably think to try just as soon as you needed the feature. I don't understand the issues well enough with the layout rules to comment on Tyson Whitehead's ideas about that, and for the same reason this may be a useless idea, but what if each clause were introduced by \, would that clarify the column structure, or does indented block structure require a less-indented `layout herald'? f = \ (Just a) (Just b) | a < 0 || b < 0 -> Nothing \ (Just a) (Just b) -> Just (a * b) \ _ _ -> Nothing Donn

On 07/06/2012 05:47 AM, Donn Cave wrote:
The `multi-clause lambda' seems more elegant, if the syntactical problems could be worked out. I mean, unnamed functions are thus just like named functions, something that you'd probably think to try just as soon as you needed the feature.
I don't understand the issues well enough with the layout rules to comment on Tyson Whitehead's ideas about that, and for the same reason this may be a useless idea, but what if each clause were introduced by \, would that clarify the column structure, or does indented block structure require a less-indented `layout herald'?
f = \ (Just a) (Just b) | a < 0 || b < 0 -> Nothing \ (Just a) (Just b) -> Just (a * b) \ _ _ -> Nothing
Donn This was suggested in the ticket comments, see http://hackage.haskell.org/trac/ghc/ticket/4359#comment:29 I'll add it to the list.

If we're voting....
I think \of is all right, and multi-argument case could be handy,
which rules out using 'case of' for lambda case, because it's the
syntax for a 0-argument case:
case of
| guard1 -> ...
| guard2 -> ...
Then multi-argument lambda case could use the comma syntax of
multi-argument case.
One thing I don't think makes sense in combination is \of with
0-arguments, since any desugaring of that is not going to involve and
actual lambda expression.
-- Dan
On Thu, Jul 5, 2012 at 5:04 PM, Edward Kmett
I really like the \of proposal!
It is a clean elision with \x -> case x of becoming \of
I still don't like it directly for multiple arguments.
One possible approach to multiple arguments is what we use for multi-argument case/alt here in our little haskell-like language, Ermine, here at S&P CapitalIQ, we allow for ',' separated patterns, but without surrounding parens to be treated as a multi argument case and alt pair. Internally we desugar our usual top level bindings directly to this representation. When mixed with the \of extension, this would give you:
foo :: Num a => Maybe a -> Maybe a -> Maybe a foo = \of Just x, Just y -> Just (x*y) _, _ -> Nothing
but it wouldn't incur parens for the usual constructor pattern matches and it sits cleanly in another syntactic hole.
A similar generalization can be applied to the expression between case and of to permit a , separated list of expressions so this becomes applicable to the usual case construct. A naked unparenthesized , is illegal there currently as well. That would effectively be constructing then matching on an unboxed tuple without the (#, #) noise, but that can be viewed as a separate proposal' then the above is just the elision of the case component of:
foo mx my = case mx, my of Just x, Just y -> Just (x*y) _, _ -> Nothing
On Jul 5, 2012, at 2:49 PM, wagnerdm@seas.upenn.edu wrote:
Quoting wagnerdm@seas.upenn.edu:
Well, for what it's worth, my vote goes for a multi-argument \case. I
Just saw a proposal for \of on the reddit post about this. That's even better, since:
1. it doesn't change the list of block heralds 2. it doesn't mention case, and therefore multi-arg \of is perhaps a bit less objectionable to those who expect "case" to be single-argument 3. 40% less typing!
Can I change my vote? =) ~d
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

On 07/05/2012 10:22 PM, wagnerdm@seas.upenn.edu wrote:
Quoting Mikhail Vorozhtsov
: After 21 months of occasional arguing the lambda-case proposal(s) is in danger of being buried under its own trac ticket comments. We need fresh blood to finally reach an agreement on the syntax. Read the wiki page[1], take a look at the ticket[2], vote and comment on the proposals!
P.S. I'm CC-ing Cafe to attract more people, but please keep the discussion to the GHC Users list.
[1] http://hackage.haskell.org/trac/ghc/wiki/LambdasVsPatternMatching [2] http://hackage.haskell.org/trac/ghc/ticket/4359
Well, for what it's worth, my vote goes for a multi-argument \case. I find the comment on the wiki page about mistyping "\case Just x" instead of "\case (Just x)" a lot a bit disingenuous, since you already need these parens with today's lambda. The complaint that multi-argument cases are unorthodox doesn't really hold a lot of weight with me -- much more serious things than syntax have changed in GHC compared to the Report! \case does /not/ require parentheses. I wrote about forgetting them when using MultiClauseLambdas, e.g.
\(A b) -> ... -- \ here reminds me to use () (C d) -> ... ... Y z -> ... -- After a while I forget about them because all I see is -- Pat -> Expr, and that's instantly a case-expression -- alternative clause for me. This might as well be just my personal thing.
Is there a more formal way to cast votes...? People are still coming up with new tweaks. I'll write a summary email with the voted (so far) proposals list, maybe it will be easier to go on from there.

Hello wagnerdm, Thursday, July 5, 2012, 7:22:38 PM, you wrote:
After 21 months of occasional arguing the lambda-case proposal(s) is
this reminded me old joke about PL/I: camel is the horse created by committee i propose to return back and summarize all the requirements we have in this area. and then try to develop global solution matching them all. my summary of requirements follows:
Now we have 3 ways to performing casing/matching:
function definition: f (Just x) (Just y) | x>0 = ... multi-line, multi-parameter case statement: case ... of Just x | x>0 -> ... multi-line, single-parameter, different syntax lambda: \(Just x) (Just y) -> ... single-line, multi-parameter, case-like syntax
What we probably need is to have common syntax for all 3 cases.
another interesting feature may be ruby-style matching defined by execution of special function `match` instead of pattern matching: switch var of 1+1 -> print "var==2" [5..10] -> print "var in [5..10]" (>20) -> print "var>20" where (var `match` (1+1)), (var `match` [5..10]), (var `match` (>20)) is tested -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On 2012-07-12 23:48, Bulat Ziganshin wrote:
another interesting feature may be ruby-style matching defined by execution of special function `match` instead of pattern matching:
switch var of 1+1 -> print "var==2" [5..10] -> print "var in [5..10]" (>20) -> print "var>20"
where (var `match` (1+1)), (var `match` [5..10]), (var `match` (>20)) is tested
With view patterns you can write case var of ((== 1+1) -> True) -> print "var==2" ((`elem` [5..10]) -> True) -> print "var in [5..10]" ((> 20) -> True) -> print "var>20" Or you can just use guards, of course. Twan

On July 5, 2012 10:42:53 Mikhail Vorozhtsov wrote:
After 21 months of occasional arguing the lambda-case proposal(s) is in danger of being buried under its own trac ticket comments. We need fresh blood to finally reach an agreement on the syntax. Read the wiki page[1], take a look at the ticket[2], vote and comment on the proposals!
If I understand correctly, we currently we have \ apat1 ... apatn -> exp The possibility using '\' as a layout herald (like let, do, etc.) \ { apat1 ... apatn -> exp; ... } is suggested on the wiki, but rejected because code like so mask $ \restore -> do stmt1 ... by translating it into (Section 9.3 of the 98 Report) mask $ \ { restore -> do { } } stmt1 http://www.haskell.org/onlinereport/syntax-iso.html The reason for this is 1 - the layout level for '\' is the column of the 'restore' token 2 - the layout level for 'do' would be the column of the first token of 'stmt1' 3 - the '\' level is greater than the potential 'do' level so the fall through '{}' insertion rule fires instead of the desired '{' insertion rule 4 - the '\' level is greater than the identation level for the first token of 'stms1' (now established to not be part of the 'do') so the '}' rule fires Why not just let enclosed scopes be less indented than their outer ones? It would then correctly translate the above. This of course implies that any code that requires the original translation (i.e., where the last of multiple enclosing blocks should be an empty block) would no longer work. Is any code actually relying on this though? It seems like a pretty esoteric corner case. If not, my vote would be to relax this rule and go with '\' being a layout hearld with full case style matching (i.e., guards too). Cheers! -Tyson

On 07/06/2012 02:31 AM, Tyson Whitehead wrote:
On July 5, 2012 10:42:53 Mikhail Vorozhtsov wrote:
After 21 months of occasional arguing the lambda-case proposal(s) is in danger of being buried under its own trac ticket comments. We need fresh blood to finally reach an agreement on the syntax. Read the wiki page[1], take a look at the ticket[2], vote and comment on the proposals!
If I understand correctly, we currently we have
\ apat1 ... apatn -> exp
The possibility using '\' as a layout herald (like let, do, etc.)
\ { apat1 ... apatn -> exp; ... }
is suggested on the wiki, but rejected because code like so
mask $ \restore -> do stmt1 ...
by translating it into (Section 9.3 of the 98 Report)
mask $ \ { restore -> do { } } stmt1
http://www.haskell.org/onlinereport/syntax-iso.html
The reason for this is
1 - the layout level for '\' is the column of the 'restore' token
2 - the layout level for 'do' would be the column of the first token of 'stmt1'
3 - the '\' level is greater than the potential 'do' level so the fall through '{}' insertion rule fires instead of the desired '{' insertion rule
4 - the '\' level is greater than the identation level for the first token of 'stms1' (now established to not be part of the 'do') so the '}' rule fires
Why not just let enclosed scopes be less indented than their outer ones?
It would then correctly translate the above. This of course implies that any code that requires the original translation (i.e., where the last of multiple enclosing blocks should be an empty block) would no longer work.
Is any code actually relying on this though? It seems like a pretty esoteric corner case. If not, my vote would be to relax this rule and go with '\' being a layout hearld with full case style matching (i.e., guards too). Hm, would it work for
getArgs >>= \args -> forM_ args putStrLn ?

On 05/07/2012 20:31, Tyson Whitehead wrote:
On July 5, 2012 10:42:53 Mikhail Vorozhtsov wrote:
After 21 months of occasional arguing the lambda-case proposal(s) is in danger of being buried under its own trac ticket comments. We need fresh blood to finally reach an agreement on the syntax. Read the wiki page[1], take a look at the ticket[2], vote and comment on the proposals!
If I understand correctly, we currently we have
\ apat1 ... apatn -> exp
The possibility using '\' as a layout herald (like let, do, etc.)
\ { apat1 ... apatn -> exp; ... }
is suggested on the wiki, but rejected because code like so
mask $ \restore -> do stmt1 ...
by translating it into (Section 9.3 of the 98 Report)
mask $ \ { restore -> do { } } stmt1
http://www.haskell.org/onlinereport/syntax-iso.html
The reason for this is
1 - the layout level for '\' is the column of the 'restore' token
2 - the layout level for 'do' would be the column of the first token of 'stmt1'
3 - the '\' level is greater than the potential 'do' level so the fall through '{}' insertion rule fires instead of the desired '{' insertion rule
4 - the '\' level is greater than the identation level for the first token of 'stms1' (now established to not be part of the 'do') so the '}' rule fires
Why not just let enclosed scopes be less indented than their outer ones?
I think this is undesirable. You get strange effects like f x y = x + y where -- I just left this where here by accident g x = ... parses as f x y = x + y where { -- I just left this empty where here by accident g x = ... } and instance Exception Foo where instance Exception Bar parses as instance Exception Foo where { instance Exception Bar } That is, layout contexts that should really be empty end up surprisingly swallowing the rest of the file. Cheers, Simon
It would then correctly translate the above. This of course implies that any code that requires the original translation (i.e., where the last of multiple enclosing blocks should be an empty block) would no longer work.
Is any code actually relying on this though? It seems like a pretty esoteric corner case. If not, my vote would be to relax this rule and go with '\' being a layout hearld with full case style matching (i.e., guards too).
Cheers! -Tyson
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

On July 6, 2012 05:25:15 Simon Marlow wrote:
Why not just let enclosed scopes be less indented than their outer ones?
Let me be entirely clear about what I was thinking about. The third case for the layout mapping in Section 9.3 of the report is L ({n}:ts) (m:ms) = { : (L ts (n:m:ms)) if n > m This function takes a possibly layout sensitive token stream augmented with '{n}' for the indentation level of the first token following a grouping token that doesn't have a '{' and '<n>' for the indentation level of first tokens after newlines that are not already augmented with '{n}'. The 'L' functions maps this to a non-augmented non-layout sensitive stream. The first argument is the augmented layout stream and the current stack of indentations for any groupings in effect. The rule above inserts a '{' if there isn't one after a grouping token and the next token is at a deeper level then the current grouping level. I was proposing to make it always fire on indentation (i.e., allow enclosing scopes to be less indented). L ({n}:ts) (m:ms) = { : (L ts (n:m:ms)) if n > 0 The rest of the '{' insertion rules are for starting the first '{' on any indentation after a grouping token not followed by a '{' and for inserting a '{}' in all other cases. L ({n}:ts) [] = { : (L ts [n]) if n > 0 L ({n}:ts) ms = { : } : (L (<n>:ts) ms) http://www.haskell.org/onlinereport/syntax-iso.html
I think this is undesirable. You get strange effects like
f x y = x + y where -- I just left this where here by accident
g x = ...
parses as
f x y = x + y where { -- I just left this empty where here by accident
g x = ... }
and
instance Exception Foo where instance Exception Bar
parses as
instance Exception Foo where { instance Exception Bar }
That is, layout contexts that should really be empty end up surprisingly swallowing the rest of the file.
These would be okay under the above so long as the following lines are not indented. The issue only arises with nested ones f x = ... where g y = ... where h y = ... Now the h gets sucked into the where clause as it is empty and nested. Using the metric of what would most people expect, I agree the above is not ideal (although I would hope empty nested where clauses not really in common use). By this same metric though, I also think things like where f x = do stmt1 stmt2 mask $ let x = do stmt1 stmt2 being parsed to where { f x = do {} } stmt1 stmt2 mask $ let { x = do {} stmt1 stmt2 } is also not ideal. The real underlying issue in both these cases and changing '\' to a group token seems to be what happens on single lines with multiple groupings when the last grouping actually starts on a newline indented further than the proceeding line. Currently it depends on the depth of this new level of indentation relative to all the groupings started on that line. I think most people would expect it to just apply to the last grouping though. That is where { f x = do { stmt1 stmt2 } } mask $ let { x = do { stmt1 stmt2 } } The rule in this case would be that if the grouping began on a newline that is idented farther then the previous line, the grouping is assocated with the grouping token and when it closes, it closes all those deeper than itself. Cheers! -Tyson

On July 6, 2012 11:49:23 Tyson Whitehead wrote:
Currently it depends on the depth of this new level of indentation relative to all the groupings started on that line. I think most people would expect it to just apply to the last grouping though. That is
where { f x = do { stmt1 stmt2 } }
mask $ let { x = do { stmt1 stmt2 } }
The rule in this case would be that if the grouping began on a newline that is idented farther then the previous line, the grouping is assocated with the grouping token and when it closes, it closes all those deeper than itself.
I've thought some more about this and it seems to me that there are two ways people might intuitively think about doing grouping via indentation. 1 - the first item is on the same line and subsequent ones are lined up with it do stmt1 stmt2 2 - the first item is on a new line and subsequent ones are lined up with it. do stmt1 stmt2 The current layout engine is targeted at (1). It appears to do (2), but it is not really reliable as things start to go south if the first line happened to open more than one grouping (precisely the problem that make '\' a group token would introduce in codes). For an example, consider let greet name = do putStr "hello " putStrLn name in f "world" It currently translates into let { greet name = do {} } putStr "hello " putStrLn name in f "world" This results in an unituituve "Empty 'do' construct" error message. I propose we detected (2) and make it work too. That is, if the line ends with a grouping construct and the next line is indented relative to that line, then assume we really don't want '{}' and instead always start grouping (even if it isn't indented further than other possible groupings also started). In other words, translate the above into let { greet name = do { putStr "hello"; putStrLn name }} in f "world" This would then correctly handle the problamatic case raised in wiki where mask $ \restore -> do stmt1 stmt2 is in translated into mask $ \ { restore -> do {} } stmt1 stmt2 under the current rules if '\' is made a grouping token. The very limited scope of this (i.e., it would only apply to lines that end with a grouping construct where the next line is indented further than that line) should also address Simon's concerns regarding things like f x y = x + y where -- I just left this where here by accident g x = ... and instance Exception Foo where instance Exception Bar Cheers! -Tyson PS: To be fully precise, the modified layout decoder in 9.3 would be L (<n>:ts) i (m:ms) = ; : (L ts n (m:ms)) if m = n = } : (L (<n>:ts) n ms) if n < m L (<n>:ts) i ms = L ts n ms L ({n}:<n>:ts) i ms = { : (L ts n (n:ms)) if n > i (new rule) L ({n}:ts) i (m:ms) = { : (L ts i (n:m:ms)) if n > m (Note 1) L ({n}:ts) i [] = { : (L ts i [n]) if n > 0 (Note 1) L ({n}:ts) i ms = { : } : (L (<n>:ts) i ms) (Note 2) L (}:ts) i (0:ms) = } : (L ts i ms) (Note 3) L (}:ts) i ms = parse-error (Note 3) L ({:ts) i ms = { : (L ts i (0:ms)) (Note 4) L (t:ts) i (m:ms) = } : (L (t:ts) i ms) if m /= 0 and parse-error(t) (Note 5) L (t:ts) i ms = t : (L ts i ms) L [] i [] = [] L [] i (m:ms) = } : L [] i ms if m /= 0 (Note 6) http://www.haskell.org/onlinereport/syntax-iso.html As before, the function 'L' maps a layout-sensitive augmented token stream to a non-layout-sensitive token stream, where the augmented token stream includes '<n>' and '{n}' to, respectively, give the indentation level of the first token on a new line and that following a grouping token not followed by '{'. This time though, we allow the '{n}' '<n>' sequence (before it was supressed to just '{n}'). We also add a new state variable 'i' to track the indentation of the current line. The new rule now opens a grouping over a newline so long as the indentation is greater than the current line. Upon a less indented line, it will then close all currently open groups with an indentation less than the new line.

Couldn't we use \\ for multi-case lambdas with layout?
If not, these are my preferences in order (all are single argument versions):
1: Omission: "case of". There seems to be some support for this but it
was not included in the summary.
2: Omission with clarification: "\case of"
3: "\of" - but I think this is a little weird. It's nice to have
short keywords but not at the expense of intuition. The goal here is
to drop the variable name not the case keyword, right?
Regards,
Jonas
On 7 July 2012 06:08, Tyson Whitehead
On July 6, 2012 11:49:23 Tyson Whitehead wrote:
Currently it depends on the depth of this new level of indentation relative to all the groupings started on that line. I think most people would expect it to just apply to the last grouping though. That is
where { f x = do { stmt1 stmt2 } }
mask $ let { x = do { stmt1 stmt2 } }
The rule in this case would be that if the grouping began on a newline that is idented farther then the previous line, the grouping is assocated with the grouping token and when it closes, it closes all those deeper than itself.
I've thought some more about this and it seems to me that there are two ways people might intuitively think about doing grouping via indentation.
1 - the first item is on the same line and subsequent ones are lined up with it
do stmt1 stmt2
2 - the first item is on a new line and subsequent ones are lined up with it.
do stmt1 stmt2
The current layout engine is targeted at (1). It appears to do (2), but it is not really reliable as things start to go south if the first line happened to open more than one grouping (precisely the problem that make '\' a group token would introduce in codes). For an example, consider
let greet name = do putStr "hello " putStrLn name in f "world"
It currently translates into
let { greet name = do {} } putStr "hello " putStrLn name in f "world"
This results in an unituituve "Empty 'do' construct" error message.
I propose we detected (2) and make it work too. That is, if the line ends with a grouping construct and the next line is indented relative to that line, then assume we really don't want '{}' and instead always start grouping (even if it isn't indented further than other possible groupings also started).
In other words, translate the above into
let { greet name = do { putStr "hello"; putStrLn name }} in f "world"
This would then correctly handle the problamatic case raised in wiki where
mask $ \restore -> do stmt1 stmt2
is in translated into
mask $ \ { restore -> do {} } stmt1 stmt2
under the current rules if '\' is made a grouping token.
The very limited scope of this (i.e., it would only apply to lines that end with a grouping construct where the next line is indented further than that line) should also address Simon's concerns regarding things like
f x y = x + y where -- I just left this where here by accident
g x = ...
and
instance Exception Foo where instance Exception Bar
Cheers! -Tyson
PS: To be fully precise, the modified layout decoder in 9.3 would be
L (<n>:ts) i (m:ms) = ; : (L ts n (m:ms)) if m = n = } : (L (<n>:ts) n ms) if n < m L (<n>:ts) i ms = L ts n ms L ({n}:<n>:ts) i ms = { : (L ts n (n:ms)) if n > i (new rule) L ({n}:ts) i (m:ms) = { : (L ts i (n:m:ms)) if n > m (Note 1) L ({n}:ts) i [] = { : (L ts i [n]) if n > 0 (Note 1) L ({n}:ts) i ms = { : } : (L (<n>:ts) i ms) (Note 2) L (}:ts) i (0:ms) = } : (L ts i ms) (Note 3) L (}:ts) i ms = parse-error (Note 3) L ({:ts) i ms = { : (L ts i (0:ms)) (Note 4) L (t:ts) i (m:ms) = } : (L (t:ts) i ms) if m /= 0 and parse-error(t) (Note 5) L (t:ts) i ms = t : (L ts i ms) L [] i [] = [] L [] i (m:ms) = } : L [] i ms if m /= 0 (Note 6)
http://www.haskell.org/onlinereport/syntax-iso.html
As before, the function 'L' maps a layout-sensitive augmented token stream to a non-layout-sensitive token stream, where the augmented token stream includes '<n>' and '{n}' to, respectively, give the indentation level of the first token on a new line and that following a grouping token not followed by '{'.
This time though, we allow the '{n}' '<n>' sequence (before it was supressed to just '{n}'). We also add a new state variable 'i' to track the indentation of the current line. The new rule now opens a grouping over a newline so long as the indentation is greater than the current line.
Upon a less indented line, it will then close all currently open groups with an indentation less than the new line.
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

On 07/07/2012, Jonas Almström Duregård
Couldn't we use \\ for multi-case lambdas with layout?
If not, these are my preferences in order (all are single argument versions): 1: Omission: "case of". There seems to be some support for this but it was not included in the summary. 2: Omission with clarification: "\case of" 3: "\of" - but I think this is a little weird. It's nice to have short keywords but not at the expense of intuition. The goal here is to drop the variable name not the case keyword, right?
Regards, Jonas
Well, since this is now suddenly a ranked-choice election, I shall re-cast my vote: 1. "case of" 2. "\ of"

On 07/07/2012 16:07, Strake wrote:
On 07/07/2012, Jonas Almström Duregård
wrote: Couldn't we use \\ for multi-case lambdas with layout?
If not, these are my preferences in order (all are single argument versions): 1: Omission: "case of". There seems to be some support for this but it was not included in the summary. 2: Omission with clarification: "\case of" 3: "\of" - but I think this is a little weird. It's nice to have short keywords but not at the expense of intuition. The goal here is to drop the variable name not the case keyword, right?
Regards, Jonas
Well, since this is now suddenly a ranked-choice election, I shall re-cast my vote:
I think some misunderstanding has crept in - we're not planning to count votes or anything here. If you have new suggestions or know of reasons for/against existing proposals then please post, otherwise there's no need to post just to express your personal preference. Cheers, Simon

Hi Simon. On 07/09/2012 08:23 PM, Simon Marlow wrote:
On 07/07/2012 16:07, Strake wrote:
On 07/07/2012, Jonas Almström Duregård
wrote: Couldn't we use \\ for multi-case lambdas with layout?
If not, these are my preferences in order (all are single argument versions): 1: Omission: "case of". There seems to be some support for this but it was not included in the summary. 2: Omission with clarification: "\case of" 3: "\of" - but I think this is a little weird. It's nice to have short keywords but not at the expense of intuition. The goal here is to drop the variable name not the case keyword, right?
Regards, Jonas
Well, since this is now suddenly a ranked-choice election, I shall re-cast my vote:
I think some misunderstanding has crept in - we're not planning to count votes or anything here. If you have new suggestions or know of reasons for/against existing proposals then please post, otherwise there's no need to post just to express your personal preference. Could you express your opinion on the case "comma sugar", i.e.
case x, y of P1, P2 -> ... P3, P4 -> ... as sugar for case (# x, y #) of (# P1, P2 #) -> ... (# P3, P4 #) -> ... and respectively \case P1, P2 -> ... P3, P4 -> ... as sugar for \x y -> case x, y of P1, P2 -> ... P3, P4 -> ... ?

On 09/07/2012 15:04, Mikhail Vorozhtsov wrote:
Hi Simon.
On 07/09/2012 08:23 PM, Simon Marlow wrote:
On 07/07/2012 16:07, Strake wrote:
On 07/07/2012, Jonas Almström Duregård
wrote: Couldn't we use \\ for multi-case lambdas with layout?
If not, these are my preferences in order (all are single argument versions): 1: Omission: "case of". There seems to be some support for this but it was not included in the summary. 2: Omission with clarification: "\case of" 3: "\of" - but I think this is a little weird. It's nice to have short keywords but not at the expense of intuition. The goal here is to drop the variable name not the case keyword, right?
Regards, Jonas
Well, since this is now suddenly a ranked-choice election, I shall re-cast my vote:
I think some misunderstanding has crept in - we're not planning to count votes or anything here. If you have new suggestions or know of reasons for/against existing proposals then please post, otherwise there's no need to post just to express your personal preference. Could you express your opinion on the case "comma sugar", i.e.
case x, y of P1, P2 -> ... P3, P4 -> ...
as sugar for
case (# x, y #) of (# P1, P2 #) -> ... (# P3, P4 #) -> ...
I like this.
and respectively
\case P1, P2 -> ... P3, P4 -> ...
as sugar for
\x y -> case x, y of P1, P2 -> ... P3, P4 -> ...
That looks a bit strange to me, because I would expect \case P1, P2 -> ... P3, P4 -> ... to be a function of type (# a, b #) -> ... Cheers, Simon

On 07/09/2012 09:49 PM, Simon Marlow wrote:
On 09/07/2012 15:04, Mikhail Vorozhtsov wrote:
Hi Simon.
On 07/09/2012 08:23 PM, Simon Marlow wrote:
On 07/07/2012 16:07, Strake wrote:
On 07/07/2012, Jonas Almström Duregård
wrote: Couldn't we use \\ for multi-case lambdas with layout?
If not, these are my preferences in order (all are single argument versions): 1: Omission: "case of". There seems to be some support for this but it was not included in the summary. 2: Omission with clarification: "\case of" 3: "\of" - but I think this is a little weird. It's nice to have short keywords but not at the expense of intuition. The goal here is to drop the variable name not the case keyword, right?
Regards, Jonas
Well, since this is now suddenly a ranked-choice election, I shall re-cast my vote:
I think some misunderstanding has crept in - we're not planning to count votes or anything here. If you have new suggestions or know of reasons for/against existing proposals then please post, otherwise there's no need to post just to express your personal preference. Could you express your opinion on the case "comma sugar", i.e.
case x, y of P1, P2 -> ... P3, P4 -> ...
as sugar for
case (# x, y #) of (# P1, P2 #) -> ... (# P3, P4 #) -> ...
I like this. Good!
and respectively
\case P1, P2 -> ... P3, P4 -> ...
as sugar for
\x y -> case x, y of P1, P2 -> ... P3, P4 -> ...
That looks a bit strange to me, because I would expect
\case P1, P2 -> ... P3, P4 -> ...
to be a function of type (# a, b #) -> ...
Hm, maybe I put it slightly wrong. Desugaring is really only a means of implementation here. Would you still expect tuples for \case if you didn't see the way `case x, y of ...` was implemented (or thought that it is a primitive construct)?

On 09/07/2012 17:32, Mikhail Vorozhtsov wrote:
On 07/09/2012 09:49 PM, Simon Marlow wrote:
On 09/07/2012 15:04, Mikhail Vorozhtsov wrote:
and respectively
\case P1, P2 -> ... P3, P4 -> ...
as sugar for
\x y -> case x, y of P1, P2 -> ... P3, P4 -> ...
That looks a bit strange to me, because I would expect
\case P1, P2 -> ... P3, P4 -> ...
to be a function of type (# a, b #) -> ... Hm, maybe I put it slightly wrong. Desugaring is really only a means of implementation here.
I think the desugaring is helpful - after all, most of the syntactic sugar in Haskell is already specified by its desugaring. And in this case, the desugaring helps to explain why the multi-argument version is strange.
Would you still expect tuples for \case if you didn't see the way `case x, y of ...` was implemented (or thought that it is a primitive construct)?
Yes, I still think it's strange. We don't separate arguments by commas anywhere else in the syntax; arguments are always separated by whitespace. Cheers, Simon

Am Dienstag, den 10.07.2012, 08:53 +0100 schrieb Simon Marlow:
On 09/07/2012 17:32, Mikhail Vorozhtsov wrote:
Would you still expect tuples for \case if you didn't see the way `case x, y of ...` was implemented (or thought that it is a primitive construct)?
Yes, I still think it's strange. We don't separate arguments by commas anywhere else in the syntax; arguments are always separated by whitespace.
This is the point I wanted to make in my e-mail yesterday. Using a comma here seems to be against established Haskell syntax conventions. Best wishes, Wolfgang

Am Montag, den 09.07.2012, 21:04 +0700 schrieb Mikhail Vorozhtsov:
Could you express your opinion on the case "comma sugar", i.e.
case x, y of P1, P2 -> ... P3, P4 -> ...
as sugar for
case (# x, y #) of (# P1, P2 #) -> ... (# P3, P4 #) -> ...
and respectively
\case P1, P2 -> ... P3, P4 -> ...
as sugar for
\x y -> case x, y of P1, P2 -> ... P3, P4 -> ...
?
Although I wasn’t asked, I want to express my opinion. I think, the use of the comma is strange. When declaring functions with multiple arguments, we don’t have commas: f Nothing y = y f (Just x) y = x In lambda expressions for multi-argument functions, we also don’t have commas: \x y -> x + y Why should we have them when using a case-lambda expression for a multi-argument function? Best wishes, Wolfgang

On 07/09/2012 11:22 PM, Wolfgang Jeltsch wrote:
Am Montag, den 09.07.2012, 21:04 +0700 schrieb Mikhail Vorozhtsov:
Could you express your opinion on the case "comma sugar", i.e.
case x, y of P1, P2 -> ... P3, P4 -> ...
as sugar for
case (# x, y #) of (# P1, P2 #) -> ... (# P3, P4 #) -> ...
and respectively
\case P1, P2 -> ... P3, P4 -> ...
as sugar for
\x y -> case x, y of P1, P2 -> ... P3, P4 -> ...
?
Although I wasn’t asked, I want to express my opinion. I think, the use of the comma is strange. When declaring functions with multiple arguments, we don’t have commas:
f Nothing y = y f (Just x) y = x
In lambda expressions for multi-argument functions, we also don’t have commas:
\x y -> x + y
Why should we have them when using a case-lambda expression for a multi-argument function? The trick here is to not start with functions, but with case-expressions. If we introduce "multi-place" case-expressions not as a sugar, but as an extension of regular case-expressions (which may be /implemented/ as a sugar under the hood), then it would be only natural for pattern syntax used with "case" to transfer to lambda-case, as it already does in the current single-argument proposals (no parentheses around patterns). lambda-CASE, not LAMBDA-case (that's why I prefer \case to \of - it says clearly "hey, it's a case expression, expect stuff to be casy").

On Mon, Jul 09, 2012 at 07:22:30PM +0300, Wolfgang Jeltsch wrote:
Although I wasn’t asked, I want to express my opinion. I think, the use of the comma is strange. When declaring functions with multiple arguments, we don’t have commas:
f Nothing y = y f (Just x) y = x
In lambda expressions for multi-argument functions, we also don’t have commas:
\x y -> x + y
Why should we have them when using a case-lambda expression for a multi-argument function?
A variant of this question is easy to answer: multi-case-multi-argument function expressions are conceptually obtained as generalisation of sets of case bindings (the part after the ``of'') instead of as a generalisation of lambda expressions. This leads me to a first quick shot: Proposal 1: ``caseof'': Introduce a new layout keyword ``caseof'' to delimit (via layout or braces) the case bindings, producing the function that currently would be \ x -> case x of ... (with fresh x). Multi-case-multi-argument function definitions are currently translated into multi-case-single-argument case expressions, with the arguments collected together into tuples --- this might provide motivation for the commas. This leads me to a second quick shot: Proposal 2: ``no-multiple-argument-case'': Make no further changes to the case bindings syntax. Programmers who want multiple arguments can put them into tuples and curry the whole caseof construct, which is reasonably cheap syntactically: zip = curry $ caseof ([] , ys ) -> [] (xs , [] ) -> [] (x : xs , y : ys) -> (x , y) : zip xs ys This has the advantage that no new rules need to be added to syntax or semantics. Side note (and shameless plug): The above is partially inspired by my work on the pattern matching calculus (PMC) where groups of case bindings form the second syntactic category of ``matchings'' (besides expressions). ``caseof'' then corresponds to the wrapping {| m |} that turns a matching into an expression, and Haskell's sequence of case bindings would be mapped to the monoid of matchings with with empty matching as unit and matching alternative as composition. PMC includes two additional features that allow equational reasoning with matchings (case binding groups): Argument supply: Applying a matching to an argument without first converting the matching into an expression. This feature can be seen as a generalisation of pattern guards. Nestable matching construction: Individual cases in PMC are of shape ``p -> m'' with a matching right-hand side instead of an expression``p -> e'' in Haskell. Nestable matching construction allows construction of multiple-argument pattern matching functions with more liberal shapes than the strict matrix shape required for function definitions, but with a different semantics. That more liberal shape can already be achieved with the tuple scheme of proposal 2 above: f = curry $ curry $ caseof (p , []) -> ... ((xs, []) , z : zs) -> ... _ -> ... and zip = curry $ caseof (x : xs , y : ys) -> (x , y) : zip xs ys _ -> [] Integrating argument supply and nestable matching construction into Haskell would be a more far-reaching change --- an ``easy'' attempt at nestable matching construction alone would turn the -> of case bindings into a layout keyword, and insert conversion of expressions into zero-argument matchings (``return'') automagically: zip = caseof [] -> [] x : xs -> [] -> [] y : ys -> (x , y) : zip xs ys The important aspect of considering the part after -> as a matching instead of as an expression is fall-through --- the nested patterns act somewhat like pattern guards: zip = caseof x : xs -> y : ys -> (x , y) : zip xs ys _ -> _ -> [] The two alternatives in this last example are intentionally not aligned to emphasise the fact that the two 2-argument matchings are constructed completely indepnedent from each other. Automagical insertion of conversion of expressions into zero-argument matchings depends on having no expressions that can legally be parsed as matchings. With what I sketched above, this might actually work, but I cannot claim that I have fully thought this through. If it can be made to work, it could be called Proposal 3: ``nestable case bindings''. Generalising pattern guard syntax into argument supply requires a second syntactic construct that contains a group of case bindings; most easily this would be another layout keyword, say ``into'' (in the PMC papers, this is $\righttriangle$; better keywords would be welcome; I guess ``|>'' is not a good idea...): Pattern guards are of shape ``pat <- arg'' with the argument to the right, as in SPJ's ``clunky'': clunky env var1 var2 | Just val1 <- lookup env var1 , Just val2 <- lookup env var2 = val1 + val2 ...other equations for clunky... For argument supply and ``into'' we use the opposite sequence, ``arg into pat'', and clunky could then become: clunky = caseof env -> var1 -> var2 -> lookup env var1 into Just val1 -> lookup env var2 into Just val2 -> val1 + val2 ... other case bindings for clunky .... (This runs into similar nested layout issues as discussed recently; if we were to change the layout rule (perhaps only for the new keywords) to not apply if the next token is separated from the layout keyword by only a single space, we could turn this into a more compact shape: clunky = caseof env -> var1 -> var2 -> lookup env var1 into Just val1 -> lookup env var2 into Just val2 -> val1 + val2 ... other case bindings for clunky .... (The alignment of the two lookups and their preceding -> is irrelevant here.) ) ``into'' would generalise pattern guards by allowing the same expression to be matched against different patterns and still enable fall-through: f = caseof [x] -> g x into [] -> [] a : b : bs -> (a, b) : h bs ... other cases, including g returning a singleton ... This could be: Proposal 4: ``case-group argument supply'' or ``generalised pattern guards'' Best wishes, Wolfram --------------------------------------------- @InProceedings{Kahl-2004a, author = {Wolfram Kahl}, title = {Basic Pattern Matching Calculi: A Fresh View on Matching Failure}, crossref = {FLOPS2004}, pages = {276--290}, DOI = {10.1007/978-3-540-24754-8_20}, SpringerURL = {http://www.springerlink.com/content/3jet4qgw1q2nu0a8/}, abstract = {We propose pattern matching calculi as a refinement of $\lambda$-calculus that integrates mechanisms appropriate for fine-grained modelling of non-strict pattern matching. Compared with the functional rewriting strategy usually employed to define the operational semantics of pattern matching in non-strict functional programming languages like Haskell or Clean, our pattern matching calculi achieve the same effects using simpler and more local rules. The main device is to embed into expressions the separate syntactic category of matchings; the resulting language naturally encompasses pattern guards and Boolean guards as special cases. By allowing a confluent reduction system and a normalising strategy, these pattern matching calculi provide a new basis for operational semantics of non-strict programming languages and also for implementations.} } @InProceedings{Kahl-Carette-Ji-2006a, author = {Wolfram Kahl and Jacques Carette and Xiaoheng Ji}, title = {Bimonadic Semantics for Basic Pattern Matching Calculi}, crossref = {MPC2006}, pages = {253--273}, DOI = {10.1007/11783596_16}, SpringerURL = {http://www.springerlink.com/content/2715070606u63648/} }

On July 7, 2012 00:08:26 Tyson Whitehead wrote:
The very limited scope of this (i.e., it would only apply to lines that end with a grouping construct where the next line is indented further than that line) should also address Simon's concerns regarding things like
f x y = x + y where -- I just left this where here by accident
g x = ...
and
instance Exception Foo where instance Exception Bar
The only thing that would still break is a line that starts multiple groupings, where the last is a valid empty groups (i.e., let or where) and the next line is further indented then the previous line. The least grotesque/contrived examples I could think of are do let stmt1 stmt2 and let f x = ... where g y = ... Cheers! -Tyson

On 07/07/2012 05:08, Tyson Whitehead wrote:
PS: To be fully precise, the modified layout decoder in 9.3 would be
L (<n>:ts) i (m:ms) = ; : (L ts n (m:ms)) if m = n = } : (L (<n>:ts) n ms) if n < m L (<n>:ts) i ms = L ts n ms L ({n}:<n>:ts) i ms = { : (L ts n (n:ms)) if n > i (new rule) L ({n}:ts) i (m:ms) = { : (L ts i (n:m:ms)) if n > m (Note 1) L ({n}:ts) i [] = { : (L ts i [n]) if n > 0 (Note 1) L ({n}:ts) i ms = { : } : (L (<n>:ts) i ms) (Note 2) L (}:ts) i (0:ms) = } : (L ts i ms) (Note 3) L (}:ts) i ms = parse-error (Note 3) L ({:ts) i ms = { : (L ts i (0:ms)) (Note 4) L (t:ts) i (m:ms) = } : (L (t:ts) i ms) if m /= 0 and parse-error(t) (Note 5) L (t:ts) i ms = t : (L ts i ms) L [] i [] = [] L [] i (m:ms) = } : L [] i ms if m /= 0 (Note 6)
http://www.haskell.org/onlinereport/syntax-iso.html
As before, the function 'L' maps a layout-sensitive augmented token stream to a non-layout-sensitive token stream, where the augmented token stream includes '<n>' and '{n}' to, respectively, give the indentation level of the first token on a new line and that following a grouping token not followed by '{'.
This time though, we allow the '{n}' '<n>' sequence (before it was supressed to just '{n}'). We also add a new state variable 'i' to track the indentation of the current line. The new rule now opens a grouping over a newline so long as the indentation is greater than the current line.
Upon a less indented line, it will then close all currently open groups with an indentation less than the new line.
It's a little hard to evaluate this without trying it for real to see whether it breaks any existing code. However, unless there are very strong reasons to do so, I would argue against making the layout rule *more* complicated. I find the current rule behaves quite intuitively, even though its description is hard to understand and it is virtually impossible to implement. I now think '\' is too quiet to introduce a new layout context. The pressing need is really for a combination of '\' and 'case', that is single-argument so that we don't have to write parentheses. I think '\case' does the job perfectly. If you want a multi-clause multi-argument function, then give it a name. Cheers, Simon

On 09/07/12 14:44, Simon Marlow wrote:
I now think '\' is too quiet to introduce a new layout context. The pressing need is really for a combination of '\' and 'case', that is single-argument so that we don't have to write parentheses. I think '\case' does the job perfectly. If you want a multi-clause multi-argument function, then give it a name.
There is an advantage here for "\of" in favor of "\case", namely that "of" already introduces layout, while "case" does not. Twan

On 07/09/2012 09:52 PM, Twan van Laarhoven wrote:
On 09/07/12 14:44, Simon Marlow wrote:
I now think '\' is too quiet to introduce a new layout context. The pressing need is really for a combination of '\' and 'case', that is single-argument so that we don't have to write parentheses. I think '\case' does the job perfectly. If you want a multi-clause multi-argument function, then give it a name.
There is an advantage here for "\of" in favor of "\case", namely that "of" already introduces layout, while "case" does not. Do you think that adding "\" + "case" as a layout herald would complicate the language spec and/or confuse users? Because it certainly does not complicate the implementation (there is a patch for \case already). IMO \case is more descriptive, "of" is just a preposition after all.

On 07/09/2012 06:01 PM, Mikhail Vorozhtsov wrote:
On 07/09/2012 09:52 PM, Twan van Laarhoven wrote:
On 09/07/12 14:44, Simon Marlow wrote:
I now think '\' is too quiet to introduce a new layout context. The pressing need is really for a combination of '\' and 'case', that is single-argument so that we don't have to write parentheses. I think '\case' does the job perfectly. If you want a multi-clause multi-argument function, then give it a name.
There is an advantage here for "\of" in favor of "\case", namely that "of" already introduces layout, while "case" does not. Do you think that adding "\" + "case" as a layout herald would complicate the language spec and/or confuse users? Because it certainly does not complicate the implementation (there is a patch for \case already).
Just being anal here, but: The existence of a patch to implement X does not mean that X doesn't complicate the implemenatation. ... as you were.

On 07/10/2012 01:09 AM, Bardur Arantsson wrote:
On 07/09/2012 06:01 PM, Mikhail Vorozhtsov wrote:
On 07/09/2012 09:52 PM, Twan van Laarhoven wrote:
On 09/07/12 14:44, Simon Marlow wrote:
I now think '\' is too quiet to introduce a new layout context. The pressing need is really for a combination of '\' and 'case', that is single-argument so that we don't have to write parentheses. I think '\case' does the job perfectly. If you want a multi-clause multi-argument function, then give it a name.
There is an advantage here for "\of" in favor of "\case", namely that "of" already introduces layout, while "case" does not. Do you think that adding "\" + "case" as a layout herald would complicate the language spec and/or confuse users? Because it certainly does not complicate the implementation (there is a patch for \case already).
Just being anal here, but: The existence of a patch to implement X does not mean that X doesn't complicate the implemenatation. In general, yes. But that particular patch[1] uses ~20 lines of pretty straightforward (if I'm allowed to say that about the code I wrote myself) code to handle layout. Which in my book is not complex at all.
[1] http://hackage.haskell.org/trac/ghc/attachment/ticket/4359/one-arg-lambda-ca...

On 10/07/2012 07:33, Mikhail Vorozhtsov wrote:
On 07/10/2012 01:09 AM, Bardur Arantsson wrote:
On 07/09/2012 06:01 PM, Mikhail Vorozhtsov wrote:
On 07/09/2012 09:52 PM, Twan van Laarhoven wrote:
On 09/07/12 14:44, Simon Marlow wrote:
I now think '\' is too quiet to introduce a new layout context. The pressing need is really for a combination of '\' and 'case', that is single-argument so that we don't have to write parentheses. I think '\case' does the job perfectly. If you want a multi-clause multi-argument function, then give it a name.
There is an advantage here for "\of" in favor of "\case", namely that "of" already introduces layout, while "case" does not. Do you think that adding "\" + "case" as a layout herald would complicate the language spec and/or confuse users? Because it certainly does not complicate the implementation (there is a patch for \case already).
Just being anal here, but: The existence of a patch to implement X does not mean that X doesn't complicate the implemenatation. In general, yes. But that particular patch[1] uses ~20 lines of pretty straightforward (if I'm allowed to say that about the code I wrote myself) code to handle layout. Which in my book is not complex at all.
[1] http://hackage.haskell.org/trac/ghc/attachment/ticket/4359/one-arg-lambda-ca...
The need to keep track of the previous token in the lexer *is* ugly though. Cheers, Simon

Right, it seems to me that there are basically three reasonable proposals here:
1. "\ of" with multiple arguments. This is consistent with existing
layout, and seems like a nice generalization of lambda syntax.
2. "case of" with a single argument. This is consistent with existing
layout, and seems like a nice generalization of sections.
3. "\" introducing layout, possibly with changes to layout rules. A
much more intrusive change, but it does have a nice efficiency to it.
Either of the first two would be fine. For that matter, they could
even *both* be done -- with #2 being a shorthand to avoid parentheses
-- without seeming too redundant to me. I tend to see the third
option as too intrusive and dangerous, but I can see the argument for
doing it. Given that we have these three options, I really don't see
the benefit to "\ case" or similar ideas, which complicate layout
rules for little reason, and mix syntax in such a way that it's
difficult for me at least to even predict whether parentheses are
required.
On Mon, Jul 9, 2012 at 8:52 AM, Twan van Laarhoven
On 09/07/12 14:44, Simon Marlow wrote:
I now think '\' is too quiet to introduce a new layout context. The pressing need is really for a combination of '\' and 'case', that is single-argument so that we don't have to write parentheses. I think '\case' does the job perfectly. If you want a multi-clause multi-argument function, then give it a name.
There is an advantage here for "\of" in favor of "\case", namely that "of" already introduces layout, while "case" does not.
Twan
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Am Montag, den 09.07.2012, 10:20 -0600 schrieb Chris Smith:
Right, it seems to me that there are basically three reasonable proposals here:
1. "\ of" with multiple arguments. This is consistent with existing layout, and seems like a nice generalization of lambda syntax. 2. "case of" with a single argument. This is consistent with existing layout, and seems like a nice generalization of sections. 3. "\" introducing layout, possibly with changes to layout rules. A much more intrusive change, but it does have a nice efficiency to it.
I strongly favor a solution where lambda-case expressions start with \, because this can be generalized to proc expressions from arrow syntax simply by replacing the \ with proc. Take, for example, the following function definition: f (Left x) = g x f (Right y) = h y Now, let’s make an arrow version of it: f = proc e -> case e of Left x -> g -< x Right y -> h -< y It would be great if we could write something like this instead: f = proc of Left x -> g -< x Right y -> h -< y This is not just a contrived issue. In my current work on Grapefruit, I encounter this situation quite often, and I would love to get rid of the extra overhead I have to deal with now. Best wishes, Wolfgang

| I strongly favor a solution where lambda-case expressions start with \, | because this can be generalized to proc expressions from arrow syntax | simply by replacing the \ with proc. | | Take, for example, the following function definition: | | f (Left x) = g x | f (Right y) = h y | | Now, let’s make an arrow version of it: | | f = proc e -> case e of | Left x -> g -< x | Right y -> h -< y | | It would be great if we could write something like this instead: | | f = proc of | Left x -> g -< x | Right y -> h -< y I don't think I was aware of the proc part. I think it's very helpful if lambdas start with a lambda, which to me suggests \case. I'm not keen on \of; "case" says "case analysis" more clearly. But you presumably do not want \proc, because proc is the lambda. So that would leave use with "\case" and "proc of" as the two constructs. Perhaps the lesser of the evils, but a bit inconsistent. Simon

On 07/10/2012 01:53 PM, Simon Peyton-Jones wrote:
| I strongly favor a solution where lambda-case expressions start with \, | because this can be generalized to proc expressions from arrow syntax | simply by replacing the \ with proc. | | Take, for example, the following function definition: | | f (Left x) = g x | f (Right y) = h y | | Now, let’s make an arrow version of it: | | f = proc e -> case e of | Left x -> g -< x | Right y -> h -< y | | It would be great if we could write something like this instead: | | f = proc of | Left x -> g -< x | Right y -> h -< y
I don't think I was aware of the proc part.
I think it's very helpful if lambdas start with a lambda, which to me suggests \case. I'm not keen on \of; "case" says "case analysis" more clearly. But you presumably do not want \proc, because proc is the lambda. So that would leave use with "\case" and "proc of" as the two constructs. Perhaps the lesser of the evils, but a bit inconsistent. Why not use "proc case"?

I think it's very helpful if lambdas start with a lambda, which to me suggests \case.
I'd be interested to hear that explained a little further. To me it isn't obvious that `case of' is `a lambda', but it's obvious enough what it is and how it works (or would work) - it's `case' with type a -> b instead of just b ... and really the backslash just seems to confuse the issue. I don't remember it from discussions of this proposal in years past.
... But you presumably do not want \proc, because proc is the lambda.
I also wondered if `case of' could be equally well generalized to allow for `proc of', but I would certainly have no idea. Donn

Am Dienstag, den 10.07.2012, 06:53 +0000 schrieb Simon Peyton-Jones:
I strongly favor a solution where lambda-case expressions start with \, because this can be generalized to proc expressions from arrow syntax simply by replacing the \ with proc.
[…]
I think it's very helpful if lambdas start with a lambda, which to me suggests \case. I'm not keen on \of; "case" says "case analysis" more clearly. But you presumably do not want \proc, because proc is the lambda. So that would leave use with "\case" and "proc of" as the two constructs. Perhaps the lesser of the evils, but a bit inconsistent.
If we use \case for functions, we should use proc case for arrows; if we use \of for functions, we should use proc of for arrows. By the way, is proc a layout herald already? Best wishes, Wolfgang

On Tue, Jul 10, 2012 at 5:53 AM, Wolfgang Jeltsch
If we use \case for functions, we should use proc case for arrows; if we use \of for functions, we should use proc of for arrows.
By the way, is proc a layout herald already?
No, proc is not a layout herald. The normal pattern is to use a do in the command part of the proc syntax, so it's do that introduces the layout. So "proc of" would fit in cleanly as a way to do proc with multiple patterns. Or "proc case", but again that's just a really ugly language wart, IMO uglier than just writing out the longhand version of "proc x -> case x of". -- Chris Smith

Hello, I am late to the discussion and this is not entirely on topic, for which I apologize, but I like the multi-branch case syntax someone mentioned earlier: Writing:
case | p1 -> e1 | p2 -> e2 | ...
desugars to:
case () of _ | p1 -> e2 | p2 -> e2 | ...
-Iavor
PS: I think it also makes sense to use "if" instead of "case" for this.
Either way, I find myself writing these kind of cases quite often, so
having the sugar would be nice.
On Tue, Jul 10, 2012 at 8:55 AM, Chris Smith
On Tue, Jul 10, 2012 at 5:53 AM, Wolfgang Jeltsch
wrote: If we use \case for functions, we should use proc case for arrows; if we use \of for functions, we should use proc of for arrows.
By the way, is proc a layout herald already?
No, proc is not a layout herald. The normal pattern is to use a do in the command part of the proc syntax, so it's do that introduces the layout. So "proc of" would fit in cleanly as a way to do proc with multiple patterns. Or "proc case", but again that's just a really ugly language wart, IMO uglier than just writing out the longhand version of "proc x -> case x of".
-- Chris Smith
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

On 07/12/2012 04:27 AM, Iavor Diatchki wrote:
Hello, I am late to the discussion and this is not entirely on topic, for which I apologize, but I like the multi-branch case syntax someone mentioned earlier:
Writing:
case | p1 -> e1 | p2 -> e2 | ...
desugars to:
case () of _ | p1 -> e2 | p2 -> e2 | ...
-Iavor PS: I think it also makes sense to use "if" instead of "case" for this. Either way, I find myself writing these kind of cases quite often, so having the sugar would be nice. See [1]. I plan to implement it after lambda-case goes in.
[1] http://hackage.haskell.org/trac/haskell-prime/wiki/MultiWayIf

Am Samstag, den 07.07.2012, 00:08 -0400 schrieb Tyson Whitehead:
I've thought some more about this and it seems to me that there are two ways people might intuitively think about doing grouping via indentation.
1 - the first item is on the same line and subsequent ones are lined up with it
do stmt1 stmt2
2 - the first item is on a new line and subsequent ones are lined up with it.
do stmt1 stmt2
The current layout engine is targeted at (1). It appears to do (2), but it is not really reliable as things start to go south if the first line happened to open more than one grouping (precisely the problem that make '\' a group token would introduce in codes). For an example, consider
let greet name = do putStr "hello " putStrLn name in f "world"
It currently translates into
let { greet name = do {} } putStr "hello " putStrLn name in f "world"
This results in an unituituve "Empty 'do' construct" error message.
The problem is that your example is not consistently using (2). A pure (2)-example would look like this: let greet name = do putStr "hello " putStrLn name in greet "world" And this works. :-) Best wishes, Wolfgang

On 07/05/2012 09:42 PM, Mikhail Vorozhtsov wrote:
Hi.
After 21 months of occasional arguing the lambda-case proposal(s) is in danger of being buried under its own trac ticket comments. We need fresh blood to finally reach an agreement on the syntax. Read the wiki page[1], take a look at the ticket[2], vote and comment on the proposals!
P.S. I'm CC-ing Cafe to attract more people, but please keep the discussion to the GHC Users list.
[1] http://hackage.haskell.org/trac/ghc/wiki/LambdasVsPatternMatching [2] http://hackage.haskell.org/trac/ghc/ticket/4359
Preliminary votes: * LambdaCase \case: 3 (Christopher, Felipe, Gábor) * LambdaCase \of: 1 (Edward) * MultiClauseLambdas \of: 1 (Daniel) * MultiClauseLambdas with \ in each clause: 1 (Donn) * MultiClauseLambdas with layout rules tweaking: 1 (Tyson) Note that LambdaCase variants do /not/ require parentheses around patterns while MultiClauseLambdas variants do. Did I forget/misunderstand someone? It would be great to have GHC HQ input on the new proposals (layout rules tweaking (Tyson) and case comma sugar (Edward)).

On 05/07/2012, Mikhail Vorozhtsov
Hi.
After 21 months of occasional arguing the lambda-case proposal(s) is in danger of being buried under its own trac ticket comments. We need fresh blood to finally reach an agreement on the syntax. Read the wiki page[1], take a look at the ticket[2], vote and comment on the proposals!
+1 for "\ of" multi-clause lambdas It looks like binding "of" to me, which it ain't, but it is nicely brief...

Whoops, my earlier answer forgot to copy mailing lists... I would love to
see \of, but I really don't think this is important enough to make case
sometimes introduce layout and other times not. If it's going to obfuscate
the lexical syntax like that, I'd rather just stick with \x->case x of.
On Jul 6, 2012 3:15 PM, "Strake"
On 05/07/2012, Mikhail Vorozhtsov
wrote: Hi.
After 21 months of occasional arguing the lambda-case proposal(s) is in danger of being buried under its own trac ticket comments. We need fresh blood to finally reach an agreement on the syntax. Read the wiki page[1], take a look at the ticket[2], vote and comment on the proposals!
+1 for "\ of" multi-clause lambdas
It looks like binding "of" to me, which it ain't, but it is nicely brief...
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Personally I don't see why everyone appears to prefer the syntax with
\ in it over just the obvious case section syntax which was originally
proposed.
case of { ... }
looks much better to me than
\case of { ... }
and the former makes sense to me as a simple extension of operator
sections to another part of the syntax.
Does anyone else agree?
On 6 July 2012 20:40, Chris Smith
Whoops, my earlier answer forgot to copy mailing lists... I would love to see \of, but I really don't think this is important enough to make case sometimes introduce layout and other times not. If it's going to obfuscate the lexical syntax like that, I'd rather just stick with \x->case x of.
On Jul 6, 2012 3:15 PM, "Strake"
wrote: On 05/07/2012, Mikhail Vorozhtsov
wrote: Hi.
After 21 months of occasional arguing the lambda-case proposal(s) is in danger of being buried under its own trac ticket comments. We need fresh blood to finally reach an agreement on the syntax. Read the wiki page[1], take a look at the ticket[2], vote and comment on the proposals!
+1 for "\ of" multi-clause lambdas
It looks like binding "of" to me, which it ain't, but it is nicely brief...
_______________________________________________ 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 Thu, Jul 12, 2012 at 01:38:56PM -0400, Cale Gibbard wrote:
Personally I don't see why everyone appears to prefer the syntax with \ in it over just the obvious case section syntax which was originally proposed.
I don't think that the 'case section syntax' is obvious, because I don't see the similarity between a function definition and a partial function application. Always using '\' would be a visual hint for a function definition. Greetings, Daniel

There are of course already lots of ways to create functions which
don't involve \
I mentioned sections (like (+1) desugaring to (\x -> x + 1)) already,
and of course, one can partially apply or compose and transform other
functions without explicit lambdas.
We're not exactly talking about function definitions, so much as
expressions whose value happens to be a function. The point is just
that there are already a few other places in the syntax where the
omission of a value results in a function having the omitted value as
its parameter. At least to me, it seems natural to extend that pattern
in this case.
On 12 July 2012 15:03, Daniel Trstenjak
On Thu, Jul 12, 2012 at 01:38:56PM -0400, Cale Gibbard wrote:
Personally I don't see why everyone appears to prefer the syntax with \ in it over just the obvious case section syntax which was originally proposed.
I don't think that the 'case section syntax' is obvious, because I don't see the similarity between a function definition and a partial function application.
Always using '\' would be a visual hint for a function definition.
Greetings, Daniel

On Thu, Jul 12, 2012 at 03:13:42PM -0400, Cale Gibbard wrote:
There are of course already lots of ways to create functions which don't involve \
Well, I think it should be clear that we're talking here about anonymous functions.
We're not exactly talking about function definitions, so much as expressions whose value happens to be a function. The point is just that there are already a few other places in the syntax where the omission of a value results in a function having the omitted value as its parameter. At least to me, it seems natural to extend that pattern in this case.
The question is, how self explanatory is the syntax? I think that sections and partial function application are pretty self explanatory just by looking at the expression, because it tells you visually pretty well what it actually does. 'case of {}' isn't self explanatory, because you don't have a visual hint what happend with the parameter between 'case' and 'of'. I can see why - I think it was Simon - proposed '\of', because you could read it as if the parameter between 'case' and 'of' is applied to the 'of'. I don't like the version 'case of {}' and I even don't like the version '\case of' that much, because I think both versions degrade the syntax of Haskell, which is part of the beauty of Haskell and we shouldn't rush in expanding it, only for pragmatic reasons. Greetings, Daniel

On 13/07/2012 3:08 AM, Cale Gibbard wrote:
Personally I don't see why everyone appears to prefer the syntax with \ in it over just the obvious case section syntax which was originally proposed.
case of { ... }
looks much better to me than
\case of { ... }
and the former makes sense to me as a simple extension of operator sections to another part of the syntax.
Does anyone else agree?
yes. I prefer "case of" rather than "\case of" for aesthetic reasons.

Am Donnerstag, den 12.07.2012, 13:38 -0400 schrieb Cale Gibbard:
Personally I don't see why everyone appears to prefer the syntax with \ in it over just the obvious case section syntax which was originally proposed.
case of { ... }
looks much better to me than
\case of { ... }
and the former makes sense to me as a simple extension of operator sections to another part of the syntax.
Does anyone else agree?
I’m strongly opposed to the case of { ... } syntax, because there seems to be no natural arrow expression analog of it. A notation that starts with \ (like “\case”) can be carried over to arrow expressions by replacing the \ with proc (like in “proc case”). Best wishes, Wolfgang

On Fri, Jul 13, 2012 at 01:21:25PM +0100, Wolfgang Jeltsch wrote:
I’m strongly opposed to the
case of { ... }
syntax, because there seems to be no natural arrow expression analog of it.
A notation that starts with \ (like “\case”) can be carried over to arrow expressions by replacing the \ with proc (like in “proc case”).
Remember that there is a \ in arrow notation in addition to proc. So one might expect any abbreviation for \x -> case x of {...} to mean the same \ thing in arrow notation too. If the abbreviation contained no \, there would be no way to replace it with a proc.

Am Freitag, den 13.07.2012, 13:40 +0100 schrieb Ross Paterson:
Remember that there is a \ in arrow notation in addition to proc. So one might expect any abbreviation for \x -> case x of {...} to mean the same \ thing in arrow notation too.
I completely agree. I had forgotten about the \ in arrow notation.
If the abbreviation contained no \, there would be no way to replace it with a proc.
Exactly. It seems, however, that it has finally been decided to use the syntax with \case, so all looks good so far. :-) Best wishes, Wolfgang

Am Montag, den 16.07.2012, 21:26 +0300 schrieb Wolfgang Jeltsch:
Am Freitag, den 13.07.2012, 13:40 +0100 schrieb Ross Paterson:
Remember that there is a \ in arrow notation in addition to proc. So one might expect any abbreviation for \x -> case x of {...} to mean the same \ thing in arrow notation too.
I completely agree. I had forgotten about the \ in arrow notation.
I have opened a new ticket for arrow analogs of lambda case and multi-way if: http://hackage.haskell.org/trac/ghc/ticket/7081 Best wishes, Wolfgang

Quoth Cale Gibbard:
Personally I don't see why everyone appears to prefer the syntax with \ in it over just the obvious case section syntax which was originally proposed.
case of { ... } ... Does anyone else agree?
Yes. I don't see this as an `anonymous function' in any special sense, only inasmuch as the workaround in its absence involves one. I.e., if I for some reason had been compelled to write \ a -> hPutStrLn stdout a ... that wouldn't make "hPutStrLn stdout" an anonymous function in my book. Neither is `case of ...' an anonymous function, or functions. Donn

Am Freitag, den 13.07.2012, 06:57 -0700 schrieb Donn Cave:
Quoth Cale Gibbard:
Personally I don't see why everyone appears to prefer the syntax with \ in it over just the obvious case section syntax which was originally proposed.
case of { ... } ... Does anyone else agree?
Yes. I don't see this as an `anonymous function' in any special sense, only inasmuch as the workaround in its absence involves one. I.e., if I for some reason had been compelled to write \ a -> hPutStrLn stdout a
... that wouldn't make "hPutStrLn stdout" an anonymous function in my book. Neither is `case of ...' an anonymous function, or functions.
Donn
What is an anonymous function? A function that has no name, that is, a function that is not assigned to an identifier. So (+ 1), \x -> x + 1, and any lambda case are all anonymous functions. Best wishes, Wolfgang

Quoth Wolfgang Jeltsch
What is an anonymous function? A function that has no name, that is, a function that is not assigned to an identifier. So (+ 1), \x -> x + 1, and any lambda case are all anonymous functions.
All right, that more general definition works for me. It doesn't take much away from my point, though - in any case, clarity doesn't demand that we use \ for all these things, only for \ x -> x + 1. Donn

On Thu, Jul 12, 2012 at 7:38 PM, Cale Gibbard
Personally I don't see why everyone appears to prefer the syntax with \ in it over just the obvious case section syntax which was originally proposed.
case of { ... }
looks much better to me than
\case of { ... }
and the former makes sense to me as a simple extension of operator sections to another part of the syntax.
Does anyone else agree?
I also completely agree, but I don't want my opinion to get in the way of progress. -- Your ship was caught in a monadic eruption.

On Fri, Jul 13, 2012 at 9:12 PM, Gábor Lehel
On Thu, Jul 12, 2012 at 7:38 PM, Cale Gibbard
wrote: case of { ... }
looks much better to me than
\case of { ... }
I also completely agree, but I don't want my opinion to get in the way of progress.
I don't much care whether what is implemented is "\case" or "case of" or even "\of" (even though that last reads weird), but "\case of" strikes me as including syntactic noise (a pointless extra token). One or the other; not both. -- brandon s allbery allbery.b@gmail.com wandering unix systems administrator (available) (412) 475-9364 vm/sms

Mikhail Vorozhtsov
Hi.
After 21 months of occasional arguing the lambda-case proposal(s) is in danger of being buried under its own trac ticket comments. We need fresh blood to finally reach an agreement on the syntax. Read the wiki page[1], take a look at the ticket[2], vote and comment on the proposals!
P.S. I'm CC-ing Cafe to attract more people, but please keep the discussion to the GHC Users list.
[1] http://hackage.haskell.org/trac/ghc/wiki/LambdasVsPatternMatching [2] http://hackage.haskell.org/trac/ghc/ticket/4359
Apart from lambda match, the suggestions seem to me to be poor solutions to an old piece of bad design and they don’t fit very well with the look of haskell. Way back at the beginning of time, I was against pattern matching altogether as it seemed like a seductive feature that wouldn’t generalise very well. I wanted algebraic combinations of some form of guarded expressions. But the rest of the committee wanted pattern matching (I think they were right — the seductive aspect is important and if I had had my way Haskell would not have been as popular as it is now) and it seemed logical to have pattern matching in lambdas too. But that led to lambdas that can fail, which I think was a bad decision. What I would rather have happen now is that we introduce a distinction between pure destructor patterns (where a type is not a sum) and patterns that can fail. Then mandate that at some future date \pattern1 -> expression will be invalid unless pattern1 is a pure destructor, (but to begin with the compiler would just issue a warning). Now \pattern1 -> expression has type a -> b without a hidden exception. Then add another lambda for patterns that can fail, eg \? pattern -> expression, which has a type reflecting the fact that the match can fail, eg a -> Maybe b. Add operators to combine such lambda expressions (eg a symbol — on the lines of || — for liftA2 mplus) and a means of getting the answer out when all the bases are covered (something a bit handier than just having an operator for liftA2 fromMaybe, though that would cover all the use cases that end with \? _ -> e). lambda match is very close to that and worked out in more detail. So I’m against the other proposals. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

On 07/05/2012 09:42 PM, Mikhail Vorozhtsov wrote:
Hi.
After 21 months of occasional arguing the lambda-case proposal(s) is in danger of being buried under its own trac ticket comments. We need fresh blood to finally reach an agreement on the syntax. Read the wiki page[1], take a look at the ticket[2], vote and comment on the proposals!
P.S. I'm CC-ing Cafe to attract more people, but please keep the discussion to the GHC Users list.
[1] http://hackage.haskell.org/trac/ghc/wiki/LambdasVsPatternMatching [2] http://hackage.haskell.org/trac/ghc/ticket/4359
GHC HQ has reached a consensus[1]. [1] http://hackage.haskell.org/trac/ghc/ticket/4359#comment:69

Good news everyone. LambdaCase and MultiWayIf are now in HEAD. Thanks
for participating in the final push!
On Thu, Jul 5, 2012 at 9:42 PM, Mikhail Vorozhtsov
Hi.
After 21 months of occasional arguing the lambda-case proposal(s) is in danger of being buried under its own trac ticket comments. We need fresh blood to finally reach an agreement on the syntax. Read the wiki page[1], take a look at the ticket[2], vote and comment on the proposals!
P.S. I'm CC-ing Cafe to attract more people, but please keep the discussion to the GHC Users list.
[1] http://hackage.haskell.org/trac/ghc/wiki/LambdasVsPatternMatching [2] http://hackage.haskell.org/trac/ghc/ticket/4359
participants (27)
-
Bardur Arantsson
-
Brandon Allbery
-
Bulat Ziganshin
-
Cale Gibbard
-
Chris Smith
-
Christopher Done
-
Dan Doel
-
Daniel Trstenjak
-
Donn Cave
-
Edward Kmett
-
Felipe Almeida Lessa
-
Gábor Lehel
-
Herbert Valerio Riedel
-
Iavor Diatchki
-
John Lask
-
Jon Fairbairn
-
Jonas Almström Duregård
-
Mikhail Vorozhtsov
-
Ross Paterson
-
Simon Marlow
-
Simon Peyton-Jones
-
Strake
-
Twan van Laarhoven
-
Tyson Whitehead
-
wagnerdm@seas.upenn.edu
-
Wolfgang Jeltsch
-
Wolfram Kahl