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

Pandora.Paradigm.Inventory.Provision

Documentation

newtype Provision e a Source #

Constructors

Provision (e -> a) 

Instances

Instances details
Monoidal (-->) (-->) (:*:) (:*:) (Provision e) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Provision

Methods

unit :: Proxy (:*:) -> (Unit (:*:) --> a) --> Provision e a Source #

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

Defined in Pandora.Paradigm.Inventory.Provision

Methods

mult :: forall (a :: k) (b :: k). (Provision e a :*: Provision e b) --> Provision e (a :*: b) Source #

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

Defined in Pandora.Paradigm.Inventory.Provision

Methods

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

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

Defined in Pandora.Paradigm.Inventory.Provision

Associated Types

type Primary (Provision e) a Source #

Methods

run :: Provision e a -> Primary (Provision e) a Source #

unite :: Primary (Provision e) a -> Provision e a Source #

(!) :: Provision e a -> Primary (Provision e) a Source #

(||=) :: (Semigroupoid (->), Interpreted (->) u) => (Primary (Provision e) a -> Primary u b) -> Provision e a -> u b Source #

(=||) :: (Semigroupoid (->), Interpreted (->) u) => (Provision e a -> u b) -> Primary (Provision e) a -> Primary u b Source #

(<$||=) :: (Semigroupoid (->), Covariant (->) (->) j, Interpreted (->) u) => (Primary (Provision e) a -> Primary u b) -> (j := Provision e a) -> (j := u b) Source #

(=||$>) :: (Covariant (->) (->) j, Interpreted (->) u) => (Provision e a -> u b) -> (j := Primary (Provision e) a) -> (j := Primary u b) Source #

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

Defined in Pandora.Paradigm.Inventory.Provision

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

Defined in Pandora.Paradigm.Inventory.Provision

Methods

wrap :: forall (u :: Type -> Type) a. Pointable u => Provision e a -> (Provision e :> u) a Source #

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

Defined in Pandora.Paradigm.Inventory.Provision

Methods

(<-|-) :: (a -> b) -> Provision e a -> Provision e b Source #

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

(<-|-|-|-) :: (Covariant (->) (Betwixt (->) (Betwixt (->) (->))) v, Covariant (Betwixt (->) (Betwixt (->) (->))) (Betwixt (Betwixt (->) (->)) (->)) u, Covariant (Betwixt (Betwixt (->) (->)) (->)) (->) (Provision e)) => (a -> b) -> Provision e (u (v a)) -> Provision e (u (v b)) Source #

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

Defined in Pandora.Paradigm.Inventory.Provision

Methods

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

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

Defined in Pandora.Paradigm.Inventory

Methods

(-|) :: (Equipment e a -> b) -> a -> Provision e b Source #

(|-) :: (a -> Provision e b) -> Equipment e a -> b Source #

Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Flip Provision a) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Provision

Methods

(>-|-) :: (a0 -> b) -> Flip Provision a b -> Flip Provision a a0 Source #

type Schematic Monad (Provision e) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Provision

type Schematic Monad (Provision e) = (<:.>) ((->) e :: Type -> Type)
type Primary (Provision e) a Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Provision

type Primary (Provision e) a = e -> a

type Provided e t = Adaptable t (->) (Provision e) Source #

provided :: Provided e t => t e Source #