Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Synopsis
- data Job (up :: Type -> Type) (action :: Type -> Type) product
- order :: up product -> Job up action product
- perform :: action product -> Job up action product
- run :: Monad action => Job (Const Void) action product -> action product
- eval :: Job (Const Void) (Const Void) product -> product
- newtype Vendor (up :: Type -> Type) (down :: Type -> Type) (action :: Type -> Type) = Vendor {}
- data Referral (up :: Type -> Type) (down :: Type -> Type) (action :: Type -> Type) product = Referral product (Vendor up down action)
- (>->) :: Vendor up middle action -> Vendor middle down action -> Vendor up down action
- (>-) :: Vendor up down action -> Job down action product -> Job up action product
- (>+) :: Vendor up down action -> Job down action product -> Job up action (Referral up down action product)
- once :: Vendor up (Unit product) action -> Job up action product
- loop :: Job up action product -> Vendor up (Unit product) action
- loop' :: (forall x. down x -> Job up action x) -> Vendor up down action
- data Unit (a :: k) (b :: k) = a ~ b => Unit
Modules
- SupplyChain.Alter — Functions for modifying requests and actions
- SupplyChain.Effect — An effect is either request or perform
- SupplyChain.Job — A job makes requests, performs actions, and returns
- SupplyChain.JobAndVendor — Job + vendor
- SupplyChain.Referral — A referral consists of a product and a new vendor
- SupplyChain.Unit — Unit is a simple interface with one request and a fixed response type
- SupplyChain.Vendor — A vendor responds to requests, makes requests, and performs actions
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
Applicative (Job up action) | |
Defined in SupplyChain.Core.Job 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) | |
Monad (Job up action) | |
Making jobs
Running jobs
Run a job in its action context
The job must not make requests, so its upstream interface
is Const Void
.
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
data Referral (up :: Type -> Type) (down :: Type -> Type) (action :: Type -> Type) product #
The conclusion of a vendor's handling of a client request
Instances
Foldable (Referral up down action) | |
Defined in SupplyChain.Core.VendorAndReferral 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 # | |
Traversable (Referral up down action) | |
Defined in SupplyChain.Core.VendorAndReferral 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) | |
Vendor connection
Connect two vendors; the first interprets requests made by the second
Vendor-job connection
Modify a job with a vendor that interprets its requests
:: 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.