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

2010-10-06 Thread Matthew Gruen
On 10/2/10, Christopher Done chrisd...@googlemail.com wrote:
 On 2 October 2010 20:23, Max Bolingbroke batterseapo...@hotmail.com wrote:
 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.

 Nice work! I like it and have wanted it for a while, and I know many
 in the #haskell IRC channel would like it. The case is especially
 useful. Maybe the if is only useful sometimes.

+1 for `case of'... I have called for it on many an occasion in
#haskell. Thanks for implementing it, Max!

I primarily see it as a way to remove a point from `\x - case x of
...', not a way to augment lambdas with pattern matching, like in `\0
- 1 \n k - k-1'.  I suppose both of them work with monadic casing,
with the `m =' trick. `\case' or `\case of' would work okay as well,
the former Simon suggested, but some keywords *somewhere* would be
nice, to avoid a perl-like procession of punctuation. (But the code
golfer in me says otherwise.)

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


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

2010-10-05 Thread Nicolas Wu
 To repeat, the analogues in SML and Erlang *do* support multiple
 clauses (as well as pattern matching) and the failure of Haskell
 lambdas to do so has always seemed like a weird restriction in a
 language that's usually free of weird restrictions.

I agree with this sentiment. I have never understood why lambdas can't
handle multiple clauses.

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

This sounds sensible, since the lambda-case clause should really be
about having a lambda with support for cases, not a case statement
that's implicitly surrounded by a lambda. While I think the case of
is a good idea, multiple clauses in lambdas seems more canonical to
me.

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


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

2010-10-05 Thread Neil Brown

On 05/10/10 07:52, Nicolas Wu wrote:

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

While I think the case of
is a good idea, multiple clauses in lambdas seems more canonical to
me.
   


Alternatively, we could abandon lambdas and just use lambda-case.

All expressions like \1 - f become case of 1 - f

Multi-argument functions are a bit more verbose, as we effectively go 
back to single argument functions with manual currying:


\x (C y) - z becomes: case of {x - case of {C y - z}}

There is the small matter of losing backwards compatibility, of course.  
But on the plus side, this would reduce the number of constructions in 
the language by one.  (I think the strictness semantics, etc match up 
for this transformation?).


;-)

Thanks,

Neil.

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


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

2010-10-05 Thread Nicolas Pouillard
On Tue, 5 Oct 2010 03:36:12 -0600, Luke Palmer lrpal...@gmail.com wrote:
 On Mon, Oct 4, 2010 at 9:04 PM, Dean Herington
 heringtonla...@mindspring.com wrote:
  With respect to datatype destructing functions, the Prelude has:
 
  maybe :: b - (a - b) - Maybe a - b
  either :: (a - c) - (b - c) - Either a b - c
 
  which suggests the following signatures for the analogues for Bool and list
  types:
 
  bool :: a - a - Bool - a
  list :: b - (a - [a] - b) - [a] - b
 
 This suggestion is not so clear to me.  Maybe and Either are both
 non-recursive, so the Church and Scott encodings coincide.  You've
 written the Scott encoding of list.  The Church encoding should look
 familiar:
 
 list :: b - (a - b - b) - [a] - b

I would argue for the previous one (Scott), since we already have this one
(this is foldr with another order for arguments).

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


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

2010-10-05 Thread Gábor Lehel
I also vote +1 for lambda-case, and abstain for lambda-if.

I don't think multiple-clause lambdas being desirable should be an
argument against lambda-case. After all, we can also define top-level
functions with either multiple clauses or a single case expression.
Haskell has always followed the TMTOWTDI school of thought with
regards to syntax, as far as I know. And lambda-case has the notable
advantage that someone has gone and implemented it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-10-05 Thread Ozgur Akgun
For what it's worth, after all this discussion my rather cheeky preference
is as follows:

Instead of introducing more specialised syntax, remove both existing special
syntaxes for if and case, and introduce multi-clause support for lambdas!

Cheers!

On 2 October 2010 19:23, Max Bolingbroke batterseapo...@hotmail.com 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




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


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

2010-10-05 Thread Henning Thielemann
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}

?

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


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

2010-10-05 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 10/5/10 12:38 , Henning Thielemann wrote:
 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}

+1; likewise for consistency it should support guards (which would preclude
using | the way Richard suggested, and goes along with the lambda-case thing).

- -- 
brandon s. allbery [linux,solaris,freebsd,perl]  allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university  KF8NH
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkyrWNIACgkQIn7hlCsL25WPLwCfYGc4KUscdpv3lJ7lQbugtbIa
jz4An2mbZdJr3LZY6rF0qZjBcle4HLsX
=kR9R
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-10-05 Thread Ketil Malde
Donn Cave d...@avvanta.com writes:

 I think you're not the first to ask.  Just out of curiosity, or is
 there a use for these variations?

Just that they seem to be natural generalizations.  If it's just the
single form of paramtrizing the condition, I think it's better served by
a regular function, 'bool' or (??) or whatever.

 The reason for the initially proposed construct seems clear enough
 to me, it's very much like `case'.  

   getargs = if then beTrue else beFalse . (==) [-t]

Isn't this equivalent, and only slightly more cumbersome?

  getArgs = case of {True - beTrue; False - beFalse} . (==) [-t]

(And of course,

  getArgs = case of [-t] - beTrue; _ - beFalse

is probably clearer anyway.)

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-10-05 Thread Donn Cave
Quoth Ketil Malde ke...@malde.org,
...
 Just that they seem to be natural generalizations.  If it's just the
 single form of paramtrizing the condition, I think it's better served by
 a regular function, 'bool' or (??) or whatever.

Well, yes, there's some logic to that.  Like,

bool b c a = if a
then b
else c

  getArgs = bool (putStrLn long) (putStrLn short) . ( 0) . length

And I agree that's competitive with lambda-if as I understand it -
though possibly not for the same reasons.

For me, Haskell is not Lisp.  Haskell's syntax takes a different direction,
a mix of S-expression with stuff like if-then-else, and it works.  If the
lambda-if feature is actually useful in a way that takes advantage of
the strength of the if-then-else notation, then I'm all for it.

The problem is that due to the rarity of True/False as ... terminal
value of a computation (I just made that up!), neither of these
constructs is going to be worth much.  Forget about lambda-if, even
the regular function looks like hell -

 bool (putStrLn long) (putStrLn short) . ( 0) . length

Compared to

 \ t - if length t  0 then putStrLn long else putStrLn short
 
... and much more so, with less trivial examples.

In a brief survey of my own very small code base, I see only hIsEOF
as a place where I could really use lambda-if.  There, it would be
vastly better than a regular bool function, but that's a pretty minimal
use case.

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


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

2010-10-05 Thread Max Bolingbroke
On 5 October 2010 17:38, Henning Thielemann
schlepp...@henning-thielemann.de 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.

To those asking where lambda-if comes from: it was just something I
hacked in while I was there - I don't have a particular motivation
example. It just seemed like a natural extension of the lambda-case
idea.

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


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

2010-10-05 Thread Max Bolingbroke
On 4 October 2010 00:38, Conal Elliott co...@conal.net wrote:
 I like it!

 Are the other sections available as well, e.g.,

     (if False then else Cafe) Haskell -- Cafe

They are not, though this would certainly make sense for lambda-if.
It's not so clear with lambda-case because of the issue of free
variables. Potentially we could support something like this, but it's
a bit scary-looking:

(case x of Just - ; Nothing -) (\y - I'm a Just) I'm a nothing

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


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

2010-10-05 Thread Richard O'Keefe

On 6/10/2010, at 5:56 AM, Brandon S Allbery KF8NH wrote:

 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}
 
 +1; likewise for consistency it should support guards (which would preclude
 using | the way Richard suggested, and goes along with the lambda-case 
 thing).

It's not that I particularly wanted |.
Just that I thought some sort of visual mark would be a good idea.
Forget I ever suggested it.

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


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

2010-10-05 Thread Evan Laforge
-1 for if then.  The examples of curried if then else look, to my
eyes, less readable than the pointed version.  And it's easy enough to
write a 'bool' deconstructor, or an 'ifM' for the monadic case.

+1 for something to solve the dummy - m; case dummy of problem.
Here are the possibilities I can think of:

1) case of:

m = case of
Just _ - z | guard - a
_ - b

2) habit's case-

case- m of
Just _ - z | guard - a
_ - b

3) extended lambda (not sure what this would look like... would the
below parse with the give layout?)

m = \
Just _ - z | guard - a
_ - b

To me, #3 looks less ad-hoc and I like the idea of loosening a
restriction instead of introducing more sugar, but I'm not sure how
the syntax would work out.  Also, from another point of view, 'f x =
...' is sugared to combine a \ and a case, while \ is unsugared, so
tacking some case sugar on to \ would introduce sugar in a previously
sugar-free area.  Of course that \ is already sugared to curry
automatically, but if you rephrase this as add more sugar rather
than loosen a restriction it suddenly becomes less attractive since
now it's just sugar vs. sugar :)

#2 looks the nicest for this specific use, but seems less general than
#1.  For instance, #1 allows f = case of { ... } . g.

So I like #1.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-10-05 Thread Dean Herington Elizabeth Lacey

At 3:36 AM -0600 10/5/10, Luke Palmer wrote:

On Mon, Oct 4, 2010 at 9:04 PM, Dean Herington
heringtonla...@mindspring.com wrote:

 With respect to datatype destructing functions, the Prelude has:

 maybe :: b - (a - b) - Maybe a - b
 either :: (a - c) - (b - c) - Either a b - c

 which suggests the following signatures for the analogues for Bool and list
 types:

 bool :: a - a - Bool - a
 list :: b - (a - [a] - b) - [a] - b


This suggestion is not so clear to me.  Maybe and Either are both
non-recursive, so the Church and Scott encodings coincide.  You've
written the Scott encoding of list.  The Church encoding should look
familiar:

list :: b - (a - b - b) - [a] - b

Intuitively, a Scott encoding peels off one layer of datatype, whereas
a Church encoding flattens down a whole recursive structure.  Church
encodings are more powerful -- you can do more without requiring a
fixed point operator.

Just to be clear, I am not arguing anything other than maybe and
either don't readily generalize to list because of list's
recursiveness.

Luke


Thanks, Luke, for pointing out the Church vs. Scott encoding issue. 
I agree with your conclusion (and feel better about the lack of the 
version of list I had suggested).


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


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

2010-10-04 Thread Ketil Malde
Max Bolingbroke batterseapo...@hotmail.com writes:

 [1] http://hackage.haskell.org/trac/haskell-prime/ticket/41

I tried to find anything about lambda-if in there, but failed  (Trac and
I aren't on very friendly terms, so it's probably my fault).  Is there
more information about the rationale and use cases for this?

 Prelude (if then Haskell else Cafe) False
 Cafe

Presumably, this extends to 

 Prelude (if False then else Cafe) Haskell
 Cafe

and

 Prelude (if then Haskell else) False Cafe
 Cafe

as well?

My gut reaction is that this doesn't buy a whole lot, and that it is
verbose and not very readable.  Any examples where this is a win?

 Prelude (case of 1 - One; _ - Not-one) 1
 One
 Prelude :q

case of looks a bit weird, but I like the points brought up about
avoiding to name a one-use variable (e.g., getArgs = case of ...)
AFACS, this isn't easily implemented in Haskell either.

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-10-04 Thread Bulat Ziganshin
Hello Ketil,

Monday, October 4, 2010, 11:30:48 AM, you wrote:
 Prelude (if then Haskell else Cafe) False

lambda-if is easily implemented in terms of usual functions.
and we even have one named bool:

bool: Bool - a - a - a

lambda-case cannot be implemented as a function since we need
matching ability of case


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


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

2010-10-04 Thread Christopher Done
On 4 October 2010 10:55, Bulat Ziganshin bulat.zigans...@gmail.com wrote:
 Hello Ketil,

 Monday, October 4, 2010, 11:30:48 AM, you wrote:
 Prelude (if then Haskell else Cafe) False

 lambda-if is easily implemented in terms of usual functions.
 and we even have one named bool:

 bool: Bool - a - a - a

I agree, in fact I have bool here:
http://hackage.haskell.org/packages/archive/higherorder/0.0/doc/html/Data-Bool-Higher.html

And the corresponding other types:

bool :: (a - b) - (a - b) - (a - Bool) - a - b
list :: b - ([a] - b) - [a] - b
maybe :: b - (a - b) - Maybe a - b

But the case is especially useful for pattern matching.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-10-04 Thread Donn Cave
Quoth Ketil Malde ke...@malde.org,
 Max Bolingbroke batterseapo...@hotmail.com writes:
...
 Prelude (if then Haskell else Cafe) False
 Cafe

 Presumably, this extends to 

 Prelude (if False then else Cafe) Haskell
 Cafe

 and

 Prelude (if then Haskell else) False Cafe
 Cafe

 as well?

I think you're not the first to ask.  Just out of curiosity, or is
there a use for these variations?

The reason for the initially proposed construct seems clear enough
to me, it's very much like `case'.  The difference is that of course
it's limited to True  False, so would naturally be used more with
more `composition', e.g.

  getargs = if then beTrue else beFalse . (==) [-t]

... and thus will quickly become unreadable with less trivial components.

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


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

2010-10-04 Thread Roel van Dijk
I really like the lambda-case. There are dozens of places in my code
where I could use it.

Not so sure about the lambda-if. It is just as easily done using an
ordinary function.

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


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

2010-10-04 Thread Richard O'Keefe

On 4/10/2010, at 8:30 PM, Ketil Malde wrote:
 
 Prelude (case of 1 - One; _ - Not-one) 1
 One
 Prelude :q
 
 case of looks a bit weird, but I like the points brought up about
 avoiding to name a one-use variable (e.g., getArgs = case of ...)
 AFACS, this isn't easily implemented in Haskell either.

Erlang manages fine with multiclause 'fun':

(fun (1) - One ; (_) - Not-one end)(1)

ML manages fine with multiclause 'fn':

(fn 1 = one | _ = not-one)(1)

In both cases, the same notation is used for multiclause lambda as
for single clause lambda.  It seems excessively ugly to use
completely different notation depending on the number of alternatives,
especially when one of the notations has another, much more common,
and distinct usage.

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


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

2010-10-04 Thread Donn Cave
Quoth Richard O'Keefe o...@cs.otago.ac.nz,
...
 Erlang manages fine with multiclause 'fun':

   (fun (1) - One ; (_) - Not-one end)(1)

 ML manages fine with multiclause 'fn':

   (fn 1 = one | _ = not-one)(1)

 In both cases, the same notation is used for multiclause lambda as
 for single clause lambda.  It seems excessively ugly to use
 completely different notation depending on the number of alternatives,
 especially when one of the notations has another, much more common,
 and distinct usage.

Just to be sure, are you saying, rather than

case of
1 - f
2 - g

you'd like to see \ support pattern matching etc. like named functions -

\ 1 - f
  2 - g

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


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

2010-10-04 Thread Richard O'Keefe

On 5/10/2010, at 12:49 PM, Donn Cave wrote:
 Just to be sure, are you saying, rather than
 
case of
1 - f
2 - g
 
 you'd like to see \ support pattern matching etc. like named functions -
 
\ 1 - f
  2 - g

Absolutely.For the record, lambda DOES support pattern matching
(Haskell 2010 report, section 3.3
lexp - \ apat1 ... apatn - exp
Lambda abstractions are written \ p1 ... pn - e where
the pi are _patterns_.
)

To repeat, the analogues in SML and Erlang *do* support multiple
clauses (as well as pattern matching) and the failure of Haskell
lambdas to do so has always seemed like a weird restriction in a
language that's usually free of weird restrictions.

'case of' is terminally cute.  I dare say its inventor felt
extremely proud of hacking it in, but it's the kind of thing
that will have admirers swearing in frustration when they get
tripped up by it yet again, and detractors sniggering.

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

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


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

2010-10-04 Thread Dean Herington

At 12:05 PM +0200 10/4/10, Christopher Done wrote:

On 4 October 2010 10:55, Bulat Ziganshin bulat.zigans...@gmail.com wrote:

 Hello Ketil,

 Monday, October 4, 2010, 11:30:48 AM, you wrote:

 Prelude (if then Haskell else Cafe) False


 lambda-if is easily implemented in terms of usual functions.
 and we even have one named bool:

 bool: Bool - a - a - a


I agree, in fact I have bool here:
http://hackage.haskell.org/packages/archive/higherorder/0.0/doc/html/Data-Bool-Higher.html

And the corresponding other types:

bool :: (a - b) - (a - b) - (a - Bool) - a - b
list :: b - ([a] - b) - [a] - b
maybe :: b - (a - b) - Maybe a - b

But the case is especially useful for pattern matching.


I agree with others that lambda-if is better provided as a normal 
function rather than special syntax, that lambda-case is much more 
useful, and that it would be best if lambda-case were simply a 
generalization of anonymous lambdas (\ ...).


With respect to datatype destructing functions, the Prelude has:

maybe :: b - (a - b) - Maybe a - b
either :: (a - c) - (b - c) - Either a b - c

which suggests the following signatures for the analogues for Bool 
and list types:


bool :: a - a - Bool - a
list :: b - (a - [a] - b) - [a] - b

(However, I do rather like the name (??) from Data.Bool.Higher, which 
is used for bool immediately above.  And I would hesitate to use 
the name list for list destruction rather than construction.  So 
I'm not about to propose adding these two functions.)


Dean


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


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

2010-10-03 Thread Conal Elliott
I like it!

Are the other sections available as well, e.g.,

(if False then else Cafe) Haskell -- Cafe

- Conal

On Sat, Oct 2, 2010 at 11:23 AM, Max Bolingbroke batterseapo...@hotmail.com
 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

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


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

2010-10-02 Thread Max Bolingbroke
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


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

2010-10-02 Thread Colin Paul Adams
 Max == Max Bolingbroke batterseapo...@hotmail.com writes:

Prelude (if then Haskell else Cafe) False
Max Cafe

My reaction is to ask:

Can you write this as:

(if then else) False  Haskell  Cafe

?
-- 
Colin Adams
Preston Lancashire
()  ascii ribbon campaign - against html e-mail
/\  www.asciiribbon.org   - against proprietary attachments
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-10-02 Thread Henning Thielemann


On Sat, 2 Oct 2010, 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.


Nice! Concerning if-then-else I would more like to see an according 
function to go to Data.Bool, then we won't need more syntactic sugar like 
if-then-else. However the lambda-case would be useful for me.

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


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

2010-10-02 Thread Henning Thielemann


On Sat, 2 Oct 2010, Colin Paul Adams wrote:


Max == Max Bolingbroke batterseapo...@hotmail.com writes:


   Prelude (if then Haskell else Cafe) False
   Max Cafe

My reaction is to ask:

Can you write this as:

(if then else) False  Haskell  Cafe

?


Sure:

ifThenElse :: Bool - a - a - a
ifThenElse True  x _ = x
ifThenElse False _ y = y

Prelude ifThenElse False Haskell Cafe

(I have done this in utility-ht, and called it if'.)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-10-02 Thread Christopher Done
On 2 October 2010 20:23, Max Bolingbroke batterseapo...@hotmail.com wrote:
 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.

Nice work! I like it and have wanted it for a while, and I know many
in the #haskell IRC channel would like it. The case is especially
useful. Maybe the if is only useful sometimes.

A benefit for lambda-case that I'll throw in the mix is:

main = do
  args - getArgs
  case args of
[path] - do exists - doesFileExist filepath
 if exists
then readFile filepath = putStrLn
else error file does not exist
_  - error usage: foo filename

becomes:

main = do
  getArgs = case of
[path] - doesFileExist filepath
  = if then readFile filepath = putStrLn
 else error file does not exist
_  - error usage: foo filename

There's nothing more annoying than having to introduce intermediate
bindings when you're going to immediate pattern match against it
immediately and never use it again. It's both annoying to have to
think of a variable name that makes sense and is not in scope or will
be in scope, and annoying to type it out, and it's just ugly. This is
*not* a special-case, it happens all the time and it's one of the few
things in the syntax I wish could be updated.

I vote yes, yes, and double yes!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-10-02 Thread Christopher Done
I just had a look at hpaste.org, and, amusingly, the first paste has this:

  down - openLazyURI http://list.iblocklist.com/?list=bt_level1;
  case down of
Left  _  - error Could not download file
Right bs - do input - bs
 ...

I can collect a huge list of instances of this annoying pattern from
Hackage and Google Code Search if it will encourage GHC HQ to make it
an extension.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-10-02 Thread Ozgur Akgun
On 2 October 2010 19:33, Henning Thielemann
lemm...@henning-thielemann.dewrote:


 On Sat, 2 Oct 2010, Max Bolingbroke wrote:

 ... lambda-case/lambda-if ...


 Nice! Concerning if-then-else I would more like to see an according
 function to go to Data.Bool, then we won't need more syntactic sugar like
 if-then-else. However the lambda-case would be useful for me.


And I was just reading this entry in the wiki:
http://www.haskell.org/haskellwiki/If-then-else

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


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

2010-10-02 Thread Jan Christiansen


On 02.10.2010, at 20:35, Henning Thielemann wrote:



On Sat, 2 Oct 2010, Colin Paul Adams wrote:



  Prelude (if then Haskell else Cafe) False
  Max Cafe

My reaction is to ask:

Can you write this as:

(if then else) False  Haskell  Cafe

?


Sure:

ifThenElse :: Bool - a - a - a
ifThenElse True  x _ = x
ifThenElse False _ y = y

Prelude ifThenElse False Haskell Cafe



You can use a similar approach for case expressions ; )


import Prelude hiding ( catch )
import System.IO.Unsafe ( unsafePerformIO )
import Control.Exception ( catch, evaluate, PatternMatchFail )


caseOf :: a - [a - b] - b
caseOf x = unsafePerformIO . firstMatch . map ($x)

firstMatch :: [a] - IO a
firstMatch (x:xs) = catch (evaluate x) (handlePatternFail (firstMatch  
xs))


handlePatternFail :: a - PatternMatchFail - a
handlePatternFail x _ = x


test = (flip caseOf [\1 - One, \_ - Not-one]) 1


Well, to tell the truth this does not work correctly as the following  
example shows.


test2 = (flip caseOf [\1 - ((\2 - One) 3), \_ - Not-one]) 1
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-10-02 Thread Felipe Lessa
On Sat, Oct 2, 2010 at 4:13 PM, Christopher Done
chrisd...@googlemail.com wrote:
 There's nothing more annoying than having to introduce intermediate
 bindings when you're going to immediate pattern match against it
 immediately and never use it again. It's both annoying to have to
 think of a variable name that makes sense and is not in scope or will
 be in scope, and annoying to type it out, and it's just ugly. This is
 *not* a special-case, it happens all the time and it's one of the few
 things in the syntax I wish could be updated.

 I vote yes, yes, and double yes!

I wholly agree with Christopher and for the same reason, +1.

Thanks,

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


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

2010-10-02 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 10/2/10 15:27 , Jan Christiansen wrote:
 You can use a similar approach for case expressions ; )

There are several better (that is, not using unsafePerformIO) versions at
http://haskell.org/haskellwiki/Case .

- -- 
brandon s. allbery [linux,solaris,freebsd,perl]  allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university  KF8NH
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkynmNsACgkQIn7hlCsL25XbOgCfdjFrXdR3PWJvPUif7VVfZZak
lOcAoMpp6l1+XOxU6vwCT+sgLI94l3Kx
=+gFp
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-10-02 Thread wren ng thornton

On 10/2/10 3:13 PM, Christopher Done wrote:

There's nothing more annoying than having to introduce intermediate
bindings when you're going to immediate pattern match against it
immediately and never use it again. It's both annoying to have to
think of a variable name that makes sense and is not in scope or will
be in scope, and annoying to type it out, and it's just ugly. This is
*not* a special-case, it happens all the time and it's one of the few
things in the syntax I wish could be updated.


+1.

In Mark Jones' new language, Habit, they have monadic versions of case 
and if-then-else for precisely this reason.


I'm not sure if the (case of {...}) syntax is the best one to use for 
this feature, but I'd love to get rid of those intermediate names for 
monadic case expressions.


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe