[Haskell] Fixpoint combinator without recursion

Edsko de Vries devriese at cs.tcd.ie
Wed Apr 4 14:39:24 EDT 2007


Hey,

It is well-known that negative datatypes can be used to encode
recursion, without actually explicitly using recursion. As a little
exercise, I set out to define the fixpoint combinator using negative
datatypes. I think the result is kinda cool :) Comments are welcome :)

Edsko

{-
	Definition of the fixpoint combinator without using recursion
	Thanks to Dimitri Vytiniotis for an explanation of the basic principle.
-}

module Y where

{-# NOINLINE app #-}

data Fn a = Fn (Fn a -> Fn a) | Value a

-- Application
app :: Fn a -> Fn a -> Fn a
app (Fn f) x = f x

-- \x -> f (x x)
delta :: Fn a -> Fn a
delta f = Fn (\x -> f `app` (x `app` x))

-- Y combinator: \f -> (\x -> f (x x)) (\x -> f (x x))
y :: Fn a -> Fn a
y f = delta f `app` delta f

-- Lifting a function to Fn
lift :: (a -> a) -> Fn a
lift f = Fn (\(Value x) -> Value (f x))

-- Inverse of lift
unlift :: Fn a -> (a -> a)
unlift f = \x -> case f `app` Value x of Value y -> y

-- Fixpoint combinator 
fix :: ((a -> a) -> (a -> a)) -> (a -> a)
fix f = unlift (y (Fn (\rec -> lift (f (unlift rec)))))

-- Example: factorial
facR f n = if n == 1 then 1 else n * f (n - 1)
fac = fix facR


More information about the Haskell mailing list