module Data.Generics.Traversable
(
GTraversable(..)
, gmap
, gmapM
, gfoldMap
, gfoldr
, gfoldl'
, Rec
, everywhere
, everywhere'
, everywhereM
, everything
)
where
import GHC.Exts (Constraint)
import Control.Applicative
import Control.Monad
import Data.Monoid
import Data.Functor.Identity
import Data.Functor.Constant
import Data.Generics.Traversable.Core
import Data.Generics.Traversable.Instances ()
class (GTraversable (Rec c) a, c a) => Rec (c :: * -> Constraint) a
instance (GTraversable (Rec c) a, c a) => Rec (c :: * -> Constraint) a
gmap
:: forall c a . (GTraversable c a)
=> (forall d . (c d) => d -> d)
-> a -> a
gmap f a = runIdentity (gtraverse @c (Identity . f) a)
gmapM
:: forall c m a . (Monad m, GTraversable c a)
=> (forall d . (c d) => d -> m d)
-> a -> m a
gmapM f = unwrapMonad . gtraverse @c (WrapMonad . f)
gfoldMap
:: forall c r a . (Monoid r, GTraversable c a)
=> (forall d . (c d) => d -> r)
-> a -> r
gfoldMap f = getConstant . gtraverse @c (Constant . f)
gfoldr
:: forall c a r . (GTraversable c a)
=> (forall d . (c d) => d -> r -> r)
-> r -> a -> r
gfoldr f z t = appEndo (gfoldMap @c (Endo . f) t) z
gfoldl'
:: forall c a r . (GTraversable c a)
=> (forall d . (c d) => r -> d -> r)
-> r -> a -> r
gfoldl' f z0 xs = gfoldr @c f' id xs z0
where f' x k z = k $! f z x
everywhere
:: forall c a .
(Rec c a)
=> (forall d. (Rec c d) => d -> d)
-> a -> a
everywhere f =
let
go :: forall b . Rec c b => b -> b
go = f . gmap @(Rec c) go
in go
everywhere'
:: forall c a .
(Rec c a)
=> (forall d. (Rec c d) => d -> d)
-> a -> a
everywhere' f =
let
go :: forall b . Rec c b => b -> b
go = gmap @(Rec c) go . f
in go
everywhereM
:: forall c m a .
(Monad m, Rec c a)
=> (forall d. (Rec c d) => d -> m d)
-> a -> m a
everywhereM f =
let
go :: forall b . Rec c b => b -> m b
go = f <=< gmapM @(Rec c) go
in go
everything
:: forall c r a .
(Rec c a)
=> (r -> r -> r)
-> (forall d . (Rec c d) => d -> r)
-> a -> r
everything combine f =
let
go :: forall b . Rec c b => b -> r
go x = gfoldl' @(Rec c) (\a y -> combine a (go y)) (f x) x
in go