Hi,
Sorry for taking so long to reply. I don't have a strong opinion about this; if no one objects I'll add it.
Thanks,
Pedro
Hi,
One thing that is hard to do with SYB (as well as with alternative generics packages in Haskell) at present is to query while keeping state that is carried down the tree but not to siblings, and use that in deciding what to return from the query.
I propose a new scheme be added to Data.Generics.Schemes, called everythingWithContext (as defined below). An everywhereWithContext might also be useful, but I don't think you would be able to define the transformation using the existing combinators, so I have limited my proposal to everythingWithContext for now.
Yours Sincerely,
Andrew Miller
{- | Summarise all nodes in top-down, left-to-right order, carrying some state down
the tree during the computation, but not left-to-right to siblings.
Example: Suppose you want to compute the maximum depth of adds in the below
simple co-recursive structure, ignoring all the other constructors. You could
write code like the following:
data MyStructure = SomeConst Int | Add MyStructure MyStructure | Times MyStructure MyStructure | Wrapped Wrapper deriving (Data, Typeable)
data Wrapper = Wrapper MyStructure deriving (Data, Typeable)
myExample = Add (SomeConst 10) (Add (Wrapped . Wrapper $ (Add (Add (Add (Times (SomeConst 30) (SomeConst 90)) (SomeConst 70)) (SomeConst 40)) (SomeConst 50))) (Add (SomeConst 20) (Add (SomeConst 60) (SomeConst 80))))
computeDepth = everythingWithContext 0 max ((\s -> (0, s)) `mkQ` depthOfAdd)
where
depthOfAdd (Add _ _) s = (s, s + 1)
depthOfAdd _ s = (s, s)
main = print $ computeDepth myExample
-}
everythingWithContext :: s -> (r -> r -> r) -> GenericQ (s -> (r, s)) -> GenericQ r
everythingWithContext s0 f q x =
foldl f r (gmapQ (everythingWithContext s' f q) x)
where (r, s') = q x s0
_______________________________________________
Generics mailing list
Generics@haskell.org
http://www.haskell.org/mailman/listinfo/generics