[Haskell-cafe] lambda case

Herbert Valerio Riedel hvr at gnu.org
Fri Nov 30 13:25:27 CET 2012


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



More information about the Haskell-Cafe mailing list