barbies-0.1.3.1: Classes for working with types that can change clothes.

Safe HaskellNone
LanguageHaskell2010

Data.Barbie.Internal.Traversable

Description

 
Synopsis

Documentation

class FunctorB b => TraversableB b where Source #

Barbie-types that can be traversed from left to right. Instances should satisfy the following laws:

 t . btraverse f = btraverse (t . f)  -- naturality
btraverse Identity = Identity         -- identity
btraverse (Compose . fmap g . f) = Compose . fmap (btraverse g) . btraverse f -- composition

There is a default btraverse implementation for Generic types, so instances can derived automatically.

Methods

btraverse :: Applicative t => (forall a. f a -> t (g a)) -> b f -> t (b g) Source #

btraverse :: (Applicative t, CanDeriveGenericInstance b) => (forall a. f a -> t (g a)) -> b f -> t (b g) Source #

Instances
TraversableB b => TraversableB (Barbie b) Source # 
Instance details

Defined in Data.Barbie.Internal.Instances

Methods

btraverse :: Applicative t => (forall a. f a -> t (g a)) -> Barbie b f -> t (Barbie b g) Source #

bsequence :: (Applicative f, TraversableB b) => b (Compose f g) -> f (b g) Source #

Evaluate each action in the structure from left to right, and collect the results.

type CanDeriveGenericInstance b = (Generic (b (Target F)), Generic (b (Target G)), GTraversableB (Rep (b (Target F))), Rep (b (Target G)) ~ Repl (Target F) (Target G) (Rep (b (Target F)))) Source #

Intuivively, the requirements to have TraversableB B derived are:

  • There is an instance of Generic (B f) for every f
  • If f is used as argument to some type in the definition of B, it is only on a Barbie-type with a TraversableB instance.
  • Recursive usages of B f are allowed to appear as argument to a Traversable (e.g. @Maybe (B f)')

class GTraversableB b Source #

Minimal complete definition

gbtraverse

Instances
GTraversableB (V1 :: * -> *) Source # 
Instance details

Defined in Data.Barbie.Internal.Traversable

Methods

gbtraverse :: Applicative t => (forall a. f a -> t (g a)) -> V1 x -> t (Repl (Target F) (Target G) V1 x)

GTraversableB (U1 :: * -> *) Source # 
Instance details

Defined in Data.Barbie.Internal.Traversable

Methods

gbtraverse :: Applicative t => (forall a. f a -> t (g a)) -> U1 x -> t (Repl (Target F) (Target G) U1 x)

(K1 i c :: * -> *) ~ Repl (Target F) (Target G) (K1 i c :: * -> *) => GTraversableB (K1 i c :: * -> *) Source # 
Instance details

Defined in Data.Barbie.Internal.Traversable

Methods

gbtraverse :: Applicative t => (forall a. f a -> t (g a)) -> K1 i c x -> t (Repl (Target F) (Target G) (K1 i c) x)

(GTraversableB l, GTraversableB r) => GTraversableB (l :+: r) Source # 
Instance details

Defined in Data.Barbie.Internal.Traversable

Methods

gbtraverse :: Applicative t => (forall a. f a -> t (g a)) -> (l :+: r) x -> t (Repl (Target F) (Target G) (l :+: r) x)

(GTraversableB l, GTraversableB r) => GTraversableB (l :*: r) Source # 
Instance details

Defined in Data.Barbie.Internal.Traversable

Methods

gbtraverse :: Applicative t => (forall a. f a -> t (g a)) -> (l :*: r) x -> t (Repl (Target F) (Target G) (l :*: r) x)

GTraversableB x => GTraversableB (M1 i c x) Source # 
Instance details

Defined in Data.Barbie.Internal.Traversable

Methods

gbtraverse :: Applicative t => (forall a. f a -> t (g a)) -> M1 i c x x0 -> t (Repl (Target F) (Target G) (M1 i c x) x0)

gbtraverseDefault :: (Applicative t, CanDeriveGenericInstance b) => (forall a. f a -> t (g a)) -> b f -> t (b g) Source #

Default implementation of btraverse based on Generic.