representable-functors-3.0.0.2: Representable functors

Stabilityexperimental
Maintainerekmett@gmail.com
Safe HaskellNone

Data.Functor.Representable

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 (Functor f, Indexable f) => Representable f whereSource

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

 tabulate . index = id
 index . tabulate = id
 tabulate . return f = return f

Methods

tabulate :: (Key f -> a) -> f aSource

 fmap f . tabulate = tabulate . fmap f

Wrapped representable functors

newtype Rep f a Source

Constructors

Rep 

Fields

unrep :: f a
 

Instances

ComonadTrans Rep 
(Monad (Rep f), Representable f, ~ * (Key f) a) => MonadReader a (Rep f) 
Representable f => Monad (Rep f) 
Representable f => Functor (Rep f) 
(Functor (Rep f), Representable f) => Applicative (Rep f) 
(Functor (Rep f), Representable f, Monoid (Key f)) => Comonad (Rep f) 
(Functor (Rep f), Representable f) => Distributive (Rep f) 
(Functor (Rep f), Representable f) => Keyed (Rep f) 
(Functor (Rep f), Representable f) => Zip (Rep f) 
(Keyed (Rep f), Zip (Rep f), Representable f) => ZipWithKey (Rep f) 
(Lookup (Rep f), Indexable f) => Indexable (Rep f) 
Indexable f => Lookup (Rep f) 
(Functor (Rep f), Representable f) => Apply (Rep f) 
(Apply (Rep f), Representable f) => Bind (Rep f) 
(Functor (Rep f), Representable f, Semigroup (Key f)) => Extend (Rep f) 
(Functor (Rep f), Indexable (Rep f), Representable f) => Representable (Rep f) 

Default definitions

Functor

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

Distributive

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

Keyed

mapWithKeyRep :: Representable f => (Key f -> a -> b) -> f a -> f bSource

Apply/Applicative

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

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

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

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

Bind/Monad

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

bindWithKeyRep :: Representable f => f a -> (Key f -> a -> f b) -> f bSource

Zip/ZipWithKey

zipWithRep :: Representable f => (a -> b -> c) -> f a -> f b -> f cSource

zipWithKeyRep :: Representable f => (Key f -> a -> b -> c) -> f a -> f b -> f cSource

MonadReader

localRep :: Representable f => (Key f -> Key f) -> f a -> f aSource

Extend

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

extendedRep :: (Representable f, Semigroup (Key f)) => (f a -> b) -> f a -> f bSource

Comonad

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

extendRep :: (Representable f, Monoid (Key f)) => (f a -> b) -> f a -> f bSource

extractRep :: (Indexable f, Monoid (Key f)) => f a -> aSource