Re: [Haskell-cafe] Largest types in SYB

2009-12-21 Thread José Pedro Magalhães
Hello Paul,

On Fri, Dec 18, 2009 at 16:47, Paul Keir pk...@dcs.gla.ac.uk wrote:

 (...)

 I'm enjoying using SYB, and had hoped to use only functions from the
 package,
 but couldn't find a way; and this does the job for now. I've also seen that
 there are many other approaches to generic programming than SYB (even for
 AST
 transformations in particular) but I wanted to understand SYB first. I'm
 interested to know if anyone has a more elegant SYB solution.


I think this looks fine. The package only provides basic generic
functionality, but when you need something more specific you can use the
basics to write your own generic functions, which is what you did.


Cheers,
Pedro
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Largest types in SYB

2009-12-18 Thread Paul Keir
I was looking for a simple generic technique targeting and transforming
the largest terms of a particular type. For example, with Expr and
Val declared as:

data Expr = Val Val | Add Expr Expr | Sub Expr Expr
  deriving (Show, Eq, Typeable, Data)

data Val = Var String | Struct [Expr]
  deriving (Show, Eq, Typeable, Data)

and a test Expr e,

e = Sub (Val $ Var A)
(Add (Val $ Var X1)
 (Val $ Struct [Add (Val $ Var Y1)
(Val $ Var Y2)]))

I wanted to replace only the inner Add expression
  Add (Val $ Var Y1) (Val $ Var Y2)
because its parent is not of the same type as itself (it's a list),
using a function such as chopAdd:

chopAdd (Add _ _)  = Val $ Var AddChop
chopAdd e  = e

But using everywhere from Scrap Your BoilerPlate (SYB):
everywhere (mkT repAdd) e
I'd get:
Sub (Val (Var A)) (Val (Var AddChop))
while I was hoping for:
Sub (Val (Var A)) (Add (Val (Var X1)) (Val (Struct [Val (Var AddChop)])))

The Haskell.org SYB wiki presents listifyWholeLists. This is relevant, though
it applies queries rather than transformations. It uses a function called
synthesize, which I was ultimately unable to properly reference, or
apply to the problem at hand.

So here is my solution:

everywhereBar :: GenericQ Bool - GenericT - GenericT
everywhereBar q f x
 | q x   =   (gmapT (everywhereBar (typeEq x) f) x)
 | otherwise = f (gmapT (everywhereBar (typeEq x) f) x)

 where typeEq p c = typeOf p == typeOf c

It's like SYB's everywhereBut, except
1. The consequence of q x being True is only to remove
   the application of f to the parent; not to stop traversal.
2. q is not constant. Instead it is the partial application of
   a local function, typeEq.

An application looks like:
everywhereBar (const False) (mkT repAdd) e
with (const False) the user is choosing the outcome of the very first q x
in everywhereBar.

I'm enjoying using SYB, and had hoped to use only functions from the package,
but couldn't find a way; and this does the job for now. I've also seen that
there are many other approaches to generic programming than SYB (even for AST
transformations in particular) but I wanted to understand SYB first. I'm
interested to know if anyone has a more elegant SYB solution.

And here's the monadic version:

everywhereBarM :: Monad m = GenericQ Bool - GenericM m - GenericM m
everywhereBarM q f x
 | q x   =  gmapM (everywhereBarM (typeEq x) f) x
 | otherwise = do x' - gmapM (everywhereBarM (typeEq x) f) x
  f x'
 where typeEq p c = typeOf p == typeOf c

Cheers,
Paul

The University of Glasgow, charity number SC004401
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe