pandora-0.5.4: A box of patterns and paradigms
Safe HaskellSafe-Inferred
LanguageHaskell2010

Pandora.Pattern.Functor.Distributive

Synopsis

Documentation

class Covariant source target t => Distributive source target t where Source #

Let f :: Distributive g => (a -> g b)
When providing a new instance, you should ensure it satisfies:
* Exactly morphism: (identity -<<) . (identity -<<) ≡ identity
* Interchange collection: (f -<<) ≡ (identity -<<) . (f <-|-)

Minimal complete definition

(-<<)

Methods

(-<<) :: Covariant source target u => source a (t b) -> target (u a) (t (u b)) infixl 7 Source #

(--<<) :: Covariant source target u => source a (t b) -> target (u a) (t (u b)) infixl 6 Source #

(---<<) :: Covariant source target u => source a (t b) -> target (u a) (t (u b)) infixl 5 Source #

(----<<) :: Covariant source target u => source a (t b) -> target (u a) (t (u b)) infixl 4 Source #

(-----<<) :: Covariant source target u => source a (t b) -> target (u a) (t (u b)) infixl 3 Source #

(------<<) :: Covariant source target u => source a (t b) -> target (u a) (t (u b)) infixl 2 Source #

(-------<<) :: Covariant source target u => source a (t b) -> target (u a) (t (u b)) infixl 1 Source #

Instances

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

Defined in Pandora.Paradigm.Primary.Functor.Proxy

Methods

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

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

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

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

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

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

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

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

Defined in Pandora.Paradigm.Inventory.Some.Provision

Methods

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

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

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

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

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

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

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

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

Defined in Pandora.Paradigm.Inventory.Some.Imprint

Methods

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

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

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

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

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

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

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

Distributive ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Tagged tag) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Tagged

Methods

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

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

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

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

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

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

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

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

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

Methods

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

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

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

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

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

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

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

Distributive ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Distributive ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Backwards t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Backwards

Methods

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

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

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

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

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

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

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

Distributive ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Distributive ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Reverse t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Reverse

Methods

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

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

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

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

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

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

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

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

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

Methods

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

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

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

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

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

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

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

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

Defined in Pandora.Paradigm.Algebraic.Exponential

Methods

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

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

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

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

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

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

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