module Data.Generics.Biplate
(
module Data.Generics.UniplateStrOn,
module Data.Generics.Biplate
) where
import Data.Generics.UniplateStrOn
class Uniplate to => Biplate from to where
biplate :: BiplateType from to
biplateList :: Biplate from to => from -> ([to], [to] -> from)
biplateList x = (c, b . d)
where
(a,b) = biplate x
(c,d) = strStructure a
universeBi :: Biplate from to => from -> [to]
universeBi = universeOn biplate
childrenBi :: Biplate from to => from -> [to]
childrenBi = childrenOn biplate
transformBi :: Biplate from to => (to -> to) -> from -> from
transformBi = transformOn biplate
transformBiM :: (Monad m, Biplate from to) => (to -> m to) -> from -> m from
transformBiM = transformOnM biplate
rewriteBi :: Biplate from to => (to -> Maybe to) -> from -> from
rewriteBi = rewriteOn biplate
rewriteBiM :: (Monad m, Biplate from to) => (to -> m (Maybe to)) -> from -> m from
rewriteBiM = rewriteOnM biplate
descendBi :: Biplate from to => (to -> to) -> from -> from
descendBi = descendOn biplate
descendBiM :: (Monad m, Biplate from to) => (to -> m to) -> from -> m from
descendBiM = descendOnM biplate
contextsBi:: Biplate from to => from -> [(to, to -> from)]
contextsBi = contextsOn biplate
holesBi:: Biplate from to => from -> [(to, to -> from)]
holesBi = holesOn biplate