[Haskell-cafe] Re: Is there already an abstraction for this?

Mitchell, Neil neil.mitchell.2 at credit-suisse.com
Mon Oct 20 03:34:35 EDT 2008


Hi Larry,

There is already an abstraction for this, its called transform, and it
resides in the Uniplate library:
http://www-users.cs.york.ac.uk/~ndm/uniplate/

I have no idea what it is, or if it exists in the algebra library!

Thanks

Neil



> -----Original Message-----
> From: haskell-cafe-bounces at haskell.org 
> [mailto:haskell-cafe-bounces at haskell.org] On Behalf Of Larry Evans
> Sent: 18 October 2008 10:48 pm
> To: haskell-cafe at haskell.org
> Subject: [Haskell-cafe] Re: Is there already an abstraction for this?
> 
> On 09/23/08 01:01, Jake Mcarthur wrote:
>  > -----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
> 
> According to:
> 
>    cata :: Functor f => Algebra f a -> FixF f -> a
> 
> from:
> 
>    http://comonad.com/reader/2008/catamorphism
> 
> ident must be:
> 
>    Algebra f a
> 
> for some Functor f; however, I don't see any declaration of 
> ident as an Algebra f a.  Could you please elaborate.
> I'm trying to apply this to a simple boolean simplifier shown 
> in the attachement.  As near as I can figure, maybe the f 
> could be the ArityN in the attachment and maybe the a would 
> be (Arity0 ConBool var).  The output of the last line of 
> attachment is:
> 
>    bool_eval:f+f+v0=(:+) (Op0 (OpCon BoolFalse)) (Op0 (OpVar V0))
> 
> however, what I want is a complete reduction to:
> 
>    (OpVar V0)
> 
> How can this be done using catamorphisms?
> 
> 
> 

==============================================================================
Please access the attached hyperlink for an important electronic communications disclaimer: 

http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html
==============================================================================



More information about the Haskell-Cafe mailing list