adjunctions-4.4: Adjunctions and representable functors

Copyright(c) Edward Kmett 2011-2014
LicenseBSD3
Maintainerekmett@gmail.com
Stabilityexperimental
Safe HaskellTrustworthy
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 #

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

Minimal complete definition

Nothing

Associated Types

type Rep f :: * #

If no definition is provided, this will default to GRep.

Methods

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

fmap f . tabulatetabulate . fmap f

If no definition is provided, this will default to gtabulate.

tabulate :: (Generic1 f, GRep f ~ Rep f, GTabulate (Rep1 f)) => (Rep f -> a) -> f a #

fmap f . tabulatetabulate . fmap f

If no definition is provided, this will default to gtabulate.

index :: f a -> Rep f -> a #

If no definition is provided, this will default to gindex.

index :: (Generic1 f, GRep f ~ Rep f, GIndex (Rep1 f)) => f a -> Rep f -> a #

If no definition is provided, this will default to gindex.

Instances
Representable Par1 # 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep Par1 :: Type #

Methods

tabulate :: (Rep Par1 -> a) -> Par1 a #

index :: Par1 a -> Rep Par1 -> a #

Representable Complex # 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep Complex :: Type #

Methods

tabulate :: (Rep Complex -> a) -> Complex a #

index :: Complex a -> Rep Complex -> a #

Representable Identity # 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep Identity :: Type #

Methods

tabulate :: (Rep Identity -> a) -> Identity a #

index :: Identity a -> Rep Identity -> a #

Representable Dual # 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep Dual :: Type #

Methods

tabulate :: (Rep Dual -> a) -> Dual a #

index :: Dual a -> Rep Dual -> a #

Representable Sum # 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep Sum :: Type #

Methods

tabulate :: (Rep Sum -> a) -> Sum a #

index :: Sum a -> Rep Sum -> a #

Representable Product # 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep Product :: Type #

Methods

tabulate :: (Rep Product -> a) -> Product a #

index :: Product a -> Rep Product -> a #

Representable (U1 :: Type -> Type) # 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep U1 :: Type #

Methods

tabulate :: (Rep U1 -> a) -> U1 a #

index :: U1 a -> Rep U1 -> a #

Representable (Proxy :: Type -> Type) # 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep Proxy :: Type #

Methods

tabulate :: (Rep Proxy -> a) -> Proxy a #

index :: Proxy a -> Rep Proxy -> a #

Representable f => Representable (Cofree f) # 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep (Cofree f) :: Type #

Methods

tabulate :: (Rep (Cofree f) -> a) -> Cofree f a #

index :: Cofree f a -> Rep (Cofree f) -> a #

Representable f => Representable (Co f) # 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep (Co f) :: Type #

Methods

tabulate :: (Rep (Co f) -> a) -> Co f a #

index :: Co f a -> Rep (Co f) -> a #

Representable f => Representable (Rec1 f) # 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep (Rec1 f) :: Type #

Methods

tabulate :: (Rep (Rec1 f) -> a) -> Rec1 f a #

index :: Rec1 f a -> Rep (Rec1 f) -> a #

Representable w => Representable (TracedT s w) # 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep (TracedT s w) :: Type #

Methods

tabulate :: (Rep (TracedT s w) -> a) -> TracedT s w a #

index :: TracedT s w a -> Rep (TracedT s w) -> a #

Representable m => Representable (IdentityT m) # 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep (IdentityT m) :: Type #

Methods

tabulate :: (Rep (IdentityT m) -> a) -> IdentityT m a #

index :: IdentityT m a -> Rep (IdentityT m) -> a #

Representable m => Representable (ReaderT e m) # 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep (ReaderT e m) :: Type #

Methods

tabulate :: (Rep (ReaderT e m) -> a) -> ReaderT e m a #

index :: ReaderT e m a -> Rep (ReaderT e m) -> a #

Representable (Tagged t) # 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep (Tagged t) :: Type #

Methods

tabulate :: (Rep (Tagged t) -> a) -> Tagged t a #

index :: Tagged t a -> Rep (Tagged t) -> a #

Representable f => Representable (Reverse f) # 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep (Reverse f) :: Type #

Methods

tabulate :: (Rep (Reverse f) -> a) -> Reverse f a #

index :: Reverse f a -> Rep (Reverse f) -> a #

Representable f => Representable (Backwards f) # 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep (Backwards f) :: Type #

Methods

tabulate :: (Rep (Backwards f) -> a) -> Backwards f a #

index :: Backwards f a -> Rep (Backwards f) -> a #

(Representable f, Representable m) => Representable (ReaderT f m) # 
Instance details

Defined in Control.Monad.Representable.Reader

Associated Types

type Rep (ReaderT f m) :: Type #

Methods

tabulate :: (Rep (ReaderT f m) -> a) -> ReaderT f m a #

index :: ReaderT f m a -> Rep (ReaderT f m) -> a #

Representable ((->) e :: Type -> Type) # 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep ((->) e) :: Type #

Methods

tabulate :: (Rep ((->) e) -> a) -> e -> a #

index :: (e -> a) -> Rep ((->) e) -> a #

(Representable f, Representable g) => Representable (f :*: g) # 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep (f :*: g) :: Type #

Methods

tabulate :: (Rep (f :*: g) -> a) -> (f :*: g) a #

index :: (f :*: g) a -> Rep (f :*: g) -> a #

(Representable f, Representable g) => Representable (Product f g) # 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep (Product f g) :: Type #

Methods

tabulate :: (Rep (Product f g) -> a) -> Product f g a #

index :: Product f g a -> Rep (Product f g) -> a #

Representable f => Representable (M1 i c f) # 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep (M1 i c f) :: Type #

Methods

tabulate :: (Rep (M1 i c f) -> a) -> M1 i c f a #

index :: M1 i c f a -> Rep (M1 i c f) -> a #

(Representable f, Representable g) => Representable (f :.: g) # 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep (f :.: g) :: Type #

Methods

tabulate :: (Rep (f :.: g) -> a) -> (f :.: g) a #

index :: (f :.: g) a -> Rep (f :.: g) -> a #

(Representable f, Representable g) => Representable (Compose f g) # 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep (Compose f g) :: Type #

Methods

tabulate :: (Rep (Compose f g) -> a) -> Compose f g a #

index :: Compose f g a -> Rep (Compose f g) -> a #

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

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 #

Constructors

Co 

Fields

Instances
ComonadTrans Co # 
Instance details

Defined in Data.Functor.Rep

Methods

lower :: Comonad w => Co w a -> w a #

(Representable f, Rep f ~ a) => MonadReader a (Co f) # 
Instance details

Defined in Data.Functor.Rep

Methods

ask :: Co f a #

local :: (a -> a) -> Co f a0 -> Co f a0 #

reader :: (a -> a0) -> Co f a0 #

Representable f => Monad (Co f) # 
Instance details

Defined in Data.Functor.Rep

Methods

(>>=) :: Co f a -> (a -> Co f b) -> Co f b #

(>>) :: Co f a -> Co f b -> Co f b #

return :: a -> Co f a #

fail :: String -> Co f a #

Functor f => Functor (Co f) # 
Instance details

Defined in Data.Functor.Rep

Methods

fmap :: (a -> b) -> Co f a -> Co f b #

(<$) :: a -> Co f b -> Co f a #

Representable f => Applicative (Co f) # 
Instance details

Defined in Data.Functor.Rep

Methods

pure :: a -> Co f a #

(<*>) :: Co f (a -> b) -> Co f a -> Co f b #

liftA2 :: (a -> b -> c) -> Co f a -> Co f b -> Co f c #

(*>) :: Co f a -> Co f b -> Co f b #

(<*) :: Co f a -> Co f b -> Co f a #

(Representable f, Monoid (Rep f)) => Comonad (Co f) # 
Instance details

Defined in Data.Functor.Rep

Methods

extract :: Co f a -> a #

duplicate :: Co f a -> Co f (Co f a) #

extend :: (Co f a -> b) -> Co f a -> Co f b #

Representable f => Distributive (Co f) # 
Instance details

Defined in Data.Functor.Rep

Methods

distribute :: Functor f0 => f0 (Co f a) -> Co f (f0 a) #

collect :: Functor f0 => (a -> Co f b) -> f0 a -> Co f (f0 b) #

distributeM :: Monad m => m (Co f a) -> Co f (m a) #

collectM :: Monad m => (a -> Co f b) -> m a -> Co f (m b) #

Representable f => Apply (Co f) # 
Instance details

Defined in Data.Functor.Rep

Methods

(<.>) :: Co f (a -> b) -> Co f a -> Co f b #

(.>) :: Co f a -> Co f b -> Co f b #

(<.) :: Co f a -> Co f b -> Co f a #

liftF2 :: (a -> b -> c) -> Co f a -> Co f b -> Co f c #

Representable f => Bind (Co f) # 
Instance details

Defined in Data.Functor.Rep

Methods

(>>-) :: Co f a -> (a -> Co f b) -> Co f b #

join :: Co f (Co f a) -> Co f a #

(Representable f, Semigroup (Rep f)) => Extend (Co f) # 
Instance details

Defined in Data.Functor.Rep

Methods

duplicated :: Co f a -> Co f (Co f a) #

extended :: (Co f a -> b) -> Co f a -> Co f b #

Representable f => Representable (Co f) # 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep (Co f) :: Type #

Methods

tabulate :: (Rep (Co f) -> a) -> Co f a #

index :: Co f a -> Rep (Co f) -> a #

type Rep (Co f) # 
Instance details

Defined in Data.Functor.Rep

type Rep (Co f) = Rep f

Default definitions

Functor

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

Distributive

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

collectRep :: (Representable f, Functor w) => (a -> f b) -> w a -> f (w b) #

Apply/Applicative

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

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

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

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

Bind/Monad

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

MonadFix

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

MonadZip

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

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

MonadReader

askRep :: Representable f => f (Rep f) #

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

Extend

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

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

Comonad

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

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

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

Comonad, with user-specified monoid

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

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

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

WithIndex

imapRep :: Representable r => (Rep r -> a -> a') -> r a -> r a' #

ifoldMapRep :: forall r m a. (Representable r, Foldable r, Monoid m) => (Rep r -> a -> m) -> r a -> m #

itraverseRep :: forall r f a a'. (Representable r, Traversable r, Applicative f) => (Rep r -> a -> f a') -> r a -> f (r a') #

Generics

type GRep f = GRep' (Rep1 f) #

A default implementation of Rep for a datatype that is an instance of Generic1. This is usually composed of Either, tuples, unit tuples, and underlying Rep values. For instance, if you have:

data Foo a = MkFoo a (Bar a) (Baz (Quux a)) deriving (Functor, Generic1)
instance Representable Foo

Then you'll get:

GRep Foo = Either () (Either (WrappedRep Bar) (WrappedRep Baz, WrappedRep Quux))

(See the Haddocks for WrappedRep for an explanation of its purpose.)

gindex :: (Generic1 f, GRep f ~ Rep f, GIndex (Rep1 f)) => f a -> Rep f -> a #

A default implementation of index in terms of GRep.

gtabulate :: (Generic1 f, GRep f ~ Rep f, GTabulate (Rep1 f)) => (Rep f -> a) -> f a #

A default implementation of tabulate in terms of GRep.

newtype WrappedRep f #

On the surface, WrappedRec is a simple wrapper around Rep. But it plays a very important role: it prevents generic Representable instances for recursive types from sending the typechecker into an infinite loop. Consider the following datatype:

data Stream a = a :< Stream a deriving (Functor, Generic1)
instance Representable Stream

With WrappedRep, we have its Rep being:

Rep Stream = Either () (WrappedRep Stream)

If WrappedRep didn't exist, it would be:

Rep Stream = Either () (Either () (Either () ...))

An infinite type! WrappedRep breaks the potentially infinite loop.

Constructors

WrapRep 

Fields