[Haskell-cafe] Language semantics

Andrew Coppin andrewcoppin at btinternet.com
Fri Jun 29 15:02:18 EDT 2007


Stefan O'Rear wrote:
> On Fri, Jun 29, 2007 at 07:18:00PM +0100, Andrew Coppin wrote:
>   
>> 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
>   

Woah... Let me sit down and grok that for an hour or two. o_o

(Hey, maybe this is why I don't develop cutting edge software for a living?)

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

What's Uniplate?



More information about the Haskell-Cafe mailing list