pandora-0.2.1: A box of patterns and paradigms

Safe HaskellSafe
LanguageHaskell2010

Pandora.Pattern.Functor.Distributive

Synopsis

Documentation

class Covariant u => Distributive u where Source #

Let f :: Distributive g => (a -> g b)
When providing a new instance, you should ensure it satisfies the two laws:
* Identity morphism: distribute . distribute ≡ identity
* Interchange collection: collect f ≡ distribute . comap f

Minimal complete definition

(>>-)

Methods

(>>-) :: Covariant t => t a -> (a -> u b) -> (u :. t) := b infixl 5 Source #

Infix and flipped version of collect

collect :: Covariant t => (a -> u b) -> t a -> (u :. t) := b Source #

Prefix version of >>-

distribute :: Covariant t => ((t :. u) := a) -> (u :. t) := a Source #

The dual of sequence

(>>>-) :: (Covariant t, Covariant v) => ((t :. v) := a) -> (a -> u b) -> (u :. (t :. v)) := b infixl 5 Source #

Infix versions of collect with various nesting levels

(>>>>-) :: (Covariant t, Covariant v, Covariant w) => ((t :. (v :. w)) := a) -> (a -> u b) -> (u :. (t :. (v :. w))) := b infixl 5 Source #

(>>>>>-) :: (Covariant t, Covariant v, Covariant w, Covariant j) => ((t :. (v :. (w :. j))) := a) -> (a -> u b) -> (u :. (t :. (v :. (w :. j)))) := b infixl 5 Source #

Instances
Distributive Identity Source # 
Instance details

Defined in Pandora.Paradigm.Basis.Identity

Methods

(>>-) :: Covariant t => t a -> (a -> Identity b) -> (Identity :. t) := b Source #

collect :: Covariant t => (a -> Identity b) -> t a -> (Identity :. t) := b Source #

distribute :: Covariant t => ((t :. Identity) := a) -> (Identity :. t) := a Source #

(>>>-) :: (Covariant t, Covariant v) => ((t :. v) := a) -> (a -> Identity b) -> (Identity :. (t :. v)) := b Source #

(>>>>-) :: (Covariant t, Covariant v, Covariant w) => ((t :. (v :. w)) := a) -> (a -> Identity b) -> (Identity :. (t :. (v :. w))) := b Source #

(>>>>>-) :: (Covariant t, Covariant v, Covariant w, Covariant j) => ((t :. (v :. (w :. j))) := a) -> (a -> Identity b) -> (Identity :. (t :. (v :. (w :. j)))) := b Source #

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

Defined in Pandora.Paradigm.Basis.Proxy

Methods

(>>-) :: Covariant t => t a -> (a -> Proxy b) -> (Proxy :. t) := b Source #

collect :: Covariant t => (a -> Proxy b) -> t a -> (Proxy :. t) := b Source #

distribute :: Covariant t => ((t :. Proxy) := a) -> (Proxy :. t) := a Source #

(>>>-) :: (Covariant t, Covariant v) => ((t :. v) := a) -> (a -> Proxy b) -> (Proxy :. (t :. v)) := b Source #

(>>>>-) :: (Covariant t, Covariant v, Covariant w) => ((t :. (v :. w)) := a) -> (a -> Proxy b) -> (Proxy :. (t :. (v :. w))) := b Source #

(>>>>>-) :: (Covariant t, Covariant v, Covariant w, Covariant j) => ((t :. (v :. (w :. j))) := a) -> (a -> Proxy b) -> (Proxy :. (t :. (v :. (w :. j)))) := b Source #

Distributive t => Distributive (Jack t) Source # 
Instance details

Defined in Pandora.Paradigm.Basis.Jack

Methods

(>>-) :: Covariant t0 => t0 a -> (a -> Jack t b) -> (Jack t :. t0) := b Source #

collect :: Covariant t0 => (a -> Jack t b) -> t0 a -> (Jack t :. t0) := b Source #

distribute :: Covariant t0 => ((t0 :. Jack t) := a) -> (Jack t :. t0) := a Source #

(>>>-) :: (Covariant t0, Covariant v) => ((t0 :. v) := a) -> (a -> Jack t b) -> (Jack t :. (t0 :. v)) := b Source #

(>>>>-) :: (Covariant t0, Covariant v, Covariant w) => ((t0 :. (v :. w)) := a) -> (a -> Jack t b) -> (Jack t :. (t0 :. (v :. w))) := b Source #

(>>>>>-) :: (Covariant t0, Covariant v, Covariant w, Covariant j) => ((t0 :. (v :. (w :. j))) := a) -> (a -> Jack t b) -> (Jack t :. (t0 :. (v :. (w :. j)))) := b Source #

Distributive (Tagged tag) Source # 
Instance details

Defined in Pandora.Paradigm.Basis.Tagged

Methods

(>>-) :: Covariant t => t a -> (a -> Tagged tag b) -> (Tagged tag :. t) := b Source #

collect :: Covariant t => (a -> Tagged tag b) -> t a -> (Tagged tag :. t) := b Source #

distribute :: Covariant t => ((t :. Tagged tag) := a) -> (Tagged tag :. t) := a Source #

(>>>-) :: (Covariant t, Covariant v) => ((t :. v) := a) -> (a -> Tagged tag b) -> (Tagged tag :. (t :. v)) := b Source #

(>>>>-) :: (Covariant t, Covariant v, Covariant w) => ((t :. (v :. w)) := a) -> (a -> Tagged tag b) -> (Tagged tag :. (t :. (v :. w))) := b Source #

(>>>>>-) :: (Covariant t, Covariant v, Covariant w, Covariant j) => ((t :. (v :. (w :. j))) := a) -> (a -> Tagged tag b) -> (Tagged tag :. (t :. (v :. (w :. j)))) := b Source #

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

Defined in Pandora.Pattern.Functor.Distributive

Methods

(>>-) :: Covariant t => t a -> (a -> e -> b) -> ((->) e :. t) := b Source #

collect :: Covariant t => (a -> e -> b) -> t a -> ((->) e :. t) := b Source #

distribute :: Covariant t => ((t :. (->) e) := a) -> ((->) e :. t) := a Source #

(>>>-) :: (Covariant t, Covariant v) => ((t :. v) := a) -> (a -> e -> b) -> ((->) e :. (t :. v)) := b Source #

(>>>>-) :: (Covariant t, Covariant v, Covariant w) => ((t :. (v :. w)) := a) -> (a -> e -> b) -> ((->) e :. (t :. (v :. w))) := b Source #

(>>>>>-) :: (Covariant t, Covariant v, Covariant w, Covariant j) => ((t :. (v :. (w :. j))) := a) -> (a -> e -> b) -> ((->) e :. (t :. (v :. (w :. j)))) := b Source #