lambda case

Brent Yorgey byorgey at seas.upenn.edu
Fri Nov 30 15:52:53 CET 2012


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 <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
> 
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users at haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
> 



More information about the Glasgow-haskell-users mailing list