[Haskell] ANNOUNCE: fixpoint 0.1

Roman Leshchinskiy rl at cse.unsw.edu.au
Tue Nov 20 05:17:07 EST 2007


I'm pleased to announce fixpoint 0.1, a (for now) small generic 
programming library which allows data types to be manipulated as 
fixpoints of their underlying functors. The library is mostly based on 
"Functional Programming with Bananas, Lenses, Envelopes and Barbed Wire" 
by Erik Meijer, Maarten Fokkinga and Ross Paterson.

The basic idea is to use associated data types, a recent GHC extension, 
to associate recursive types with their underlying functors. The core of 
the library is just one typeclass:

class Functor (Pre t) => Fixpoint t where
   data Pre t :: * -> *

   -- | Projection from the data type to its underlying functor.
   project :: t -> Pre t t

   -- | Injection from the underlying functor into the data type.
   inject  :: Pre t t -> t

Here, Pre t is a functor such that its fixpoint is t. For instance, for 
lists we have:

instance Fixpoint [a] where
   data Pre [a] s = Nil | Cons a s

   project []     = Nil
   project (x:xs) = Cons x xs

   inject Nil         = []
   inject (Cons x xs) = x : xs

With this, we can easily define things like catamorphisms:

cata :: Fixpoint t => (Pre t s -> s) -> t -> s
cata f = f . fmap (cata f) . project

which can then be used for generic programming:

size :: (Fixpoint t, Foldable (Pre t)) => t -> Int
size = cata (F.foldr (+) 1)

At the moment, the package doesn't contain much more than the above but 
this will change soon(ish).

To enjoy the minimalistic interface of fixpoint-0.1, grab it from 
Hackage or from my site:

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/fixpoint-0.1
http://www.cse.unsw.edu.au/~rl/code/fixpoint.html

Comments and suggestion are always welcome.

Roman



More information about the Haskell mailing list