Safe Haskell | None |
---|---|
Language | Haskell2010 |
Functors on indexed-types.
Synopsis
- class FunctorT (t :: (k -> Type) -> k' -> Type) where
- tmap :: (forall a. f a -> g a) -> forall x. t f x -> t g x
- class FunctorT t => TraversableT (t :: (k -> Type) -> k' -> Type) where
- ttraverse :: Applicative e => (forall a. f a -> e (g a)) -> forall x. t f x -> e (t g x)
- ttraverse_ :: (TraversableT t, Applicative e) => (forall a. f a -> e c) -> t f x -> e ()
- tfoldMap :: (TraversableT t, Monoid m) => (forall a. f a -> m) -> t f x -> m
- tsequence :: (Applicative e, TraversableT t) => t (Compose e f) x -> e (t f x)
- tsequence' :: (Applicative e, TraversableT t) => t e x -> e (t Identity x)
- class FunctorT t => DistributiveT (t :: (Type -> Type) -> i -> Type) where
- tdistribute :: Functor f => f (t g x) -> t (Compose f g) x
- tdistribute' :: (DistributiveT t, Functor f) => f (t Identity x) -> t f x
- tcotraverse :: (DistributiveT t, Functor f) => (forall a. f (g a) -> f a) -> f (t g x) -> t f x
- tdecompose :: DistributiveT t => (a -> t Identity x) -> t ((->) a) x
- trecompose :: FunctorT t => t ((->) a) x -> a -> t Identity x
- class FunctorT t => ApplicativeT (t :: (k -> Type) -> k' -> Type) where
- tzip :: ApplicativeT t => t f x -> t g x -> t (f `Product` g) x
- tunzip :: ApplicativeT t => t (f `Product` g) x -> (t f x, t g x)
- tzipWith :: ApplicativeT t => (forall a. f a -> g a -> h a) -> t f x -> t g x -> t h x
- 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
- 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
- class FunctorT t => MonadT t where
- class FunctorT t => ConstraintsT (t :: (kl -> *) -> kr -> *) where
- type AllT (c :: k -> Constraint) t :: Constraint
- taddDicts :: forall c f x. AllT c t => t f x -> t (Dict c `Product` f) x
- type AllTF c f t = AllT (ClassF c f) t
- 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
- 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)
- newtype Rec (p :: Type) a x = Rec {}
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.
Nothing
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
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) -- naturalityttraverse
Identity
=Identity
-- identityttraverse
(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.
Nothing
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
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 #
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
-- naturalitytdistribute
.Identity
=tmap
(Compose
.Identity
) -- identitytdistribute
.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 -> bIdentity
) -> 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
.
Nothing
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
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:
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) = vtmap
((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
.
Nothing
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 # | |
Applicative f => ApplicativeT (Compose f :: (k' -> Type) -> k' -> Type) Source # | |
(forall (f :: k'). ApplicativeB (b f)) => ApplicativeT (Flip b :: (k -> Type) -> k' -> Type) Source # | |
Alternative f => ApplicativeT (Product f :: (Type -> Type) -> Type -> Type) Source # | |
Alternative f => ApplicativeT (Sum f :: (Type -> Type) -> Type -> Type) Source # | |
Utility functions
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 (
or tlift
, tjoin
)(
. In the former:tlift
, tembed
)
tmap
h .tlift
=tlift
. htmap
h .tjoin
=tjoin
.tmap
(tmap
h)tjoin
.tlift
=id
tjoin
. 'tmap tlift' =id
tjoin
.tjoin
=tjoin
.tmap
tjoin
In the latter:
tembed
f .tlift
= ftembed
tlift
=id
tembed
f .tembed
g =tembed
(tembed
f . g)
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 # | |
MonadT (IdentityT :: (k' -> Type) -> k' -> Type) Source # | |
MonadT (Backwards :: (k' -> Type) -> k' -> Type) Source # | |
MonadT (ReaderT r :: (k' -> Type) -> k' -> Type) Source # | |
MonadT (Sum f :: (k' -> Type) -> k' -> Type) Source # | |
Monad f => MonadT (Compose f :: (k' -> Type) -> k' -> Type) Source # | |
MonadT Lift Source # | |
Alternative f => MonadT (Product f :: (Type -> Type) -> Type -> Type) 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 (fInt
) (fString
) | B (fBool
) (fInt
) instanceConstraintsT
T where typeAllT
c T = (cInt
, cString
, cBool
)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 instanceGeneric
(T f a) instanceConstraintsT
T
Nothing
type AllT (c :: k -> Constraint) t :: Constraint 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 #
Instances
GTraversable (n :: k3) (f :: k2 -> Type) (g :: k2 -> Type) (Rec a a :: k1 -> Type) (Rec a a :: k1 -> Type) Source # | |
Defined in Barbies.Generics.Traversable | |
GConstraints n (c :: k3 -> Constraint) (f :: k2) (Rec a' a :: Type -> Type) (Rec a a :: k1 -> Type) (Rec a a :: k1 -> Type) 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 # | |
GFunctor n (f :: k2 -> Type) (g :: k2 -> Type) (Rec x x :: k1 -> Type) (Rec x x :: k1 -> Type) Source # | |
repbi ~ repbb => GBare n (Rec repbi repbi :: k -> Type) (Rec repbb repbb :: k -> Type) Source # | |
type GAll n (c :: k -> Constraint) (Rec a a :: Type -> Type) Source # | |
Defined in Barbies.Generics.Constraints |