traverse-with-class-1.0.1.1: Generic applicative traversals
Safe HaskellNone
LanguageHaskell2010

Data.Generics.Traversable

Description

All of the functions below work only on «interesting» subterms. It is up to the instance writer to decide which subterms are interesting and which subterms should count as immediate. This can also depend on the context c.

The context, denoted c, is a constraint (of kind * -> Constraint) that provides additional facilities to work with the data. In most cases, the context cannot be inferred automatically. You need to provide it using the type application syntax:

gmap @Show f x
everywhere @Typeable f x

etc.

For more information, see:

Scrap your boilerplate with class
https://www.microsoft.com/en-us/research/publication/scrap-your-boilerplate-with-class/
Generalizing generic fold
http://ro-che.info/articles/2013-03-11-generalizing-gfoldl
Synopsis

Open recursion combinators

class GTraversable (c :: * -> Constraint) a where Source #

Minimal complete definition

Nothing

Methods

gtraverse :: Applicative f => (forall d. c d => d -> f d) -> a -> f a Source #

Applicative traversal over (a subset of) immediate subterms. This is a generic version of traverse.

The supplied function is applied only to the «interesting» subterms.

Other subterms are lifted using pure, and the whole structure is folded back using <*>.

gtraverse has a default implementation const pure, which works for types without interesting subterms (in particular, atomic types).

Instances

Instances details
GTraversable c Ordering Source # 
Instance details

Defined in Data.Generics.Traversable.Instances

Methods

gtraverse :: Applicative f => (forall d. c d => d -> f d) -> Ordering -> f Ordering Source #

GTraversable c Char Source # 
Instance details

Defined in Data.Generics.Traversable.Instances

Methods

gtraverse :: Applicative f => (forall d. c d => d -> f d) -> Char -> f Char Source #

GTraversable c Double Source # 
Instance details

Defined in Data.Generics.Traversable.Instances

Methods

gtraverse :: Applicative f => (forall d. c d => d -> f d) -> Double -> f Double Source #

GTraversable c Float Source # 
Instance details

Defined in Data.Generics.Traversable.Instances

Methods

gtraverse :: Applicative f => (forall d. c d => d -> f d) -> Float -> f Float Source #

GTraversable c Integer Source # 
Instance details

Defined in Data.Generics.Traversable.Instances

Methods

gtraverse :: Applicative f => (forall d. c d => d -> f d) -> Integer -> f Integer Source #

GTraversable c Int Source # 
Instance details

Defined in Data.Generics.Traversable.Instances

Methods

gtraverse :: Applicative f => (forall d. c d => d -> f d) -> Int -> f Int Source #

GTraversable c Bool Source # 
Instance details

Defined in Data.Generics.Traversable.Instances

Methods

gtraverse :: Applicative f => (forall d. c d => d -> f d) -> Bool -> f Bool Source #

GTraversable c () Source # 
Instance details

Defined in Data.Generics.Traversable.Instances

Methods

gtraverse :: Applicative f => (forall d. c d => d -> f d) -> () -> f () Source #

(Generic a, GTraversable' c (Rep a)) => GTraversable c a Source # 
Instance details

Defined in Data.Generics.Traversable.Generic

Methods

gtraverse :: Applicative f => (forall d. c d => d -> f d) -> a -> f a Source #

GTraversable c (Ratio n) Source # 
Instance details

Defined in Data.Generics.Traversable.Instances

Methods

gtraverse :: Applicative f => (forall d. c d => d -> f d) -> Ratio n -> f (Ratio n) Source #

c a => GTraversable c (Maybe a) Source # 
Instance details

Defined in Data.Generics.Traversable.Instances

Methods

gtraverse :: Applicative f => (forall d. c d => d -> f d) -> Maybe a -> f (Maybe a) Source #

c a => GTraversable c [a] Source # 
Instance details

Defined in Data.Generics.Traversable.Instances

Methods

gtraverse :: Applicative f => (forall d. c d => d -> f d) -> [a] -> f [a] Source #

(c a, c b) => GTraversable c (Either a b) Source # 
Instance details

Defined in Data.Generics.Traversable.Instances

Methods

gtraverse :: Applicative f => (forall d. c d => d -> f d) -> Either a b -> f (Either a b) Source #

(c a, c b) => GTraversable c (a, b) Source # 
Instance details

Defined in Data.Generics.Traversable.Instances

Methods

gtraverse :: Applicative f => (forall d. c d => d -> f d) -> (a, b) -> f (a, b) Source #

(c1 a, c1 b, c1 c2) => GTraversable c1 (a, b, c2) Source # 
Instance details

Defined in Data.Generics.Traversable.Instances

Methods

gtraverse :: Applicative f => (forall d. c1 d => d -> f d) -> (a, b, c2) -> f (a, b, c2) Source #

gmap :: forall c a. GTraversable c a => (forall d. c d => d -> d) -> a -> a Source #

Generic map over the immediate subterms

gmapM :: forall c m a. (Monad m, GTraversable c a) => (forall d. c d => d -> m d) -> a -> m a Source #

Generic monadic map over the immediate subterms

gfoldMap :: forall c r a. (Monoid r, GTraversable c a) => (forall d. c d => d -> r) -> a -> r Source #

Generic monoidal fold over the immediate subterms (cf. foldMap)

gfoldr :: forall c a r. GTraversable c a => (forall d. c d => d -> r -> r) -> r -> a -> r Source #

Generic right fold over the immediate subterms

gfoldl' :: forall c a r. GTraversable c a => (forall d. c d => r -> d -> r) -> r -> a -> r Source #

Generic strict left fold over the immediate subterms

Closed recursion combinators

class (GTraversable (Rec c) a, c a) => Rec (c :: * -> Constraint) a Source #

Rec enables "deep traversals".

It is satisfied automatically when its superclass constraints are satisfied — you are not supposed to declare new instances of this class.

Instances

Instances details
(GTraversable (Rec c) a, c a) => Rec c a Source # 
Instance details

Defined in Data.Generics.Traversable

everywhere :: forall c a. Rec c a => (forall d. Rec c d => d -> d) -> a -> a Source #

Apply a transformation everywhere in bottom-up manner

everywhere' :: forall c a. Rec c a => (forall d. Rec c d => d -> d) -> a -> a Source #

Apply a transformation everywhere in top-down manner

everywhereM :: forall c m a. (Monad m, Rec c a) => (forall d. Rec c d => d -> m d) -> a -> m a Source #

Monadic variation on everywhere

everything :: forall c r a. Rec c a => (r -> r -> r) -> (forall d. Rec c d => d -> r) -> a -> r Source #

Strict left fold over all elements, top-down