Re: [Haskell-cafe] Re: Lambda-case / lambda-if

2010-10-08 Thread Nicolas Pouillard
On Fri, 8 Oct 2010 01:13:20 +0300, Lauri Alanko  wrote:
> On Thu, Oct 07, 2010 at 02:45:58PM -0700, Nicolas Pouillard wrote:
> > On Thu, 07 Oct 2010 18:03:48 +0100, Peter Wortmann  
> > wrote:
> > > Might be off-topic here, but I have wondered for a while why Haskell
> > > doesn't support something like follows:
> > > 
> > >   do case (<- m) of ...
> > > 
> > > With the more general rule being:
> > > 
> > >   do ... e (<- m) g
> > > =>
> > >   ... m >>= \tmp -> e tmp g
> 
> Your "general" rule doesn't subsume your case example, since a case
> expression is not an application. I think you mean something like
> 
>  do C[(<- m)]
> =>
>  m >>= \tmp -> C[tmp]
> 
> where C is an arbitrary expression context. It could further be
> generalized to allow several (<- ...) subterms in an expression, with
> implied left-to right sequencing. Frankly, that seems like a very
> attractive way to make the do-notation into a more practical
> imperative sub-language.

This is clearer. However this does not seems very robust against manual
refactoring of the "do" notation.

Imagine find this code:

do s1
   C[(<- s2)]

And I don't see the (<- s2) in C, and so I refactor it as:

s1 >> C[(<- s2)]

And so the s2 get affected somewhere else.

-- 
Nicolas Pouillard
http://nicolaspouillard.fr
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Lambda-case / lambda-if

2010-10-07 Thread Lauri Alanko
On Thu, Oct 07, 2010 at 02:45:58PM -0700, Nicolas Pouillard wrote:
> On Thu, 07 Oct 2010 18:03:48 +0100, Peter Wortmann  wrote:
> > Might be off-topic here, but I have wondered for a while why Haskell
> > doesn't support something like follows:
> > 
> >   do case (<- m) of ...
> > 
> > With the more general rule being:
> > 
> >   do ... e (<- m) g
> > =>
> >   ... m >>= \tmp -> e tmp g

Your "general" rule doesn't subsume your case example, since a case
expression is not an application. I think you mean something like

 do C[(<- m)]
=>
 m >>= \tmp -> C[tmp]

where C is an arbitrary expression context. It could further be
generalized to allow several (<- ...) subterms in an expression, with
implied left-to right sequencing. Frankly, that seems like a very
attractive way to make the do-notation into a more practical
imperative sub-language.

This should probably also cover binding, i.e. do { p <- C[(<- m)];
... } should also work.

> Imagine these examples:
> 
> do {a; b (<- c) d; e} => do {a; x <- c; b x d; e}
> 
> do {a >> b (<- c) d; e}
>   |
>   +--> do {x <- c; a >> b x d; e}
>   |
>   +--> do {a; x <- c; b x d; e}

To my understanding no rule would produce this latter variant. do {a;
b} is transformed into a >> do {b}, not the other way around. The
proposed transformation rule seems clear to me: the context covers the
entire expression-statement, including of course expressions
containing monadic operations:

do {a >> b (<- c) d; e}  =>  c >>= \x -> a >> b x d >> e

and if you want a to go before c, you have to do

do {a; b (<- c) d; e)=>  a >> c >>= \x -> b x d >> e

> Imagine that "b" can be equal to "b1 >> b2" and so where placing the
> "x <- c" is non obvious and it should be.

I don't see what this has to do with anything. All we are interested
in is the syntax of do-expressions. The do-transformation is
completely oblivious to monadic operations within the statements, it
only produces some more monadic operations.

Cheers,


Lauri
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Lambda-case / lambda-if

2010-10-07 Thread Nicolas Pouillard
On Thu, 07 Oct 2010 18:03:48 +0100, Peter Wortmann  wrote:
> 
> On Tue, 2010-10-05 at 17:10 -0700, Evan Laforge wrote:
> > +1 for something to solve the "dummy <- m; case dummy of" problem.
> > Here are the possibilities I can think of:
> 
> Might be off-topic here, but I have wondered for a while why Haskell
> doesn't support something like follows:
> 
>   do case (<- m) of ...
> 
> With the more general rule being:
> 
>   do ... e (<- m) g
> =>
>   ... m >>= \tmp -> e tmp g
> 
> Reasons:
> * "<-" is already "sugary", and the transformation is similar. Just
>   removes the need for the user to define a throw-away name.
> * Better than liftMX and the Applicative operators. As shown, this is
>   more flexible while requiring less magic operators as a bonus. Also
>   makes more clear where the sides effects actually are.
> * Goes well with the spirit of getting the good parts of imperative
>   coding where it potentially makes the code more concise. Can be
>   abused, obviously, but I have also seen a lot of code that I feel   
>   could be written better using this.
> 
> Anything I am overlooking here? I tried to find a discussion about
> something like this, but didn't really know what to look for...

Your notation feels very tempting, however it relies a lot on finding
the "do" to put the bind. Recall that "do" is just syntax, and that
it has no more meaning than its desugaring.

Imagine these examples:

do {a; b (<- c) d; e} => do {a; x <- c; b x d; e}

do {a >> b (<- c) d; e}
  |
  +--> do {x <- c; a >> b x d; e}
  |
  +--> do {a; x <- c; b x d; e}

Imagine that "b" can be equal to "b1 >> b2" and so where placing the
"x <- c" is non obvious and it should be.

On the other hand case (<- m) of {...} being translated into
m >>= \x -> case x of {...} is non-ambigous.

Best regards,

-- 
Nicolas Pouillard
http://nicolaspouillard.fr
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Lambda-case / lambda-if

2010-10-07 Thread Miguel Mitrofanov


Отправлено с iPhone

Oct 7, 2010, в 21:03, Peter Wortmann  написал(а):

> 
> On Tue, 2010-10-05 at 17:10 -0700, Evan Laforge wrote:
>> +1 for something to solve the "dummy <- m; case dummy of" problem.
>> Here are the possibilities I can think of:
> 
> Might be off-topic here, but I have wondered for a while why Haskell
> doesn't support something like follows:
> 
>  do case (<- m) of ...

I think it'd be better to write just 'case (<- m) of', without 'do'.

> 
> With the more general rule being:
> 
>  do ... e (<- m) g
>=>
>  ... m >>= \tmp -> e tmp g
> 
> Reasons:
> * "<-" is already "sugary", and the transformation is similar. Just
>  removes the need for the user to define a throw-away name.
> * Better than liftMX and the Applicative operators. As shown, this is
>  more flexible while requiring less magic operators as a bonus. Also
>  makes more clear where the sides effects actually are.
> * Goes well with the spirit of getting the good parts of imperative
>  coding where it potentially makes the code more concise. Can be
>  abused, obviously, but I have also seen a lot of code that I feel   
>  could be written better using this.
> 
> Anything I am overlooking here? I tried to find a discussion about
> something like this, but didn't really know what to look for...
> 
> Greetings,
>  Peter Wortmann
> 
> 
> ___
> 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


[Haskell-cafe] Re: Lambda-case / lambda-if

2010-10-07 Thread Peter Wortmann

On Tue, 2010-10-05 at 17:10 -0700, Evan Laforge wrote:
> +1 for something to solve the "dummy <- m; case dummy of" problem.
> Here are the possibilities I can think of:

Might be off-topic here, but I have wondered for a while why Haskell
doesn't support something like follows:

  do case (<- m) of ...

With the more general rule being:

  do ... e (<- m) g
=>
  ... m >>= \tmp -> e tmp g

Reasons:
* "<-" is already "sugary", and the transformation is similar. Just
  removes the need for the user to define a throw-away name.
* Better than liftMX and the Applicative operators. As shown, this is
  more flexible while requiring less magic operators as a bonus. Also
  makes more clear where the sides effects actually are.
* Goes well with the spirit of getting the good parts of imperative
  coding where it potentially makes the code more concise. Can be
  abused, obviously, but I have also seen a lot of code that I feel   
  could be written better using this.

Anything I am overlooking here? I tried to find a discussion about
something like this, but didn't really know what to look for...

Greetings,
  Peter Wortmann


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Lambda-case / lambda-if

2010-10-07 Thread Jean-Marie Gaillourdet
Hi,

On 06.10.2010, at 22:43, Sterling Clover wrote:

> 
> On Oct 6, 2010, at 5:39 AM, Simon Marlow wrote:
> 
>> A slightly different suggestion from Simon PJ and myself (we agreed on 
>> something syntax-related :-) is the following:
>> 
>> \case 1 -> f
>>  2 -> g
>> 
>> where the two-token sequence '\ case' introduces a new optional layout 
>> context, the body of which is exactly the same as in a case expression.  So 
>> you could also write
>> 
>> \case { 1 -> f; 2 -> g }
>> 
>> if you want.  Guards are allowed of course.
> 
>> * a bit more noisy than just \:  I'm not sure what the
>>  ramifications of having \ introduce a layout context
>>  on its own would be, but I suspect there would be difficulties.
>>  Certainly some existing code would fail to parse, e.g.
>> 
>>  (case e of [] -> \x -> x+1; (x:xs) -> \x -> x+2)
> 
> \ introducing a layout context is a no-go because, as in the example given, 
> it breaks too much code. However, \case as described is somewhat less 
> powerful. In particular, \ with a layout context lets us have multi-argument 
> pattern matching, while both \case and "case of" give only single argument 
> pattern matching. I don't know if the extra functionality is that important, 
> but I don't see why we can't provide for it anyway, as in:
> 
> \case (x:xs) n -> go xs; _ n -> n;

Then, there is an inconsistency between lambda-case and traditional case and 
people will start complaining about that.

Haskell98 is a very well thought out language with very few syntactiv warts. 
I'd avoid introducing new language extensions which do introduce new warts. 
Backwards compatibility is not so important, because GHC will hopefully make it 
optional. Even when an extended \{ p1 -> e1; p2 -> e2 } is part of Haskell 2012 
GHC will probably support Haskell 2011 as well. Therefore, I'd worry less about 
backwards compatibility, but concentrate more on consistency and elegance. I.e 
I'll favor
\p1 p2 -> e1
 p3 p4 -> e2

Just my 2 cents.

-- Jean___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Lambda-case / lambda-if

2010-10-06 Thread Evan Laforge
> I would also very much like to have multi-argument pattern matching, but in
>
>    \case a b -> ...
>          ...
>
> it sure suggests to me that `a` should be applied to `b` before casing.

I feel like sugar is designed to make a couple of specific uses nicer.
 Being as general and orthogonal as possible is the job of the
primitives.  So I don't mind too much if sugar is a little ad-hoc.
Single argument \case addresses the monadic case problem.  Does
someone have some examples of nice expressions that you need a multi
argument case-lambda for?

I don't mind writing 'case (a, b) of ...' very much.  Seems like you
could get the same effect with 'curry':

(\case { a b -> ... ; a b -> ...}) x y

can be written

(curry $ \case { (a, b) -> ... }) x y

Not as pretty, but still point-free.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Lambda-case / lambda-if

2010-10-06 Thread Dean Herington

At 4:43 PM -0400 10/6/10, Sterling Clover wrote:

On Oct 6, 2010, at 5:39 AM, Simon Marlow wrote:

 A slightly different suggestion from Simon PJ and myself (we 
agreed on something syntax-related :-) is the following:


  \case 1 -> f
2 -> g

 where the two-token sequence '\ case' introduces a new optional 
layout context, the body of which is exactly the same as in a case 
expression.  So you could also write


  \case { 1 -> f; 2 -> g }

 if you want.  Guards are allowed of course.



 * a bit more noisy than just \:  I'm not sure what the
   ramifications of having \ introduce a layout context
   on its own would be, but I suspect there would be difficulties.
   Certainly some existing code would fail to parse, e.g.

   (case e of [] -> \x -> x+1; (x:xs) -> \x -> x+2)


\ introducing a layout context is a no-go because, as in the example 
given, it breaks too much code. However, \case as described is 
somewhat less powerful. In particular, \ with a layout context lets 
us have multi-argument pattern matching, while both \case and "case 
of" give only single argument pattern matching. I don't know if the 
extra functionality is that important, but I don't see why we can't 
provide for it anyway, as in:


\case (x:xs) n -> go xs; _ n -> n;

Cheers,
Sterl.___


I would also very much like to have multi-argument pattern matching, but in

\case a b -> ...
  ...

it sure suggests to me that `a` should be applied to `b` before casing.

Dean
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Lambda-case / lambda-if

2010-10-06 Thread Sterling Clover

On Oct 6, 2010, at 5:39 AM, Simon Marlow wrote:

> A slightly different suggestion from Simon PJ and myself (we agreed on 
> something syntax-related :-) is the following:
> 
>  \case 1 -> f
>   2 -> g
> 
> where the two-token sequence '\ case' introduces a new optional layout 
> context, the body of which is exactly the same as in a case expression.  So 
> you could also write
> 
>  \case { 1 -> f; 2 -> g }
> 
> if you want.  Guards are allowed of course.

> * a bit more noisy than just \:  I'm not sure what the
>   ramifications of having \ introduce a layout context
>   on its own would be, but I suspect there would be difficulties.
>   Certainly some existing code would fail to parse, e.g.
> 
>   (case e of [] -> \x -> x+1; (x:xs) -> \x -> x+2)

\ introducing a layout context is a no-go because, as in the example given, it 
breaks too much code. However, \case as described is somewhat less powerful. In 
particular, \ with a layout context lets us have multi-argument pattern 
matching, while both \case and "case of" give only single argument pattern 
matching. I don't know if the extra functionality is that important, but I 
don't see why we can't provide for it anyway, as in:

\case (x:xs) n -> go xs; _ n -> n;

Cheers,
Sterl.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Lambda-case / lambda-if

2010-10-06 Thread Gregory Crosswhite

 On 10/06/10 13:32, steffen wrote:

A slightly different suggestion from Simon PJ and myself (we agreed on
something syntax-related :-) is the following:
  \case 1 ->  f
2 ->  g
...
  \case { 1 ->  f; 2 ->  g }

+1

I like this because it has exactly the same properties of Max's
case-of, but is shorter and still reads with sense.

+1
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

+1...million

Cheers,
Greg
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Lambda-case / lambda-if

2010-10-06 Thread steffen
> > A slightly different suggestion from Simon PJ and myself (we agreed on
> > something syntax-related :-) is the following:
>
> >  \case 1 -> f
> >        2 -> g
> > ...
> >  \case { 1 -> f; 2 -> g }
>
> +1
>
> I like this because it has exactly the same properties of Max's
> case-of, but is shorter and still reads with sense.
+1
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Lambda-case / lambda-if

2010-10-06 Thread Christopher Done
On 6 October 2010 11:39, Simon Marlow  wrote:
>   Certainly some existing code would fail to parse, e.g.
>   (case e of [] -> \x -> x+1; (x:xs) -> \x -> x+2)

That's definitely a problem. The multi-pattern lambda is nice as I
think it follows naturally from function definitions (indeed, I think
many a Haskeller including myself have written (\x -> k; \y -> l) once
expecting it to work), but problems like this are kind of a deal
breaker.

> A slightly different suggestion from Simon PJ and myself (we agreed on
> something syntax-related :-) is the following:
>
>  \case 1 -> f
>        2 -> g
> ...
>  \case { 1 -> f; 2 -> g }
>

+1

I like this because it has exactly the same properties of Max's
case-of, but is shorter and still reads with sense.

I created a poll about for/against the case-of idea, but it seems,
just from the messages here, unanimous that people *do* want something
like this, mostly to solve the unnecessary/dummy formal parameters
problem.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Lambda-case / lambda-if

2010-10-06 Thread Simon Marlow

On 06/10/2010 00:04, Max Bolingbroke wrote:

On 5 October 2010 17:38, Henning Thielemann
  wrote:

Richard O'Keefe schrieb:


I'd prefer to see something like
   \ 1 ->  f
   | 2 ->  g
but I'm sure something could be worked out.


In order to be consistent with current case, maybe in layout mode:

\1 ->  f
  2 ->  g

and in non-layout mode

\{1 ->  f; 2 ->  g}


Duncan Coutts also suggested this possibility to me - once I saw it
actually liked it rather better than the lambda-case stuff,
particularly since it generalises nicely to multiple arguments. I may
try to write a patch for this extension instead when I get some free
time.


A slightly different suggestion from Simon PJ and myself (we agreed on 
something syntax-related :-) is the following:


  \case 1 -> f
2 -> g

where the two-token sequence '\ case' introduces a new optional layout 
context, the body of which is exactly the same as in a case expression. 
 So you could also write


  \case { 1 -> f; 2 -> g }

if you want.  Guards are allowed of course.

The motivation for this syntax is:

 * easy to mentally parse: \ still introduces a function.
   (better than 'case of' in this respect)

 * a bit more noisy than just \:  I'm not sure what the
   ramifications of having \ introduce a layout context
   on its own would be, but I suspect there would be difficulties.
   Certainly some existing code would fail to parse, e.g.

   (case e of [] -> \x -> x+1; (x:xs) -> \x -> x+2)


Cheers,
Simon
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Lambda-case / lambda-if

2010-10-02 Thread Max Bolingbroke
Thanks to everyone who replied - it looks like this feature is enough
in demand that GHC HQ may want to accept it. I've created a ticket at
http://hackage.haskell.org/trac/ghc/ticket/4359

On 2 October 2010 14:23, Max Bolingbroke  wrote:
> Hi Cafe,
>
> I implemented the proposed Haskell' feature lambda-case/lambda-if [1]
> during the Haskell Implementors Workshop yesterday for a bit of fun.
> The patches are online [2, 3].
>
> The feature is demonstrated in this GHCi session:
>
> $ inplace/bin/ghc-stage2 --interactive -XLambdaCase
> GHCi, version 7.1.20101002: http://www.haskell.org/ghc/  :? for help
> Loading package ghc-prim ... linking ... done.
> Loading package integer-gmp ... linking ... done.
> Loading package base ... linking ... done.
> Loading package ffi-1.0 ... linking ... done.
> Prelude> (if then "Haskell" else "Cafe") False
> "Cafe"
> Prelude> (case of 1 -> "One"; _ -> "Not-one") 1
> "One"
> Prelude> :q
>
> Do you like this feature and think it would be worth incorporating
> this into GHC? Or is it too specialised to be of use? If there is
> enough support, I'll create a ticket and see what GHC HQ make of it.
>
> Max
>
> [1] http://hackage.haskell.org/trac/haskell-prime/ticket/41
> [2] http://www.omega-prime.co.uk/files/LambdaCase-Testsuite.patch
> [3] http://www.omega-prime.co.uk/files/LambdaCase-Compiler.patch
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe