distributive-0.6.1: 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 HaskellTrustworthy
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.

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.

Minimal complete definition

distribute | collect

Methods

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

The dual of sequenceA

>>> distribute [(+1),(+2)] 1
[2,3]
distribute = collect id
distribute . distribute = 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 Par1 Source # 
Instance details

Defined in Data.Distributive

Methods

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

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

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

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

Distributive Complex Source # 
Instance details

Defined in Data.Distributive

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 Min Source # 
Instance details

Defined in Data.Distributive

Methods

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

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

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

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

Distributive Max Source # 
Instance details

Defined in Data.Distributive

Methods

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

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

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

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

Distributive First Source # 
Instance details

Defined in Data.Distributive

Methods

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

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

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

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

Distributive Last Source # 
Instance details

Defined in Data.Distributive

Methods

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

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

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

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

Distributive Identity Source # 
Instance details

Defined in Data.Distributive

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 Dual Source # 
Instance details

Defined in Data.Distributive

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 # 
Instance details

Defined in Data.Distributive

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 # 
Instance details

Defined in Data.Distributive

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 (U1 :: Type -> Type) Source # 
Instance details

Defined in Data.Distributive

Methods

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

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

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

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

(Distributive m, Monad m) => Distributive (WrappedMonad m) Source # 
Instance details

Defined in Data.Distributive

Methods

distribute :: Functor f => f (WrappedMonad m a) -> WrappedMonad m (f a) Source #

collect :: Functor f => (a -> WrappedMonad m b) -> f a -> WrappedMonad m (f b) Source #

distributeM :: Monad m0 => m0 (WrappedMonad m a) -> WrappedMonad m (m0 a) Source #

collectM :: Monad m0 => (a -> WrappedMonad m b) -> m0 a -> WrappedMonad m (m0 b) Source #

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

Defined in Data.Distributive

Methods

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

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

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

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

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

Defined in Data.Distributive

Methods

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

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

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

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

Distributive (Tagged t) Source # 
Instance details

Defined in Data.Distributive

Methods

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

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

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

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

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

Defined in Data.Distributive

Methods

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

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

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

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

Distributive g => Distributive (IdentityT g) Source # 
Instance details

Defined in Data.Distributive

Methods

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

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

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

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

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

Defined in Data.Distributive

Methods

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

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

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

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

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

Defined in Data.Distributive

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 a, Distributive b) => Distributive (a :*: b) Source # 
Instance details

Defined in Data.Distributive

Methods

distribute :: Functor f => f ((a :*: b) a0) -> (a :*: b) (f a0) Source #

collect :: Functor f => (a0 -> (a :*: b) b0) -> f a0 -> (a :*: b) (f b0) Source #

distributeM :: Monad m => m ((a :*: b) a0) -> (a :*: b) (m a0) Source #

collectM :: Monad m => (a0 -> (a :*: b) b0) -> m a0 -> (a :*: b) (m b0) Source #

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

Defined in Data.Distributive

Methods

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

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

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

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

Distributive g => Distributive (ReaderT e g) Source # 
Instance details

Defined in Data.Distributive

Methods

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

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

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

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

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

Defined in Data.Distributive

Methods

distribute :: Functor f0 => f0 (M1 i c f a) -> M1 i c f (f0 a) Source #

collect :: Functor f0 => (a -> M1 i c f b) -> f0 a -> M1 i c f (f0 b) Source #

distributeM :: Monad m => m (M1 i c f a) -> M1 i c f (m a) Source #

collectM :: Monad m => (a -> M1 i c f b) -> m a -> M1 i c f (m b) Source #

(Distributive a, Distributive b) => Distributive (a :.: b) Source # 
Instance details

Defined in Data.Distributive

Methods

distribute :: Functor f => f ((a :.: b) a0) -> (a :.: b) (f a0) Source #

collect :: Functor f => (a0 -> (a :.: b) b0) -> f a0 -> (a :.: b) (f b0) Source #

distributeM :: Monad m => m ((a :.: b) a0) -> (a :.: b) (m a0) Source #

collectM :: Monad m => (a0 -> (a :.: b) b0) -> m a0 -> (a :.: b) (m b0) Source #

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

Defined in Data.Distributive

Methods

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

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

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

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

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

The dual of traverse

cotraverse f = fmap f . distribute

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

The dual of mapM

comapM f = fmap f . distributeM