-----BEGIN PGP SIGNED MESSAGE-----
Hash: SHA1

The first thing I thought of was to try to apply one of the recursion schemes in the category-extras package. Here is what I managed using catamorphism.

- - Jake

- 
--------------------------------------------------------------------------------

data Expr' a
  = Quotient a a
  | Product a a
  | Sum a a
  | Difference a a
  | Lit Double
  | Var Char

type Expr = FixF Expr'

instance Functor Expr' where
    fmap f (a `Quotient` b) = f a `Quotient` f b
    fmap f (a `Product` b) = f a `Product` f b
    fmap f (a `Sum` b) = f a `Sum` f b
    fmap f (a `Difference` b) = f a `Difference` f b
    fmap _ (Lit x) = Lit x
    fmap _ (Var x) = Var x

identity = cata ident
    where ident (a `Quotient` InF (Lit 1)) = a
          ident (a `Product` InF (Lit 1)) = a
          ident (InF (Lit 1) `Product` b) = b
          ident (a `Sum` InF (Lit 0)) = a
          ident (InF (Lit 0) `Sum` b) = b
          ident (a `Difference` InF (Lit 0)) = a
          ident (Lit x) = InF $ Lit x
          ident (Var x) = InF $ Var x
-----BEGIN PGP SIGNATURE-----
Version: GnuPG v1.4.8 (Darwin)

iEYEARECAAYFAkjYhjwACgkQye5hVyvIUKnwhgCgypz0ppFgqn2dMhoJPUzO4+J1
BMUAni277vm9d2e5wTFt2Qrx+DDVjs6z
=0SHe
-----END PGP SIGNATURE-----
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to