distributive-0.5.0.2: Distributive functors -- Dual to Traversable

Copyright(C) 2011-2016 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Data.Distributive

Description

 

Synopsis

Documentation

class Functor g => Distributive g where Source

This is the categorical dual of Traversable.

Due to the lack of non-trivial comonoids in Haskell, we can restrict ourselves to requiring a Functor rather than some Coapplicative class. Categorically every Distributive functor is actually a right adjoint, and so it must be Representable endofunctor and preserve all limits. This is a fancy way of saying it isomorphic to `(->) x` for some x.

Minimal complete definition: distribute or collect

To be distributable a container will need to have a way to consistently zip a potentially infinite number of copies of itself. This effectively means that the holes in all values of that type, must have the same cardinality, fixed sized vectors, infinite streams, functions, etc. and no extra information to try to merge together.

Methods

distribute :: Functor f => f (g a) -> g (f a) Source

The dual of sequenceA

>>> distribute [(+1),(+2)] 1
[2,3]
distribute = collect id

collect :: Functor f => (a -> g b) -> f a -> g (f b) Source

distributeM :: Monad m => m (g a) -> g (m a) Source

collectM :: Monad m => (a -> g b) -> m a -> g (m b) Source

Instances

Distributive Identity Source 

Methods

distribute :: Functor f => f (Identity a) -> Identity (f a) Source

collect :: Functor f => (a -> Identity b) -> f a -> Identity (f b) Source

distributeM :: Monad m => m (Identity a) -> Identity (m a) Source

collectM :: Monad m => (a -> Identity b) -> m a -> Identity (m b) Source

Distributive Complex Source 

Methods

distribute :: Functor f => f (Complex a) -> Complex (f a) Source

collect :: Functor f => (a -> Complex b) -> f a -> Complex (f b) Source

distributeM :: Monad m => m (Complex a) -> Complex (m a) Source

collectM :: Monad m => (a -> Complex b) -> m a -> Complex (m b) Source

Distributive Dual Source 

Methods

distribute :: Functor f => f (Dual a) -> Dual (f a) Source

collect :: Functor f => (a -> Dual b) -> f a -> Dual (f b) Source

distributeM :: Monad m => m (Dual a) -> Dual (m a) Source

collectM :: Monad m => (a -> Dual b) -> m a -> Dual (m b) Source

Distributive Sum Source 

Methods

distribute :: Functor f => f (Sum a) -> Sum (f a) Source

collect :: Functor f => (a -> Sum b) -> f a -> Sum (f b) Source

distributeM :: Monad m => m (Sum a) -> Sum (m a) Source

collectM :: Monad m => (a -> Sum b) -> m a -> Sum (m b) Source

Distributive Product Source 

Methods

distribute :: Functor f => f (Product a) -> Product (f a) Source

collect :: Functor f => (a -> Product b) -> f a -> Product (f b) Source

distributeM :: Monad m => m (Product a) -> Product (m a) Source

collectM :: Monad m => (a -> Product b) -> m a -> Product (m b) Source

Distributive ((->) e) Source 

Methods

distribute :: Functor f => f (e -> a) -> e -> f a Source

collect :: Functor f => (a -> e -> b) -> f a -> e -> f b Source

distributeM :: Monad m => m (e -> a) -> e -> m a Source

collectM :: Monad m => (a -> e -> b) -> m a -> e -> m b Source

Distributive (Proxy (TYPE Lifted)) Source 

Methods

distribute :: Functor f => f (Proxy (TYPE Lifted) a) -> Proxy (TYPE Lifted) (f a) Source

collect :: Functor f => (a -> Proxy (TYPE Lifted) b) -> f a -> Proxy (TYPE Lifted) (f b) Source

distributeM :: Monad m => m (Proxy (TYPE Lifted) a) -> Proxy (TYPE Lifted) (m a) Source

collectM :: Monad m => (a -> Proxy (TYPE Lifted) b) -> m a -> Proxy (TYPE Lifted) (m b) Source

Distributive f => Distributive (Reverse (TYPE Lifted) f) Source 

Methods

distribute :: Functor f => f (Reverse (TYPE Lifted) f a) -> Reverse (TYPE Lifted) f (f a) Source

collect :: Functor f => (a -> Reverse (TYPE Lifted) f b) -> f a -> Reverse (TYPE Lifted) f (f b) Source

distributeM :: Monad m => m (Reverse (TYPE Lifted) f a) -> Reverse (TYPE Lifted) f (m a) Source

collectM :: Monad m => (a -> Reverse (TYPE Lifted) f b) -> m a -> Reverse (TYPE Lifted) f (m b) Source

Distributive f => Distributive (Backwards (TYPE Lifted) f) Source 

Methods

distribute :: Functor f => f (Backwards (TYPE Lifted) f a) -> Backwards (TYPE Lifted) f (f a) Source

collect :: Functor f => (a -> Backwards (TYPE Lifted) f b) -> f a -> Backwards (TYPE Lifted) f (f b) Source

distributeM :: Monad m => m (Backwards (TYPE Lifted) f a) -> Backwards (TYPE Lifted) f (m a) Source

collectM :: Monad m => (a -> Backwards (TYPE Lifted) f b) -> m a -> Backwards (TYPE Lifted) f (m b) Source

Distributive g => Distributive (IdentityT (TYPE Lifted) g) Source 

Methods

distribute :: Functor f => f (IdentityT (TYPE Lifted) g a) -> IdentityT (TYPE Lifted) g (f a) Source

collect :: Functor f => (a -> IdentityT (TYPE Lifted) g b) -> f a -> IdentityT (TYPE Lifted) g (f b) Source

distributeM :: Monad m => m (IdentityT (TYPE Lifted) g a) -> IdentityT (TYPE Lifted) g (m a) Source

collectM :: Monad m => (a -> IdentityT (TYPE Lifted) g b) -> m a -> IdentityT (TYPE Lifted) g (m b) Source

Distributive (Tagged (TYPE Lifted) t) Source 

Methods

distribute :: Functor f => f (Tagged (TYPE Lifted) t a) -> Tagged (TYPE Lifted) t (f a) Source

collect :: Functor f => (a -> Tagged (TYPE Lifted) t b) -> f a -> Tagged (TYPE Lifted) t (f b) Source

distributeM :: Monad m => m (Tagged (TYPE Lifted) t a) -> Tagged (TYPE Lifted) t (m a) Source

collectM :: Monad m => (a -> Tagged (TYPE Lifted) t b) -> m a -> Tagged (TYPE Lifted) t (m b) Source

(Distributive f, Distributive g) => Distributive (Product (TYPE Lifted) f g) Source 

Methods

distribute :: Functor f => f (Product (TYPE Lifted) f g a) -> Product (TYPE Lifted) f g (f a) Source

collect :: Functor f => (a -> Product (TYPE Lifted) f g b) -> f a -> Product (TYPE Lifted) f g (f b) Source

distributeM :: Monad m => m (Product (TYPE Lifted) f g a) -> Product (TYPE Lifted) f g (m a) Source

collectM :: Monad m => (a -> Product (TYPE Lifted) f g b) -> m a -> Product (TYPE Lifted) f g (m b) Source

Distributive g => Distributive (ReaderT (TYPE Lifted) e g) Source 

Methods

distribute :: Functor f => f (ReaderT (TYPE Lifted) e g a) -> ReaderT (TYPE Lifted) e g (f a) Source

collect :: Functor f => (a -> ReaderT (TYPE Lifted) e g b) -> f a -> ReaderT (TYPE Lifted) e g (f b) Source

distributeM :: Monad m => m (ReaderT (TYPE Lifted) e g a) -> ReaderT (TYPE Lifted) e g (m a) Source

collectM :: Monad m => (a -> ReaderT (TYPE Lifted) e g b) -> m a -> ReaderT (TYPE Lifted) e g (m b) Source

(Distributive f, Distributive g) => Distributive (Compose (TYPE Lifted) (TYPE Lifted) f g) Source 

Methods

distribute :: Functor f => f (Compose (TYPE Lifted) (TYPE Lifted) f g a) -> Compose (TYPE Lifted) (TYPE Lifted) f g (f a) Source

collect :: Functor f => (a -> Compose (TYPE Lifted) (TYPE Lifted) f g b) -> f a -> Compose (TYPE Lifted) (TYPE Lifted) f g (f b) Source

distributeM :: Monad m => m (Compose (TYPE Lifted) (TYPE Lifted) f g a) -> Compose (TYPE Lifted) (TYPE Lifted) f g (m a) Source

collectM :: Monad m => (a -> Compose (TYPE Lifted) (TYPE Lifted) f g b) -> m a -> Compose (TYPE Lifted) (TYPE Lifted) f g (m b) Source

cotraverse :: (Functor f, Distributive g) => (f a -> b) -> f (g a) -> g b Source

The dual of traverse

cotraverse f = fmap f . distribute

comapM :: (Monad m, Distributive g) => (m a -> b) -> m (g a) -> g b Source

The dual of mapM

comapM f = fmap f . distributeM