adjunctions-4.4.2: Adjunctions and representable functors
Copyright (c) Edward Kmett 2011-2014
License BSD3
Maintainer ekmett@gmail.com
Stability experimental
Safe Haskell Trustworthy
Language Haskell2010

Data.Functor.Rep

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

Minimal complete definition

Nothing

Associated Types

type Rep f :: * Source #

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

type Rep f = GRep f

Methods

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

fmap f . tabulatetabulate . fmap f

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

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

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

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

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

Instances

Instances details
Representable Par1 Source #
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep Par1 Source #

Representable Complex Source #
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep Complex Source #

Representable Identity Source #
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep Identity Source #

Representable Dual Source #
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep Dual Source #

Representable Sum Source #
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep Sum Source #

Representable Product Source #
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep Product Source #

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

Defined in Data.Functor.Rep

Associated Types

type Rep U1 Source #

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

Defined in Data.Functor.Rep

Associated Types

type Rep Proxy Source #

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

Defined in Data.Functor.Rep

Associated Types

type Rep ( Cofree f) Source #

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

Defined in Data.Functor.Rep

Associated Types

type Rep ( Co f) Source #

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

Defined in Data.Functor.Rep

Associated Types

type Rep ( Rec1 f) Source #

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

Defined in Data.Functor.Rep

Associated Types

type Rep ( TracedT s w) Source #

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

Defined in Data.Functor.Rep

Associated Types

type Rep ( IdentityT m) Source #

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

Defined in Data.Functor.Rep

Associated Types

type Rep ( ReaderT e m) Source #

Representable ( Tagged t) Source #
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep ( Tagged t) Source #

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

Defined in Data.Functor.Rep

Associated Types

type Rep ( Reverse f) Source #

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

Defined in Data.Functor.Rep

Associated Types

type Rep ( Backwards f) Source #

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

Defined in Control.Monad.Representable.Reader

Associated Types

type Rep ( ReaderT f m) Source #

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

Defined in Data.Functor.Rep

Associated Types

type Rep ((->) e) Source #

Methods

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

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

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

Defined in Data.Functor.Rep

Associated Types

type Rep (f :*: g) Source #

Methods

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

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

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

Defined in Data.Functor.Rep

Associated Types

type Rep ( Product f g) Source #

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

Defined in Data.Functor.Rep

Associated Types

type Rep ( M1 i c f) Source #

Methods

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

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

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

Defined in Data.Functor.Rep

Associated Types

type Rep (f :.: g) Source #

Methods

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

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

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

Defined in Data.Functor.Rep

Associated Types

type Rep ( Compose f g) 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

Instances

Instances details
ComonadTrans Co Source #
Instance details

Defined in Data.Functor.Rep

Methods

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

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

Defined in Data.Functor.Rep

Methods

ask :: Co f a Source #

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

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

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

Defined in Data.Functor.Rep

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

Defined in Data.Functor.Rep

Methods

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

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

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

Defined in Data.Functor.Rep

Methods

pure :: a -> Co f a Source #

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

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

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

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

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

Defined in Data.Functor.Rep

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

Defined in Data.Functor.Rep

Methods

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

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

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

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

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

Defined in Data.Functor.Rep

Methods

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

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

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

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

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

Defined in Data.Functor.Rep

Methods

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

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

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

Defined in Data.Functor.Rep

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

Defined in Data.Functor.Rep

Associated Types

type Rep ( Co f) Source #

type Rep ( Co f) Source #
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 Source #

Distributive

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

Apply/Applicative

apRep :: Representable f => f (a -> b) -> f a -> f b 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

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

Extend

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

Comonad

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

Comonad, with user-specified monoid

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

WithIndex

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

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

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

Generics

type GRep f = GRep' ( Rep1 f) Source #

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 Source #

A default implementation of index in terms of GRep .

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

A default implementation of tabulate in terms of GRep .

newtype WrappedRep f Source #

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