supply-chain-0.0.1.0: Composable request-response pipelines
Safe HaskellSafe-Inferred
LanguageGHC2021

SupplyChain

Synopsis

Modules

Job type

data Job (up :: Type -> Type) (action :: Type -> Type) product #

Monadic context that supports making requests, performing actions, and returning a single result

Instances

Instances details
Applicative (Job up action) 
Instance details

Defined in SupplyChain.Core.Job

Methods

pure :: a -> Job up action a #

(<*>) :: Job up action (a -> b) -> Job up action a -> Job up action b #

liftA2 :: (a -> b -> c) -> Job up action a -> Job up action b -> Job up action c #

(*>) :: Job up action a -> Job up action b -> Job up action b #

(<*) :: Job up action a -> Job up action b -> Job up action a #

Functor (Job up action) 
Instance details

Defined in SupplyChain.Core.Job

Methods

fmap :: (a -> b) -> Job up action a -> Job up action b #

(<$) :: a -> Job up action b -> Job up action a #

Monad (Job up action) 
Instance details

Defined in SupplyChain.Core.Job

Methods

(>>=) :: Job up action a -> (a -> Job up action b) -> Job up action b #

(>>) :: Job up action a -> Job up action b -> Job up action b #

return :: a -> Job up action a #

Making jobs

order Source #

Arguments

:: up product

Request

-> Job up action product

Job

perform Source #

Arguments

:: action product

Action

-> Job up action product

Job

Running jobs

run Source #

Arguments

:: Monad action 
=> Job (Const Void) action product

Job

-> action product

Action

Run a job in its action context

The job must not make requests, so its upstream interface is Const Void.

eval Source #

Arguments

:: Job (Const Void) (Const Void) product

Job

-> product

Result

Evaluate a job with no context

The job must evokes neither request nor actions, so both its upstream and action contexts are Const Void.

Vendor type

newtype Vendor (up :: Type -> Type) (down :: Type -> Type) (action :: Type -> Type) #

Makes requests, responds to requests, and performs actions

Constructors

Vendor 

Fields

  • handle :: forall product. down product -> Job up action (Referral up down action product)
     

data Referral (up :: Type -> Type) (down :: Type -> Type) (action :: Type -> Type) product #

The conclusion of a vendor's handling of a client request

Constructors

Referral product (Vendor up down action) 

Instances

Instances details
Foldable (Referral up down action) 
Instance details

Defined in SupplyChain.Core.VendorAndReferral

Methods

fold :: Monoid m => Referral up down action m -> m #

foldMap :: Monoid m => (a -> m) -> Referral up down action a -> m #

foldMap' :: Monoid m => (a -> m) -> Referral up down action a -> m #

foldr :: (a -> b -> b) -> b -> Referral up down action a -> b #

foldr' :: (a -> b -> b) -> b -> Referral up down action a -> b #

foldl :: (b -> a -> b) -> b -> Referral up down action a -> b #

foldl' :: (b -> a -> b) -> b -> Referral up down action a -> b #

foldr1 :: (a -> a -> a) -> Referral up down action a -> a #

foldl1 :: (a -> a -> a) -> Referral up down action a -> a #

toList :: Referral up down action a -> [a] #

null :: Referral up down action a -> Bool #

length :: Referral up down action a -> Int #

elem :: Eq a => a -> Referral up down action a -> Bool #

maximum :: Ord a => Referral up down action a -> a #

minimum :: Ord a => Referral up down action a -> a #

sum :: Num a => Referral up down action a -> a #

product :: Num a => Referral up down action a -> a #

Traversable (Referral up down action) 
Instance details

Defined in SupplyChain.Core.VendorAndReferral

Methods

traverse :: Applicative f => (a -> f b) -> Referral up down action a -> f (Referral up down action b) #

sequenceA :: Applicative f => Referral up down action (f a) -> f (Referral up down action a) #

mapM :: Monad m => (a -> m b) -> Referral up down action a -> m (Referral up down action b) #

sequence :: Monad m => Referral up down action (m a) -> m (Referral up down action a) #

Functor (Referral up down action) 
Instance details

Defined in SupplyChain.Core.VendorAndReferral

Methods

fmap :: (a -> b) -> Referral up down action a -> Referral up down action b #

(<$) :: a -> Referral up down action b -> Referral up down action a #

Vendor connection

(>->) Source #

Arguments

:: Vendor up middle action

Upstream

-> Vendor middle down action

Downstream

-> Vendor up down action 

Connect two vendors; the first interprets requests made by the second

Vendor-job connection

(>-) Source #

Arguments

:: Vendor up down action

Upstream

-> Job down action product

Downstream

-> Job up action product 

Modify a job with a vendor that interprets its requests

(>+) Source #

Arguments

:: Vendor up down action

Upstream

-> Job down action product

Downstream

-> Job up action (Referral up down action product) 

Connect a vendor to a job, producing a job which returns both the product and a new version of the vendor.

Use this function instead of (>-) if you need to attach a succession of jobs to one stateful vendor.

Vendor/job conversion

once Source #

Arguments

:: Vendor up (Unit product) action

Vendor

-> Job up action product

Job

loop Source #

Arguments

:: Job up action product

Job

-> Vendor up (Unit product) action

Vendor

loop' Source #

Arguments

:: (forall x. down x -> Job up action x)

Stateless handler

-> Vendor up down action

Vendor

data Unit (a :: k) (b :: k) #

Unit a is a simple interface: It has a single request value (Unit), and a fixed response type (a).

Constructors

a ~ b => Unit