[Haskell-cafe] Idiomatic usage of the fixpoint library

Roman Cheplyaka roma at ro-che.info
Sun Sep 4 12:31:08 CEST 2011


Hi,

I'm looking for an example of idiomatic usage of the fixpoint library[1].

[1]: http://hackage.haskell.org/package/fixpoint-0.1.1

Here's what I managed to get:

    {-# LANGUAGE TypeFamilies, FlexibleContexts, UndecidableInstances, FlexibleInstances #-}
    import Data.Fixpoint

    newtype Expr = Expr { unExpr :: Pre Expr Expr }

    instance Functor (Pre Expr) => Fixpoint Expr where
        data Pre Expr a
            = Add a a
            | Const Int
        project = unExpr
        inject = Expr

    instance Functor (Pre Expr) where
        fmap f (Const x) = Const x
        fmap f (Add x1 x2) = Add (f x1) (f x2)

    eval = cata eval' where
        eval' (Const x) = x
        eval' (Add x1 x2) = x1 + x2

There are some issues with this code, compared to simply using

    newtype Fix f = In { out :: f (Fix f) }

to build an Expr.

1. Since 'Pre' is a data (not type) family, we cannot simply make use of
   a functor defined elsewhere. We need to define the functor inside the
   instance declaration (or at least wrap an existing functor).

2. I wasn't able to derive the Functor instance, getting an error

        Derived instance `Functor (Pre Expr)'
          requires illegal partial application of data type family Pre
        In the data type instance declaration for `Pre'

3. Having to use UndecidableInstances makes me feel a bit uncomfortable.

This makes me think that the intended usage is somewhat different.
So, could someone give an example?

-- 
Roman I. Cheplyaka :: http://ro-che.info/



More information about the Haskell-Cafe mailing list