[Haskell-cafe] Transformation sequence

Andrew Coppin andrewcoppin at btinternet.com
Sat Oct 20 15:40:28 EDT 2007


Stefan O'Rear wrote:
> On Sat, Oct 20, 2007 at 08:05:37PM +0100, Andrew Coppin wrote:
>   
>> I want to construct a program that prints out something like this:
>>
>> [\fx -> f(fx)]
>> [\f -> [\x -> f(fx)]]
>> [\f -> S[\x -> f][\x -> fx]]
>> [\f -> S(Kf)[\x -> fx]]
>> [\f -> S(Kf)f]
>> S[\f -> S(Kf)][\f -> f]
>> S(S[\f -> S][\f -> Kf])[\f -> f]
>> S(S(KS)[\f -> Kf])[\f -> f]
>> S(S(KS)K)[\f -> f]
>> S(S(KS)K)I
>>
>> I can quite happily construct a program which, given the first line, yields 
>> the last line. But getting it to print all the intermediate steps is 
>> harder. And, like I said, when something is "hard" in Haskell, it usually 
>> means you're doing it the wrong way... ;-)
>>     
>
> Thought it sounded fun, so I did it:
>
>
> data Term = Lam String Term | Term :$ Term | Var String
>
> paren act = if act then \ a -> ('(':) . a . (')':) else id
>
> ppr i (Lam s t) = paren (i > 0) $ (:) '\\' . (++) s . (++) ". " . ppr 0 t
> ppr i (a :$ b)  = paren (i > 1) $ ppr 1 a . (:) ' ' . ppr 2 b
> ppr i (Var s)   = paren (i > 2) $ (++) s
>
> reduce (Lam nm bd :$ obj) = Just (subst bd) where
>     subst (Lam nm' bd') = Lam nm' (if nm == nm' then bd' else subst bd')
>     subst (a :$ b)      = subst a :$ subst b
>     subst (Var nm')     = if nm == nm' then obj else Var nm'
> reduce (left :$ right)    = fmap (:$ right) (reduce left)
> reduce other              = Nothing
>
> trail' ob = ppr 0 ob "\n" : maybe [] trail' (reduce ob)
> trail = concat . trail'
>
> The important part is the co-recursive trail, which produces a value
> using (:) before calling itself.  No monads necessary.
>   

Unbelievable... I spend an entire day coding something, and somebody 
else manages to write a complete working solution in under 20 minutes. 
Heh. 8^)

I feel it might take me another 20 minutes just to figure out how this 
works...



More information about the Haskell-Cafe mailing list