pandora-0.2.3: A box of patterns and paradigms

Safe HaskellSafe
LanguageHaskell2010

Pandora.Pattern.Functor.Distributive

Synopsis

Documentation

class Covariant t => Distributive t 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 u => u a -> (a -> t b) -> (t :. u) := b infixl 5 Source #

Infix and flipped version of collect

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

Prefix version of >>-

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

The dual of sequence

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

Infix versions of collect with various nesting levels

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

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

Instances
Distributive Identity Source # 
Instance details

Defined in Pandora.Paradigm.Basis.Identity

Methods

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

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

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

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

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

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

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

Defined in Pandora.Paradigm.Basis.Proxy

Methods

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

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

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

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

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

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

Distributive (Environment e) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Environment

Methods

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

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

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

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

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

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

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

Defined in Pandora.Paradigm.Basis.Jack

Methods

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

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

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

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

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

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

Distributive (Schematic Monad t u) => Distributive (t :> u) Source # 
Instance details

Defined in Pandora.Paradigm.Controlflow.Joint.Transformer.Monadic

Methods

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

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

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

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

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

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

Distributive (Schematic Comonad t u) => Distributive (t :< u) Source # 
Instance details

Defined in Pandora.Paradigm.Controlflow.Joint.Transformer.Comonadic

Methods

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

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

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

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

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

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

Distributive (Tagged tag) Source # 
Instance details

Defined in Pandora.Paradigm.Basis.Tagged

Methods

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

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

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

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

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

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

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

Defined in Pandora.Pattern.Functor.Distributive

Methods

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

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

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

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

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

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