adjunctions-4.2.2: Adjunctions and representable functors

Copyright(c) Edward Kmett 2011-2014
LicenseBSD3
Maintainerekmett@gmail.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell98

Data.Functor.Rep

Contents

Description

Representable endofunctors over the category of Haskell types are isomorphic to the reader monad and so inherit a very large number of properties for free.

Synopsis

Representable Functors

class Distributive f => Representable f where Source

A Functor f is Representable if tabulate and index witness an isomorphism to (->) x.

Every Distributive Functor is actually Representable.

Every Representable Functor from Hask to Hask is a right adjoint.

tabulate . index  ≡ id
index . tabulate  ≡ id
tabulate . returnreturn

Associated Types

type Rep f :: * Source

Methods

tabulate :: (Rep f -> a) -> f a Source

fmap f . tabulatetabulate . fmap f

index :: f a -> Rep f -> a Source

tabulated :: (Representable f, Representable g, Profunctor p, Functor h) => p (f a) (h (g b)) -> p (Rep f -> a) (h (Rep g -> b)) Source

tabulate and index form two halves of an isomorphism.

This can be used with the combinators from the lens package.

tabulated :: Representable f => Iso' (Rep f -> a) (f a)

Wrapped representable functors

newtype Co f a Source

Constructors

Co 

Fields

unCo :: f a
 

Instances

ComonadTrans Co 
(Representable f, (~) * (Rep f) a) => MonadReader a (Co f) 
Representable f => Monad (Co f) 
Functor f => Functor (Co f) 
Representable f => Applicative (Co f) 
(Representable f, Monoid (Rep f)) => Comonad (Co f) 
Representable f => Distributive (Co f) 
Representable f => Apply (Co f) 
Representable f => Bind (Co f) 
(Representable f, Semigroup (Rep f)) => Extend (Co f) 
Representable f => Representable (Co f) 
type Rep (Co f) = Rep f 

Default definitions

Functor

fmapRep :: Representable f => (a -> b) -> f a -> f b Source

Distributive

distributeRep :: (Representable f, Functor w) => w (f a) -> f (w a) Source

Apply/Applicative

apRep :: Representable f => f (a -> b) -> f a -> f b Source

pureRep :: Representable f => a -> f a Source

liftR2 :: Representable f => (a -> b -> c) -> f a -> f b -> f c Source

liftR3 :: Representable f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d Source

Bind/Monad

bindRep :: Representable f => f a -> (a -> f b) -> f b Source

MonadFix

mfixRep :: Representable f => (a -> f a) -> f a Source

MonadZip

mzipRep :: Representable f => f a -> f b -> f (a, b) Source

mzipWithRep :: Representable f => (a -> b -> c) -> f a -> f b -> f c Source

MonadReader

localRep :: Representable f => (Rep f -> Rep f) -> f a -> f a Source

Extend

duplicatedRep :: (Representable f, Semigroup (Rep f)) => f a -> f (f a) Source

extendedRep :: (Representable f, Semigroup (Rep f)) => (f a -> b) -> f a -> f b Source

Comonad

duplicateRep :: (Representable f, Monoid (Rep f)) => f a -> f (f a) Source

extendRep :: (Representable f, Monoid (Rep f)) => (f a -> b) -> f a -> f b Source

extractRep :: (Representable f, Monoid (Rep f)) => f a -> a Source

Comonad, with user-specified monoid

duplicateRepBy :: Representable f => (Rep f -> Rep f -> Rep f) -> f a -> f (f a) Source

extendRepBy :: Representable f => (Rep f -> Rep f -> Rep f) -> (f a -> b) -> f a -> f b Source

extractRepBy :: Representable f => Rep f -> f a -> a Source