Re: [Haskell-cafe] lambda case (was Re: A big hurray for lambda-case (and all the other good stuff))

2013-01-01 Thread Tillmann Rendel

Hi,

Brandon Allbery wrote:

[...] syntax extension [...]


I think someone's already working on this (SugarHaskell?).


Yes, we are working on it. See our paper [1] and Sebastian's talk [2] at 
the Haskell Symposium. Our current prototype can be installed as an 
Eclipse plugin [3] or as a command-line tool [4].


 [1] http://sugarj.org/sugarhaskell.pdf
 [2] http://www.youtube.com/watch?v=Kjm7bOLnuy0
 [3] http://update.sugarj.org/
 [4] http://hackage.haskell.org/package/sugarhaskell

One use case we have in mind for SugarHaskell is prototyping of language 
extensions like the one discussed in this thread.


  Tillmann

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


Re: [Haskell-cafe] lambda case (was Re: A big hurray for lambda-case (and all the other good stuff))

2012-12-31 Thread adam vogt
On Sun, Dec 30, 2012 at 10:00 PM, Brandon Allbery  wrote:
> On Sun, Dec 30, 2012 at 8:42 PM, Dan Burton 
> wrote:
>>>
>>> [featureX] is usually too powerful, it surely would be abused
>>> extensively, which would make developer's life a nightmare, unless there is
>>> only one developer and whole development takes no more than a couple of
>>> months.
>>
>>
>> This doesn't say much about why syntax extension is too powerful, nor how
>> that would lead to extensive abuse. Well, "too powerful" or not,
>> meta-programming should be more easily available at least at some layer of
>> language development without having to resort to hacking the compiler.
>
>
> I think someone's already working on this (SugarHaskell?).

Hi All,

Petr's suggestion has some similarities with this quasiquoter
,
at least as far as picking a different return type if some patterns
can fail. If new syntax implemented by a quasiquoter is really that
good, then these possible issues should be worth it:

- have to type [| |]
- haskell-src-exts parser called may not have the same extensions enabled as ghc
- when other new syntax is added, template haskell (and
haskell-src-meta) may not gain those features for a year or more

Regards,
Adam

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


Re: [Haskell-cafe] lambda case (was Re: A big hurray for lambda-case (and all the other good stuff))

2012-12-30 Thread Brandon Allbery
On Sun, Dec 30, 2012 at 8:42 PM, Dan Burton wrote:

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

I think someone's already working on this (SugarHaskell?).

-- 
brandon s allbery kf8nh   sine nomine associates
allber...@gmail.com  ballb...@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonadhttp://sinenomine.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] lambda case (was Re: A big hurray for lambda-case (and all the other good stuff))

2012-12-30 Thread Dan Burton
> [featureX] is usually too powerful, it surely would be abused extensively,
> which would make developer's life a nightmare, unless there is only one
> developer and whole development takes no more than a couple of months.


This doesn't say much about *why* syntax extension is too powerful, nor *how
*that would lead to extensive abuse. Well, "too powerful" or not,
meta-programming should be more easily available at least at *some *layer
of language development without having to resort to hacking the compiler.

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


Re: [Haskell-cafe] lambda case (was Re: A big hurray for lambda-case (and all the other good stuff))

2012-12-30 Thread MigMit
Syntax extensibility is usually too powerful, it surely would be abused 
extensively, which would make developer's life a nightmare, unless there is 
only one developer and whole development takes no more than a couple of months.

On Dec 31, 2012, at 1:09 AM, Dan Burton  wrote:

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


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


Re: [Haskell-cafe] lambda case (was Re: A big hurray for lambda-case (and all the other good stuff))

2012-12-30 Thread Dan Burton
My 2 cents on the issue:

We should have a better forms of meta-programming to solve this sort of
issue generally. With the power of first-class functions and laziness, we
can get away with a lot of things without meta-programming, but case
expression syntax is not first class, so cannot benefit from the
flexibility proffered to the rest of the language.

tl;dr give me easily extensible syntax, rather than having to run to GHC
devs every time I want a new or different flavor of sugar.

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


Re: [Haskell-cafe] lambda case (was Re: A big hurray for lambda-case (and all the other good stuff))

2012-12-30 Thread Chris Smith
On Sun, Dec 30, 2012 at 8:51 AM, David Thomas wrote:

> Jon's suggestion sounds great.
>
> The bike shed should be green.
>

There were plenty of proposals that would work fine.  `case of` was great.
 `\ of` was great.  It's less obvious to me that stand-alone `of` is never
ambiguous... but if that's true, it's reasonable.  Sadly, the option that
was worse that doing nothing at all is what was implemented.

The "bikeshedding" nonsense is frustrating.  Bikeshedding is about wasting
time debating the minutia of a significant improvement, when everyone
agrees the improvement is a good idea.  Here, what happened was that
someone proposed a minor syntax tweak (from `\x -> case x of` to `case
of`), other reasonable minor syntax tweaks were proposed instead to
accomplish the same goal, and then in the end, out of the blue, it was
decided to turn `case` into a layout-inducing keyword (or even worse, only
sometimes but not always layout-inducing).

There is no bike shed here.  There are just colors (minor syntax tweaks).
 And I don't get the use of "bikeshedding" as basically just a rude comment
to be made at people who don't like the same syntax others do.

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


Re: [Haskell-cafe] lambda case (was Re: A big hurray for lambda-case (and all the other good stuff))

2012-12-30 Thread David Thomas
Jon's suggestion sounds great.

The bike shed should be green.

That is all.


On Sun, Dec 30, 2012 at 4:44 PM, Petr P  wrote:

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


Re: [Haskell-cafe] lambda case (was Re: A big hurray for lambda-case (and all the other good stuff))

2012-12-30 Thread Petr P
Hi,

I also support Jon's proposal for standalone of { ... }. Seems to me
clearer and more useful than the special "\case" construct.

I suppose 'of { ... }' could be generalized to multiple arguments, so that
of (Just x) (Just y) -> x ++ y
would create an anonymous function of type 'Maybe String -> Maybe String ->
String'.

Considering the recent thread about partial functions:
http://www.haskell.org/pipermail/haskell-cafe/2012-December/105445.html
we could have variants of 'of' to distinguish partial functions. For
example, we could have something like 'ofFull' that would require an
exhaustive list of patterns, and something like 'ofPart' that would instead
produce results of type 'Maybe something'. (Most likely we'd have to think
of better names for them.) For example:
  ofPart [x] [y] -> x ++ y
would be of type '[String] -> [String] -> Maybe String', returning
`Nothing` if one of the input isn't a 1-element list - an approach similar
to Scala's partial functions. <
http://www.scala-lang.org/api/current/scala/PartialFunction.html>

[Perhaps we could have 'of' to work both ways - if the list of patterns
would be exhaustive, the result would be pure. If it would be
non-exhaustive, the result would be 'Maybe something'. Of course 'case x of
...' would still work as now, not caring about exhaustiveness. But I'm not
sure if this wouldn't be too error prone.]

We could even generalize 'ofPart' to work with any Alternative instance so
that
  ofPart [x] [y] -> x ++ y
would be of type '(Alternative f) => [String] -> [String] -> f String'.
Matching patterns would return results using 'pure', non-matching 'empty',
and they would be all combined combined using <|>. 'empty' would be
returned if nothing matched. (Among other things, this could have some
interesting consequences when overlapping patterns would be applied to
'Alternative []'.) For example

fn = ofPart (Right 0) -> 1
(Right x) -> x

would produce (using today's syntax):

fn :: (Alternative f) => Either Bool Int -> f Int
fn x = case x of { Right 0   -> pure 1 ; _ -> empty; } <|>
   case x of { Right x   -> pure x ; _ -> empty; } <|>
   empty


Best regards,
Petr


2012/12/29 Tom Ellis 

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


Re: [Haskell-cafe] lambda case (was Re: A big hurray for lambda-case (and all the other good stuff))

2012-12-29 Thread Tom Ellis
On Thu, Nov 29, 2012 at 05:49:53PM +, Jon Fairbairn wrote:
> Ben Franksen  writes:
> > just wanted to drop by to say how much I like the new lambda case 
> > extension. 
> > I use it all the time and I just *love* how it relieves me from conjuring 
> > up 
> > dummy variables, which makes teh code not only esier to write but also to 
> > read.
> 
> > [...] should *definitely* go into Haskell'13.
[...]
> To me it seems obvious that if we are going to do this [...] we should do
> it simply by making the "case exp" part of a case expression optional.
> 
>of {alts...}
> 
> and we would then describe
> 
>case e of {...}
> 
> as syntactic sugar for
> 
>(of {...}) (e)

My very belated and unsolicited layman's reply is that I am a strong
supporter of Jon's position.  His suggestion is parsimonious and natural. 
Without wishing to start the discussion again, I disagree that it is
bikeshedding.  One lesson I learned from Haskell is that syntax is much more
important than I previously realised.

Tom

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


Re: [Haskell-cafe] lambda case

2012-12-01 Thread Brandon Allbery
On Sat, Dec 1, 2012 at 5:30 AM, Roman Cheplyaka  wrote:

> I find this discussion useful — there are some interesting points
> (splitting "case of" into two parts) that I don't remember reading in the
> original thread (but maybe it's just me).
>

Mentioned twice that I recall, as treating 'of' as a lambda and as '\of'.
 It got somewhat short shrift, likely because while it makes sense from an
existing language syntax viewpoint, it makes little to none from a
readability standpoint.

-- 
brandon s allbery kf8nh   sine nomine associates
allber...@gmail.com  ballb...@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonadhttp://sinenomine.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] lambda case

2012-12-01 Thread Roman Cheplyaka
It hasn't made it to the standard yet, though. If some experimental
feature is implemented in GHC, it doesn't mean it's set in stone.

I find this discussion useful — there are some interesting points
(splitting "case of" into two parts) that I don't remember reading in the
original thread (but maybe it's just me).

Roman

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

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


Re: [Haskell-cafe] lambda case

2012-11-30 Thread Andreas Abel

Right, case..of is superfluous,

  case e of
branches

can now be written as

  e |> \case
branches

with backwards application |> (or some prefer & --- sadly, the proposal 
to add backwards appliation to base did not make it to a consensus).


This is in accordance to the monadic

  me >>= \case
branches

If there was an opportunity to make drastic language changes, case..of 
could be disposed of altogether.  \case could become 'cases' or 'match' 
or 'fun' (rather not 'of', for my taste).


The current compromise it not too bad, I think.

Unfortunately, I have to wait for 7.6 to become the standard before 
using \case in Agda source...


Cheers,
Andreas

On 30.11.12 7:25 AM, Herbert Valerio Riedel wrote:

Jon Fairbairn  writes:

[...]


“\case” complicates lambda, using “of” simply breaks “case … of …”
into two easily understood parts.


Just some observation (I'm rather late to the lambda-case discussion, so
this might have been already pointed out previously):

if the reserved keyword 'of' was to take the place of '\case', shouldn't
then

   'case' exp

w/o the "'of' { alts }"-part become a separately valid expression (with
'case' essentially meaning 'flip ($)') to really break it up into two
independent parts? Then 'case exp of { alts }' wouldn't be a special
form anymore, but would just result from combining 'case' and 'of';

'case' wouldn't even need to be a reserved keyword (and thus the grammar
could be simplified), if it wasn't for the current grammar which
requires to isolate a \case-expression by using () or $, consider e.g.:

   {-# LANGUAGE LambdaCase #-}

   import System.Environment

   case' :: b -> (b -> c) -> c
   case' = flip ($)

   main = do
 s <- getArgs

 case' s $ \case  -- image '\case' was actually '\of' or 'of'
   [x] -> putStrLn ("Hello " ++ x)
   _   -> putStrLn "wrong number of arguments given"


just my 2¢

cheers,
   hvr

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



--
Andreas Abel  <><  Du bist der geliebte Mensch.

Theoretical Computer Science, University of Munich
Oettingenstr. 67, D-80538 Munich, GERMANY

andreas.a...@ifi.lmu.de
http://www2.tcs.ifi.lmu.de/~abel/

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


Re: [Haskell-cafe] lambda case

2012-11-30 Thread Brent Yorgey
Oh, PLEASE people.  Let's not have another round of bikeshedding about
this AFTER the feature is already implemented!

-Brent

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

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


Re: [Haskell-cafe] lambda case

2012-11-30 Thread Herbert Valerio Riedel
Jon Fairbairn  writes:

[...]

> “\case” complicates lambda, using “of” simply breaks “case … of …”
> into two easily understood parts.

Just some observation (I'm rather late to the lambda-case discussion, so
this might have been already pointed out previously):

if the reserved keyword 'of' was to take the place of '\case', shouldn't
then

  'case' exp

w/o the "'of' { alts }"-part become a separately valid expression (with
'case' essentially meaning 'flip ($)') to really break it up into two
independent parts? Then 'case exp of { alts }' wouldn't be a special
form anymore, but would just result from combining 'case' and 'of';

'case' wouldn't even need to be a reserved keyword (and thus the grammar
could be simplified), if it wasn't for the current grammar which
requires to isolate a \case-expression by using () or $, consider e.g.:

  {-# LANGUAGE LambdaCase #-}
  
  import System.Environment
  
  case' :: b -> (b -> c) -> c
  case' = flip ($)
  
  main = do
s <- getArgs
  
case' s $ \case  -- image '\case' was actually '\of' or 'of'
  [x] -> putStrLn ("Hello " ++ x)
  _   -> putStrLn "wrong number of arguments given"


just my 2¢

cheers,
  hvr

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


Re: [Haskell-cafe] lambda case

2012-11-30 Thread Jon Fairbairn
Andreas Abel  writes:

> I had been missing a pattern matching lambda in Haskell for
> a long time (SML had "fn" since ages) and my typical use
> will be
>
>   monadic_expr >>= \case
> branches

We’ve been through that.  I want something similar, but would
have preferred something more algebraic.

> I think "\case" is not the worst choice, certainly better than
> "of" ...

What’s your argument? You’ll have to do better than blatant
assertion to convince me. Making “case exp” optional builds on
an existing expression syntax, giving an explicit meaning to a
part of it, so a reader only has to know that “of {alts}” is a
function and case does something specific with it. This “\case”
takes the keyword from that expression syntax and makes it a
special case of lambda, so a reader seeing a lambda now has to
check for a keyword instead of knowing straight off that the
next thing is going to be a variable.

Back when we originally designed Haskell there were lots of
things that people wanted to put in, and eventually we reached a
point where we said that we would only put something new in if
it allowed us to remove (or simplify) something else. “\case”
complicates lambda, using “of” simply breaks “case … of …” into
two easily understood parts.
-- 
Jón Fairbairn jon.fairba...@cl.cam.ac.uk



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


Re: [Haskell-cafe] lambda case (was Re: A big hurray for lambda-case (and all the other good stuff))

2012-11-29 Thread Andreas Abel
I had been missing a pattern matching lambda in Haskell for a long time 
(SML had "fn" since ages) and my typical use will be


  monadic_expr >>= \case
branches

I think "\case" is not the worst choice, certainly better than "of" ...

Thanks to the GHC 7.6 developers!

Cheers,
Andreas

On 29.11.12 12:49 PM, Jon Fairbairn wrote:

Ben Franksen  writes:


just wanted to drop by to say how much I like the new lambda case extension.
I use it all the time and I just *love* how it relieves me from conjuring up
dummy variables, which makes teh code not only esier to write but also to
read.



[…] should *definitely* go into Haskell'13.


As I was opposed to the suggestion for lambda case I didn’t
really follow the discussion of the syntax, but I’m puzzled by
the choice. To me it seems obvious that if we are going to do
this (as opposed to something more decomposable like
lambda-match), we should do it simply by making the “case exp”
part of a case expression optional. So the syntax for lambda-
case would be

of {alts…}

and we would then describe

case e of {…}

as syntactic sugar for

(of {…}) (e)

Doing it this way doesn’t introduce any new syntactic elements
and has fewer tokens at the point of use.

I don’t see any need for a \ in the syntax: this is a functional
language we are talking about after all. Once we know that “of”
introduces a function, that should be enough.



--
Andreas Abel  <><  Du bist der geliebte Mensch.

Theoretical Computer Science, University of Munich
Oettingenstr. 67, D-80538 Munich, GERMANY

andreas.a...@ifi.lmu.de
http://www2.tcs.ifi.lmu.de/~abel/

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


[Haskell-cafe] lambda case (was Re: A big hurray for lambda-case (and all the other good stuff))

2012-11-29 Thread Jon Fairbairn
Ben Franksen  writes:

> just wanted to drop by to say how much I like the new lambda case extension. 
> I use it all the time and I just *love* how it relieves me from conjuring up 
> dummy variables, which makes teh code not only esier to write but also to 
> read.

> […] should *definitely* go into Haskell'13.

As I was opposed to the suggestion for lambda case I didn’t
really follow the discussion of the syntax, but I’m puzzled by
the choice. To me it seems obvious that if we are going to do
this (as opposed to something more decomposable like
lambda-match), we should do it simply by making the “case exp”
part of a case expression optional. So the syntax for lambda-
case would be

   of {alts…}

and we would then describe

   case e of {…}

as syntactic sugar for

   (of {…}) (e)

Doing it this way doesn’t introduce any new syntactic elements
and has fewer tokens at the point of use.

I don’t see any need for a \ in the syntax: this is a functional
language we are talking about after all. Once we know that “of”
introduces a function, that should be enough.

-- 
Jón Fairbairn jon.fairba...@cl.cam.ac.uk


___
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-06 Thread Matthew Gruen
On 10/2/10, Christopher Done  wrote:
> On 2 October 2010 20:23, Max Bolingbroke  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: 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
 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-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: [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 Max Bolingbroke
On 4 October 2010 00:38, Conal Elliott  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 Max Bolingbroke
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.

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 Donn Cave
Quoth Ketil Malde ,
...
> 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 Ketil Malde
Donn Cave  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 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 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 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  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 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: 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  wrote:
> On Mon, Oct 4, 2010 at 9:04 PM, Dean Herington
>  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 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 Luke Palmer
On Mon, Oct 4, 2010 at 9:04 PM, Dean Herington
 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
___
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 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: 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  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-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: [Haskell-cafe] Lambda-case / lambda-if

2010-10-04 Thread Donn Cave
Quoth "Richard O'Keefe" ,
...
> 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 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 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 Donn Cave
Quoth Ketil Malde ,
> Max Bolingbroke  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: Re[2]: [Haskell-cafe] Lambda-case / lambda-if

2010-10-04 Thread Christopher Done
On 4 October 2010 10:55, Bulat Ziganshin  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[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: [Haskell-cafe] Lambda-case / lambda-if

2010-10-04 Thread Ketil Malde
Max Bolingbroke  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: [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  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


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


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 Felipe Lessa
On Sat, Oct 2, 2010 at 4: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.
>
> 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 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 Ozgur Akgun
On 2 October 2010 19:33, Henning Thielemann
wrote:

>
> 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 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 Christopher Done
On 2 October 2010 20:23, Max Bolingbroke  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 "

becomes:

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

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 Henning Thielemann


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


"Max" == Max Bolingbroke  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 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 Colin Paul Adams
> "Max" == Max Bolingbroke  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


[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