kan-extensions-3.1.0.1: Kan extensions, the Yoneda lemma, and (co)density (co)monads

PortabilityGADTs, MPTCs, fundeps
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellNone

Data.Functor.Yoneda.Contravariant

Description

 

Synopsis

Documentation

data Yoneda f a whereSource

The contravariant Yoneda lemma applied to a covariant functor

Constructors

Yoneda :: (b -> a) -> f b -> Yoneda f a 

Instances

ComonadTrans Yoneda 
MonadTrans Yoneda 
Monad m => Monad (Yoneda m) 
Functor (Yoneda f) 
(Monad (Yoneda f), MonadFix f) => MonadFix (Yoneda f) 
(Monad (Yoneda f), MonadPlus f) => MonadPlus (Yoneda f) 
(Functor (Yoneda f), Applicative f) => Applicative (Yoneda f) 
Foldable f => Foldable (Yoneda f) 
(Functor (Yoneda f), Foldable (Yoneda f), Traversable f) => Traversable (Yoneda f) 
(Applicative (Yoneda f), Alternative f) => Alternative (Yoneda f) 
(Functor (Yoneda w), Comonad w) => Comonad (Yoneda w) 
(Functor (Yoneda f), Distributive f) => Distributive (Yoneda f) 
(Functor (Yoneda f), Keyed f) => Keyed (Yoneda f) 
(Functor (Yoneda f), Zip f) => Zip (Yoneda f) 
(Keyed (Yoneda f), Zip (Yoneda f), ZipWithKey f) => ZipWithKey (Yoneda f) 
(Lookup (Yoneda f), Functor f, Indexable f) => Indexable (Yoneda f) 
(Functor f, Lookup f) => Lookup (Yoneda f) 
(Foldable (Yoneda f), FoldableWithKey f) => FoldableWithKey (Yoneda f) 
(Foldable1 (Yoneda f), FoldableWithKey (Yoneda f), FoldableWithKey1 f) => FoldableWithKey1 (Yoneda f) 
(Keyed (Yoneda f), FoldableWithKey (Yoneda f), Traversable (Yoneda f), TraversableWithKey f) => TraversableWithKey (Yoneda f) 
(Traversable1 (Yoneda f), FoldableWithKey1 (Yoneda f), TraversableWithKey (Yoneda f), TraversableWithKey1 f) => TraversableWithKey1 (Yoneda f) 
(Functor (Yoneda f), Indexable (Yoneda f), Representable f) => Representable (Yoneda f) 
(Alt (Yoneda f), Plus f) => Plus (Yoneda f) 
(Functor (Yoneda f), Alt f) => Alt (Yoneda f) 
(Foldable1 (Yoneda f), Traversable (Yoneda f), Traversable1 f) => Traversable1 (Yoneda f) 
(Foldable (Yoneda f), Foldable1 f) => Foldable1 (Yoneda f) 
(Functor (Yoneda f), Apply f) => Apply (Yoneda f) 
(Apply (Yoneda m), Bind m) => Bind (Yoneda m) 
(Functor (Yoneda w), Extend w) => Extend (Yoneda w) 
(Functor (Yoneda f), Representable (Yoneda g), Adjunction f g) => Adjunction (Yoneda f) (Yoneda g) 
(Functor f, Eq (f a)) => Eq (Yoneda f a) 
(Eq (Yoneda f a), Functor f, Ord (f a)) => Ord (Yoneda f a) 
(Functor f, Read (f a)) => Read (Yoneda f a) 
(Functor f, Show (f a)) => Show (Yoneda f a) 

liftYoneda :: f a -> Yoneda f aSource

lowerYoneda :: Functor f => Yoneda f a -> f aSource

lowerM :: Monad f => Yoneda f a -> f aSource