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

Safe HaskellNone
LanguageHaskell2010

Data.Functor.Transformer

Contents

Description

Functors on indexed-types.

Synopsis

Functor

class FunctorT (t :: (k -> Type) -> k' -> Type) where Source #

Functor from indexed-types to indexed-types. Instances of FunctorT should satisfy the following laws:

tmap id = id
tmap f . tmap g = tmap (f . g)

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

Minimal complete definition

Nothing

Methods

tmap :: (forall a. f a -> g a) -> forall x. t f x -> t g x Source #

tmap :: forall f g x. CanDeriveFunctorT t f g x => (forall a. f a -> g a) -> t f x -> t g x Source #

Instances
FunctorT (IdentityT :: (k' -> Type) -> k' -> Type) Source # 
Instance details

Defined in Barbies.Internal.FunctorT

Methods

tmap :: (forall (a :: k). f a -> g a) -> forall (x :: k'0). IdentityT f x -> IdentityT g x Source #

FunctorT (Reverse :: (k' -> Type) -> k' -> Type) Source # 
Instance details

Defined in Barbies.Internal.FunctorT

Methods

tmap :: (forall (a :: k). f a -> g a) -> forall (x :: k'0). Reverse f x -> Reverse g x Source #

FunctorT (Backwards :: (k' -> Type) -> k' -> Type) Source # 
Instance details

Defined in Barbies.Internal.FunctorT

Methods

tmap :: (forall (a :: k). f a -> g a) -> forall (x :: k'0). Backwards f x -> Backwards g x Source #

FunctorT (ReaderT r :: (k' -> Type) -> k' -> Type) Source # 
Instance details

Defined in Barbies.Internal.FunctorT

Methods

tmap :: (forall (a :: k). f a -> g a) -> forall (x :: k'0). ReaderT r f x -> ReaderT r g x Source #

FunctorT (Sum f :: (k' -> Type) -> k' -> Type) Source # 
Instance details

Defined in Barbies.Internal.FunctorT

Methods

tmap :: (forall (a :: k). f0 a -> g a) -> forall (x :: k'0). Sum f f0 x -> Sum f g x Source #

FunctorT (Product f :: (k' -> Type) -> k' -> Type) Source # 
Instance details

Defined in Barbies.Internal.FunctorT

Methods

tmap :: (forall (a :: k). f0 a -> g a) -> forall (x :: k'0). Product f f0 x -> Product f g x Source #

Functor f => FunctorT (Compose f :: (k' -> Type) -> k' -> Type) Source # 
Instance details

Defined in Barbies.Internal.FunctorT

Methods

tmap :: (forall (a :: k). f0 a -> g a) -> forall (x :: k'0). Compose f f0 x -> Compose f g x Source #

(forall (f :: k'). FunctorB (b f)) => FunctorT (Flip b :: (k -> Type) -> k' -> Type) Source # 
Instance details

Defined in Barbies.Bi

Methods

tmap :: (forall (a :: k0). f a -> g a) -> forall (x :: k'0). Flip b f x -> Flip b g x Source #

FunctorT Lift Source # 
Instance details

Defined in Barbies.Internal.FunctorT

Methods

tmap :: (forall (a :: k). f a -> g a) -> forall (x :: k'). Lift f x -> Lift g x Source #

FunctorT MaybeT Source # 
Instance details

Defined in Barbies.Internal.FunctorT

Methods

tmap :: (forall (a :: k). f a -> g a) -> forall (x :: k'). MaybeT f x -> MaybeT g x Source #

FunctorT (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Barbies.Internal.FunctorT

Methods

tmap :: (forall (a :: k). f a -> g a) -> forall (x :: k'). WriterT w f x -> WriterT w g x Source #

FunctorT (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Barbies.Internal.FunctorT

Methods

tmap :: (forall (a :: k). f a -> g a) -> forall (x :: k'). WriterT w f x -> WriterT w g x Source #

FunctorT (StateT s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Barbies.Internal.FunctorT

Methods

tmap :: (forall (a :: k). f a -> g a) -> forall (x :: k'). StateT s f x -> StateT s g x Source #

FunctorT (StateT s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Barbies.Internal.FunctorT

Methods

tmap :: (forall (a :: k). f a -> g a) -> forall (x :: k'). StateT s f x -> StateT s g x Source #

FunctorT (ExceptT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Barbies.Internal.FunctorT

Methods

tmap :: (forall (a :: k). f a -> g a) -> forall (x :: k'). ExceptT e f x -> ExceptT e g x Source #

FunctorT (RWST r w s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Barbies.Internal.FunctorT

Methods

tmap :: (forall (a :: k). f a -> g a) -> forall (x :: k'). RWST r w s f x -> RWST r w s g x Source #

FunctorT (RWST r w s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Barbies.Internal.FunctorT

Methods

tmap :: (forall (a :: k). f a -> g a) -> forall (x :: k'). RWST r w s f x -> RWST r w s g x Source #

Traversable

class FunctorT t => TraversableT (t :: (k -> Type) -> k' -> Type) where Source #

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

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

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

Minimal complete definition

Nothing

Methods

ttraverse :: Applicative e => (forall a. f a -> e (g a)) -> forall x. t f x -> e (t g x) Source #

ttraverse :: (Applicative e, CanDeriveTraversableT t f g x) => (forall a. f a -> e (g a)) -> t f x -> e (t g x) Source #

Instances
TraversableT (IdentityT :: (k' -> Type) -> k' -> Type) Source # 
Instance details

Defined in Barbies.Internal.TraversableT

Methods

ttraverse :: Applicative e => (forall (a :: k). f a -> e (g a)) -> forall (x :: k'0). IdentityT f x -> e (IdentityT g x) Source #

TraversableT (Reverse :: (k' -> Type) -> k' -> Type) Source # 
Instance details

Defined in Barbies.Internal.TraversableT

Methods

ttraverse :: Applicative e => (forall (a :: k). f a -> e (g a)) -> forall (x :: k'0). Reverse f x -> e (Reverse g x) Source #

TraversableT (Backwards :: (k' -> Type) -> k' -> Type) Source # 
Instance details

Defined in Barbies.Internal.TraversableT

Methods

ttraverse :: Applicative e => (forall (a :: k). f a -> e (g a)) -> forall (x :: k'0). Backwards f x -> e (Backwards g x) Source #

TraversableT (Sum f :: (k' -> Type) -> k' -> Type) Source # 
Instance details

Defined in Barbies.Internal.TraversableT

Methods

ttraverse :: Applicative e => (forall (a :: k). f0 a -> e (g a)) -> forall (x :: k'0). Sum f f0 x -> e (Sum f g x) Source #

TraversableT (Product f :: (k' -> Type) -> k' -> Type) Source # 
Instance details

Defined in Barbies.Internal.TraversableT

Methods

ttraverse :: Applicative e => (forall (a :: k). f0 a -> e (g a)) -> forall (x :: k'0). Product f f0 x -> e (Product f g x) Source #

Traversable f => TraversableT (Compose f :: (k' -> Type) -> k' -> Type) Source # 
Instance details

Defined in Barbies.Internal.TraversableT

Methods

ttraverse :: Applicative e => (forall (a :: k). f0 a -> e (g a)) -> forall (x :: k'0). Compose f f0 x -> e (Compose f g x) Source #

(forall (f :: k'). TraversableB (b f)) => TraversableT (Flip b :: (k -> Type) -> k' -> Type) Source # 
Instance details

Defined in Barbies.Bi

Methods

ttraverse :: Applicative e => (forall (a :: k0). f a -> e (g a)) -> forall (x :: k'0). Flip b f x -> e (Flip b g x) Source #

TraversableT Lift Source # 
Instance details

Defined in Barbies.Internal.TraversableT

Methods

ttraverse :: Applicative e => (forall (a :: k). f a -> e (g a)) -> forall (x :: k'). Lift f x -> e (Lift g x) Source #

TraversableT MaybeT Source # 
Instance details

Defined in Barbies.Internal.TraversableT

Methods

ttraverse :: Applicative e => (forall (a :: k). f a -> e (g a)) -> forall (x :: k'). MaybeT f x -> e (MaybeT g x) Source #

TraversableT (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Barbies.Internal.TraversableT

Methods

ttraverse :: Applicative e => (forall (a :: k). f a -> e (g a)) -> forall (x :: k'). WriterT w f x -> e (WriterT w g x) Source #

TraversableT (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Barbies.Internal.TraversableT

Methods

ttraverse :: Applicative e => (forall (a :: k). f a -> e (g a)) -> forall (x :: k'). WriterT w f x -> e (WriterT w g x) Source #

TraversableT (ExceptT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Barbies.Internal.TraversableT

Methods

ttraverse :: Applicative e0 => (forall (a :: k). f a -> e0 (g a)) -> forall (x :: k'). ExceptT e f x -> e0 (ExceptT e g x) Source #

Utility functions

ttraverse_ :: (TraversableT t, Applicative e) => (forall a. f a -> e c) -> t f x -> e () Source #

Map each element to an action, evaluate these actions from left to right, and ignore the results.

tfoldMap :: (TraversableT t, Monoid m) => (forall a. f a -> m) -> t f x -> m Source #

Map each element to a monoid, and combine the results.

tsequence :: (Applicative e, TraversableT t) => t (Compose e f) x -> e (t f x) Source #

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

tsequence' :: (Applicative e, TraversableT t) => t e x -> e (t Identity x) Source #

A version of tsequence with f specialized to Identity.

Distributive

class FunctorT t => DistributiveT (t :: (Type -> Type) -> i -> Type) where Source #

A FunctorT where the effects can be distributed to the fields: tdistribute turns an effectful way of building a transformer-type into a pure transformer-type with effectful ways of computing the values of its fields.

This class is the categorical dual of TraversableT, with tdistribute the dual of tsequence and tcotraverse the dual of ttraverse. As such, instances need to satisfy these laws:

tdistribute . h = tmap (Compose . h . getCompose) . tdistribute    -- naturality
tdistribute . Identity = tmap (Compose . Identity)                 -- identity
tdistribute . Compose = fmap (Compose . Compose . fmap getCompose . getCompose) . tdistribute . fmap distribute -- composition

By specializing f to ((->) a) and g to Identity, we can define a function that decomposes a function on distributive transformers into a collection of simpler functions:

tdecompose :: DistributiveT b => (a -> b Identity) -> b ((->) a)
tdecompose = tmap (fmap runIdentity . getCompose) . tdistribute

Lawful instances of the class can then be characterized as those that satisfy:

trecompose . tdecompose = id
tdecompose . trecompose = id

This means intuitively that instances need to have a fixed shape (i.e. no sum-types can be involved). Typically, this means record types, as long as they don't contain fields where the functor argument is not applied.

There is a default implementation of tdistribute based on Generic. Intuitively, it works on product types where the shape of a pure value is uniquely defined and every field is covered by the argument f.

Minimal complete definition

Nothing

Methods

tdistribute :: Functor f => f (t g x) -> t (Compose f g) x Source #

tdistribute :: forall f g x. CanDeriveDistributiveT t f g x => f (t g x) -> t (Compose f g) x Source #

Instances
DistributiveT (Reverse :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Barbies.Internal.DistributiveT

Methods

tdistribute :: Functor f => f (Reverse g x) -> Reverse (Compose f g) x Source #

DistributiveT (IdentityT :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Barbies.Internal.DistributiveT

Methods

tdistribute :: Functor f => f (IdentityT g x) -> IdentityT (Compose f g) x Source #

DistributiveT (Backwards :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Barbies.Internal.DistributiveT

Methods

tdistribute :: Functor f => f (Backwards g x) -> Backwards (Compose f g) x Source #

DistributiveT (ReaderT r :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Barbies.Internal.DistributiveT

Methods

tdistribute :: Functor f => f (ReaderT r g x) -> ReaderT r (Compose f g) x Source #

Distributive f => DistributiveT (Compose f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Barbies.Internal.DistributiveT

Methods

tdistribute :: Functor f0 => f0 (Compose f g x) -> Compose f (Compose f0 g) x Source #

(forall (f :: i). DistributiveB (b f)) => DistributiveT (Flip b :: (Type -> Type) -> i -> Type) Source # 
Instance details

Defined in Barbies.Bi

Methods

tdistribute :: Functor f => f (Flip b g x) -> Flip b (Compose f g) x Source #

DistributiveT MaybeT Source # 
Instance details

Defined in Barbies.Internal.DistributiveT

Methods

tdistribute :: Functor f => f (MaybeT g x) -> MaybeT (Compose f g) x Source #

DistributiveT (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Barbies.Internal.DistributiveT

Methods

tdistribute :: Functor f => f (WriterT w g x) -> WriterT w (Compose f g) x Source #

DistributiveT (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Barbies.Internal.DistributiveT

Methods

tdistribute :: Functor f => f (WriterT w g x) -> WriterT w (Compose f g) x Source #

DistributiveT (StateT s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Barbies.Internal.DistributiveT

Methods

tdistribute :: Functor f => f (StateT s g x) -> StateT s (Compose f g) x Source #

DistributiveT (StateT s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Barbies.Internal.DistributiveT

Methods

tdistribute :: Functor f => f (StateT s g x) -> StateT s (Compose f g) x Source #

DistributiveT (ExceptT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Barbies.Internal.DistributiveT

Methods

tdistribute :: Functor f => f (ExceptT e g x) -> ExceptT e (Compose f g) x Source #

DistributiveT (RWST r w s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Barbies.Internal.DistributiveT

Methods

tdistribute :: Functor f => f (RWST r w s g x) -> RWST r w s (Compose f g) x Source #

DistributiveT (RWST r w s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Barbies.Internal.DistributiveT

Methods

tdistribute :: Functor f => f (RWST r w s g x) -> RWST r w s (Compose f g) x Source #

tdistribute' :: (DistributiveT t, Functor f) => f (t Identity x) -> t f x Source #

A version of tdistribute with g specialized to Identity.

tcotraverse :: (DistributiveT t, Functor f) => (forall a. f (g a) -> f a) -> f (t g x) -> t f x Source #

Dual of ttraverse

tdecompose :: DistributiveT t => (a -> t Identity x) -> t ((->) a) x Source #

Decompose a function returning a distributive transformer, into a collection of simpler functions.

trecompose :: FunctorT t => t ((->) a) x -> a -> t Identity x Source #

Recompose a decomposed function.

Applicative

class FunctorT t => ApplicativeT (t :: (k -> Type) -> k' -> Type) where Source #

A FunctorT with application, providing operations to:

  • embed an "empty" value (tpure)
  • align and combine values (tprod)

It should satisfy the following laws:

Naturality of tprod
tmap ((Pair a b) -> Pair (f a) (g b)) (u `tprod' v) = tmap f u `tprod' tmap g v
Left and right identity
tmap ((Pair _ b) -> b) (tpure e `tprod' v) = v
tmap ((Pair a _) -> a) (u `tprod' tpure e) = u
Associativity
tmap ((Pair a (Pair b c)) -> Pair (Pair a b) c) (u `tprod' (v `tprod' w)) = (u `tprod' v) `tprod' w

It is to FunctorT in the same way is Applicative relates to Functor. For a presentation of Applicative as a monoidal functor, see Section 7 of Applicative Programming with Effects.

There is a default implementation of tprod and tpure based on Generic. Intuitively, it works on types where the value of tpure is uniquely defined. This corresponds rougly to record types (in the presence of sums, there would be several candidates for tpure), where every field is either a Monoid or covered by the argument f.

Minimal complete definition

Nothing

Methods

tpure :: (forall a. f a) -> forall x. t f x Source #

tprod :: t f x -> t g x -> t (f `Product` g) x Source #

tpure :: CanDeriveApplicativeT t f f x => (forall a. f a) -> t f x Source #

tprod :: CanDeriveApplicativeT t f g x => t f x -> t g x -> t (f `Product` g) x Source #

Instances
ApplicativeT (Reverse :: (k' -> Type) -> k' -> Type) Source # 
Instance details

Defined in Barbies.Internal.ApplicativeT

Methods

tpure :: (forall (a :: k). f a) -> forall (x :: k'0). Reverse f x Source #

tprod :: Reverse f x -> Reverse g x -> Reverse (Product f g) x Source #

Applicative f => ApplicativeT (Compose f :: (k' -> Type) -> k' -> Type) Source # 
Instance details

Defined in Barbies.Internal.ApplicativeT

Methods

tpure :: (forall (a :: k). f0 a) -> forall (x :: k'0). Compose f f0 x Source #

tprod :: Compose f f0 x -> Compose f g x -> Compose f (Product f0 g) x Source #

(forall (f :: k'). ApplicativeB (b f)) => ApplicativeT (Flip b :: (k -> Type) -> k' -> Type) Source # 
Instance details

Defined in Barbies.Bi

Methods

tpure :: (forall (a :: k0). f a) -> forall (x :: k'0). Flip b f x Source #

tprod :: Flip b f x -> Flip b g x -> Flip b (Product f g) x Source #

Alternative f => ApplicativeT (Product f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Barbies.Internal.ApplicativeT

Methods

tpure :: (forall (a :: k). f0 a) -> forall (x :: k'). Product f f0 x Source #

tprod :: Product f f0 x -> Product f g x -> Product f (Product f0 g) x Source #

Alternative f => ApplicativeT (Sum f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Barbies.Internal.ApplicativeT

Methods

tpure :: (forall (a :: k). f0 a) -> forall (x :: k'). Sum f f0 x Source #

tprod :: Sum f f0 x -> Sum f g x -> Sum f (Product f0 g) x Source #

Utility functions

tzip :: ApplicativeT t => t f x -> t g x -> t (f `Product` g) x Source #

An alias of tprod.

tunzip :: ApplicativeT t => t (f `Product` g) x -> (t f x, t g x) Source #

An equivalent of unzip.

tzipWith :: ApplicativeT t => (forall a. f a -> g a -> h a) -> t f x -> t g x -> t h x Source #

An equivalent of zipWith.

tzipWith3 :: ApplicativeT t => (forall a. f a -> g a -> h a -> i a) -> t f x -> t g x -> t h x -> t i x Source #

An equivalent of zipWith3.

tzipWith4 :: ApplicativeT t => (forall a. f a -> g a -> h a -> i a -> j a) -> t f x -> t g x -> t h x -> t i x -> t j x Source #

An equivalent of zipWith4.

Monad

class FunctorT t => MonadT t where Source #

Some endo-functors on indexed-types are monads. Common examples would be "functor-transformers", like Compose or ReaderT. In that sense, MonadT is similar to MonadTrans but with additional structure (see also mmorph's MMonad class).

Notice though that while lift assumes a Monad instance of the value to be lifted, tlift has no such constraint. This means we cannot have instances for most "monad transformers", since lifting typically involves an fmap.

MonadT also corresponds to the indexed-monad of Kleisli arrows of outrageous fortune.

Instances of this class should to satisfy the monad laws. They laws can stated either in terms of (tlift, tjoin) or (tlift, tembed). In the former:

tmap h . tlift = tlift . h
tmap h . tjoin = tjoin . tmap (tmap h)
tjoin . tlift  = id
tjoin . 'tmap tlift' = id
tjoin . tjoin = tjoin . tmap tjoin

In the latter:

tembed f . tlift = f
tembed tlift = id
tembed f . tembed g = tembed (tembed f . g)

Minimal complete definition

tlift, tjoin | tlift, tembed

Methods

tlift :: f a -> t f a Source #

Lift a functor to a transformed functor.

tjoin :: t (t f) a -> t f a Source #

The conventional monad join operator. It is used to remove one level of monadic structure, projecting its bound argument into the outer level.

tembed :: MonadT t => (forall x. f x -> t g x) -> t f a -> t g a Source #

Analogous to (=<<).

Instances
MonadT (Reverse :: (k' -> Type) -> k' -> Type) Source # 
Instance details

Defined in Barbies.Internal.MonadT

Methods

tlift :: f a -> Reverse f a Source #

tjoin :: Reverse (Reverse f) a -> Reverse f a Source #

tembed :: MonadT Reverse => (forall (x :: k'0). f x -> Reverse g x) -> Reverse f a -> Reverse g a Source #

MonadT (IdentityT :: (k' -> Type) -> k' -> Type) Source # 
Instance details

Defined in Barbies.Internal.MonadT

Methods

tlift :: f a -> IdentityT f a Source #

tjoin :: IdentityT (IdentityT f) a -> IdentityT f a Source #

tembed :: MonadT IdentityT => (forall (x :: k'0). f x -> IdentityT g x) -> IdentityT f a -> IdentityT g a Source #

MonadT (Backwards :: (k' -> Type) -> k' -> Type) Source # 
Instance details

Defined in Barbies.Internal.MonadT

Methods

tlift :: f a -> Backwards f a Source #

tjoin :: Backwards (Backwards f) a -> Backwards f a Source #

tembed :: MonadT Backwards => (forall (x :: k'0). f x -> Backwards g x) -> Backwards f a -> Backwards g a Source #

MonadT (ReaderT r :: (k' -> Type) -> k' -> Type) Source # 
Instance details

Defined in Barbies.Internal.MonadT

Methods

tlift :: f a -> ReaderT r f a Source #

tjoin :: ReaderT r (ReaderT r f) a -> ReaderT r f a Source #

tembed :: MonadT (ReaderT r) => (forall (x :: k'0). f x -> ReaderT r g x) -> ReaderT r f a -> ReaderT r g a Source #

MonadT (Sum f :: (k' -> Type) -> k' -> Type) Source # 
Instance details

Defined in Barbies.Internal.MonadT

Methods

tlift :: f0 a -> Sum f f0 a Source #

tjoin :: Sum f (Sum f f0) a -> Sum f f0 a Source #

tembed :: MonadT (Sum f) => (forall (x :: k'0). f0 x -> Sum f g x) -> Sum f f0 a -> Sum f g a Source #

Monad f => MonadT (Compose f :: (k' -> Type) -> k' -> Type) Source # 
Instance details

Defined in Barbies.Internal.MonadT

Methods

tlift :: f0 a -> Compose f f0 a Source #

tjoin :: Compose f (Compose f f0) a -> Compose f f0 a Source #

tembed :: MonadT (Compose f) => (forall (x :: k'0). f0 x -> Compose f g x) -> Compose f f0 a -> Compose f g a Source #

MonadT Lift Source # 
Instance details

Defined in Barbies.Internal.MonadT

Methods

tlift :: f a -> Lift f a Source #

tjoin :: Lift (Lift f) a -> Lift f a Source #

tembed :: MonadT Lift => (forall (x :: k'). f x -> Lift g x) -> Lift f a -> Lift g a Source #

Alternative f => MonadT (Product f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Barbies.Internal.MonadT

Methods

tlift :: f0 a -> Product f f0 a Source #

tjoin :: Product f (Product f f0) a -> Product f f0 a Source #

tembed :: MonadT (Product f) => (forall (x :: k'). f0 x -> Product f g x) -> Product f f0 a -> Product f g a Source #

Constraints and instance dictionaries

class FunctorT t => ConstraintsT (t :: (kl -> *) -> kr -> *) where Source #

Instances of this class provide means to talk about constraints, both at compile-time, using AllT, and at run-time, in the form of Dict, via taddDicts.

A manual definition would look like this:

data T f a = A (f Int) (f String) | B (f Bool) (f Int)

instance ConstraintsT T where
  type AllT c T = (c Int, c String, c Bool)

  taddDicts t = case t of
    A x y -> A (Pair Dict x) (Pair Dict y)
    B z w -> B (Pair Dict z) (Pair Dict w)

Now, when we given a T f, if we need to use the Show instance of their fields, we can use:

taddDicts :: AllT Show t => t f -> t (Dict Show `Product' f)

There is a default implementation of ConstraintsT for Generic types, so in practice one will simply do:

derive instance Generic (T f a)
instance ConstraintsT T

Minimal complete definition

Nothing

Associated Types

type AllT (c :: k -> Constraint) t :: Constraint Source #

AllT c t should contain a constraint c a for each a occurring under an f in t f.

For requiring constraints of the form c (f a), use AllTF.

Methods

taddDicts :: forall c f x. AllT c t => t f x -> t (Dict c `Product` f) x Source #

taddDicts :: forall c f x. (CanDeriveConstraintsT c t f x, AllT c t) => t f x -> t (Dict c `Product` f) x Source #

type AllTF c f t = AllT (ClassF c f) t Source #

Similar to AllT but will put the functor argument f between the constraint c and the type a.

Utility functions

tmapC :: forall c t f g x. (AllT c t, ConstraintsT t) => (forall a. c a => f a -> g a) -> t f x -> t g x Source #

Like tmap but a constraint is allowed to be required on each element of t.

ttraverseC :: forall c t f g e x. (TraversableT t, ConstraintsT t, AllT c t, Applicative e) => (forall a. c a => f a -> e (g a)) -> t f x -> e (t g x) Source #

Like ttraverse but with a constraint on the elements of t.

Support for generic derivations

newtype Rec (p :: Type) a x Source #

Constructors

Rec 

Fields

Instances
GTraversable (n :: k3) (f :: k2 -> Type) (g :: k2 -> Type) (Rec a a :: k1 -> Type) (Rec a a :: k1 -> Type) Source # 
Instance details

Defined in Barbies.Generics.Traversable

Methods

gtraverse :: Applicative t => Proxy n -> (forall (a0 :: k). f a0 -> t (g a0)) -> Rec a a x -> t (Rec a a x) Source #

GConstraints n (c :: k3 -> Constraint) (f :: k2) (Rec a' a :: Type -> Type) (Rec a a :: k1 -> Type) (Rec a a :: k1 -> Type) Source # 
Instance details

Defined in Barbies.Generics.Constraints

Methods

gaddDicts :: GAll n c (Rec a' a) => Rec a a x -> Rec a a x Source #

Monoid x => GApplicative (n :: k3) (f :: k2 -> Type) (g :: k2 -> Type) (Rec x x :: k1 -> Type) (Rec x x :: k1 -> Type) (Rec x x :: k1 -> Type) Source # 
Instance details

Defined in Barbies.Generics.Applicative

Methods

gprod :: Proxy n -> Proxy f -> Proxy g -> Rec x x x0 -> Rec x x x0 -> Rec x x x0 Source #

gpure :: (f ~ g, Rec x x ~ Rec x x) => Proxy n -> Proxy f -> Proxy (Rec x x) -> Proxy (Rec x x) -> (forall (a :: k). f a) -> Rec x x x0 Source #

GFunctor n (f :: k2 -> Type) (g :: k2 -> Type) (Rec x x :: k1 -> Type) (Rec x x :: k1 -> Type) Source # 
Instance details

Defined in Barbies.Generics.Functor

Methods

gmap :: Proxy n -> (forall (a :: k). f a -> g a) -> Rec x x x0 -> Rec x x x0 Source #

repbi ~ repbb => GBare n (Rec repbi repbi :: k -> Type) (Rec repbb repbb :: k -> Type) Source # 
Instance details

Defined in Barbies.Generics.Bare

Methods

gstrip :: Proxy n -> Rec repbi repbi x -> Rec repbb repbb x Source #

gcover :: Proxy n -> Rec repbb repbb x -> Rec repbi repbi x Source #

type GAll n (c :: k -> Constraint) (Rec a a :: Type -> Type) Source # 
Instance details

Defined in Barbies.Generics.Constraints

type GAll n (c :: k -> Constraint) (Rec a a :: Type -> Type) = ()