[Haskell-cafe] lambda case
Andreas Abel
andreas.abel at ifi.lmu.de
Fri Nov 30 15:55:54 CET 2012
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 <jon.fairbairn at cl.cam.ac.uk> 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 at 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.abel at ifi.lmu.de
http://www2.tcs.ifi.lmu.de/~abel/
More information about the Haskell-Cafe
mailing list