[Haskell-cafe] Language semantics

Stefan O'Rear stefanor at cox.net
Fri Jun 29 14:47:53 EDT 2007


On Fri, Jun 29, 2007 at 07:18:00PM +0100, Andrew Coppin wrote:
> Dan Mead wrote:
> >Andrew: Try using catchalls in your guards
> >
> >
> >pattern1
> >| guard1 =
> >| guard2 =
> >| otherwise =
> >
> >This makes it much easier to use pattern guards.
> >"otherwise" is a reserved word used for this stuff in ghc.
> 
> Yeah, it's good practice to include an explicit otherwise clause - but 
> in this specific instance, I'm trying to do tricky stuff where one rule 
> falls through to another if some condition doesn't hold - but that 
> condition is only expressible as a function.
> 
> Well, let me show you the code - somebody will probably recognise this 
> stuff...
> 
> convert1 :: Expression -> Expression
> convert1 S = S
> convert1 K = K
> convert1 I = I
> convert1 (Var v) = Var v
> convert1 (x :@: y) = (convert1 x) :@: (convert1 y)
> convert1 (Lam n e)
>  | n `not_in` e = K :@: (convert1 e)
> convert1 (Lam n (Var v))
>  | n == v = I
>  | otherwise = K :@: (convert1 (Var v))
> convert1 (Lam n (x :@: y))
>  | y `is_var` n && n `not_in` x = convert1 x
>  | otherwise                    = S :@: (convert1 (Lam n x)) :@: 
> (convert1 (Lam n y))
> convert1 (Lam n (Lam m e))
>  | n `not_in` e = K :@: (convert1 (Lam m e))
>  | otherwise    = convert1 (Lam n (convert1 (Lam m e)))

This is *much* easier expressed as a bottom-up traversal.

compile = transform optimize . transform eliminate

eliminate (Lam v e) = transform (abstract v) e
eliminate x = x

abstract v (Var v') | v == v'   = I
abstract v (a :@ b) = S :@ a :@ b
abstract v x = x

optimize (S :@ (K :@ x) :@ (K :@ y)) = K :@ (x :@ y)
optimize (S :@ (K :@ x) :@ I) = x
optimize x = x

(Here using Uniplate, mostly because it is the freshest in my mind of
all of them).

Stefan


More information about the Haskell-Cafe mailing list