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

Pandora.Pattern.Functor.Distributive

Synopsis

Documentation

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

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

Methods

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

Instances

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

Defined in Pandora.Paradigm.Primary.Functor.Proxy

Methods

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

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

Defined in Pandora.Paradigm.Inventory.Imprint

Methods

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

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

Defined in Pandora.Paradigm.Inventory.Environment

Methods

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

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

Defined in Pandora.Paradigm.Primary.Functor.Tagged

Methods

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

Distributive (Schematic Monad t u) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Distributive (t :> u) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) 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 #

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

Defined in Pandora.Paradigm.Primary.Transformer.Backwards

Methods

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Reverse

Methods

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

Distributive (Schematic Comonad t u) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Distributive (t :< u) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) 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 #

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

Defined in Pandora.Paradigm.Primary.Algebraic.Exponential

Methods

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