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

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

Data.Functor.Yoneda

Description

 

Documentation

newtype Yoneda f a Source

Constructors

Yoneda 

Fields

runYoneda :: forall b. (a -> b) -> f b
 

Instances

ComonadTrans Yoneda 
MonadTrans Yoneda 
(Monad (Yoneda m), Functor f, MonadFree f m) => MonadFree f (Yoneda m) 
Monad m => Monad (Yoneda m) 
Functor (Yoneda f) 
(Monad (Yoneda m), MonadFix m) => MonadFix (Yoneda m) 
(Monad (Yoneda m), MonadPlus m) => MonadPlus (Yoneda m) 
(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), Indexable f) => Indexable (Yoneda 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 g), Indexable (Yoneda g), Representable g) => Representable (Yoneda g) 
(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) 
Eq (f a) => Eq (Yoneda f a) 
(Eq (Yoneda f a), Ord (f a)) => Ord (Yoneda f a) 
(Functor f, Read (f a)) => Read (Yoneda f a) 
Show (f a) => Show (Yoneda f a) 

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

maxF :: (Functor f, Ord (f a)) => Yoneda f a -> Yoneda f a -> Yoneda f aSource

minF :: (Functor f, Ord (f a)) => Yoneda f a -> Yoneda f a -> Yoneda f aSource

maxM :: (Monad m, Ord (m a)) => Yoneda m a -> Yoneda m a -> Yoneda m aSource

minM :: (Monad m, Ord (m a)) => Yoneda m a -> Yoneda m a -> Yoneda m aSource