dep-t-0.6.6.0: Dependency injection for records-of-functions.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Dep.Constructor

Description

This module provides a method for performing dependency injection in Phased environments by means of building fixpoints.

To ease the reader into the concept, here's how we can define the factorial function using only fix from base:

>>> :{
type FactorialDeps = Int -> Int
makeFactorial :: FactorialDeps -> Int -> Int  
makeFactorial deps n = if n == 0 then 1 else n * deps (n-1)
factorial :: Int -> Int
factorial = fix makeFactorial
:}

Looking at it, we can interpret it as a form of dependency injection. In the example, makeFactorial depends on another function of type FactorialDeps for the n > 1 logic. So we build a fixpoint in which the resulting "closed" factorial is passed as the dependency to makeFactorial.

Very good, but what does this have to do with dependency injection in a real application? For real applications, we have a multitude of functions, not only one. Each component has potentially many functions, and there may be many components, with a complex directed acyclic graph of dependencies between components!

This module provides the Constructor applicative. A Phased dependency injection environment parameterized by Constructor is like the set of all component constructors taking part in dependency injection, each one still "open" like makeFactorial, still waiting for its own dependencies.

And when we use the fixEnv function on this "open" environment, we get back a "closed" environment parameterized by Identity, were all the dependencies have been resolved and the components are ready to be used.

Synopsis

Constructor phase

data Constructor (deps :: Type) component Source #

A phase with the effect of "constructing each component by reading its dependencies from a completed environment". It should be the final phase.

The deps type parameter will typically be the "closed" form of the dependency injection environment. That is, the type of environment produced by fixEnv.

Instances

Instances details
Arrow Constructor Source #

Mostly useful for arr, which builds a Constructor out of a regular function.

Instance details

Defined in Dep.Constructor

Methods

arr :: (b -> c) -> Constructor b c #

first :: Constructor b c -> Constructor (b, d) (c, d) #

second :: Constructor b c -> Constructor (d, b) (d, c) #

(***) :: Constructor b c -> Constructor b' c' -> Constructor (b, b') (c, c') #

(&&&) :: Constructor b c -> Constructor b c' -> Constructor b (c, c') #

Category Constructor Source # 
Instance details

Defined in Dep.Constructor

Methods

id :: forall (a :: k). Constructor a a #

(.) :: forall (b :: k) (c :: k) (a :: k). Constructor b c -> Constructor a b -> Constructor a c #

Applicative (Constructor deps) Source #

pure lifts a component that doesn't require any dependencies.

Instance details

Defined in Dep.Constructor

Methods

pure :: a -> Constructor deps a #

(<*>) :: Constructor deps (a -> b) -> Constructor deps a -> Constructor deps b #

liftA2 :: (a -> b -> c) -> Constructor deps a -> Constructor deps b -> Constructor deps c #

(*>) :: Constructor deps a -> Constructor deps b -> Constructor deps b #

(<*) :: Constructor deps a -> Constructor deps b -> Constructor deps a #

Functor (Constructor deps) Source # 
Instance details

Defined in Dep.Constructor

Methods

fmap :: (a -> b) -> Constructor deps a -> Constructor deps b #

(<$) :: a -> Constructor deps b -> Constructor deps a #

constructor :: forall deps component. (deps -> component) -> Constructor deps component Source #

Turn an environment-consuming function into a Constructor that can be slotted into some field of a Phased environment.

Equivalent to arr.

lmapConstructor Source #

Arguments

:: forall deps deps' component. Typeable component 
=> (TypeRep -> deps -> deps')

Modifies the environment, with access to the TypeRep of the component.

-> Constructor deps' component 
-> Constructor deps component 

Change the dependency environment seen by the component.

fixEnv Source #

Arguments

:: (Phased deps_, Typeable deps_, Typeable m) 
=> deps_ (Constructor (deps_ Identity m)) m

Environment where each field is wrapped in a Constructor

-> deps_ Identity m

Fully constructed environment, ready for use.

This is a method of performing dependency injection by building fixpoints.

If we have a environment whose fields are functions that construct each component by searching for its dependencies in a "fully built" version of the environment, we can "tie the knot" to obtain the "fully built" environment. This works as long as there aren't any circular dependencies between components.

Think of it as a version of fix that, instead of "tying" a single function, ties a whole record of them.

We might have arrived as this "ready-to-wire" environment by peeling away successive layers of applicative functor composition using pullPhase, until only the wiring phase remains.

>>> :{
newtype Foo d = Foo {foo :: String -> d ()} deriving Generic
newtype Bar d = Bar {bar :: String -> d ()} deriving Generic
makeIOFoo :: MonadIO m => Foo m
makeIOFoo = Foo (liftIO . putStrLn)
makeBar :: Has Foo m env => env -> Bar m
makeBar (asCall -> call) = Bar (call foo)
type Deps_ = InductiveEnv [Bar,Foo]
type Deps = Deps_ Identity
deps_ :: Deps_ (Constructor (Deps IO)) IO
deps_ = EmptyEnv
    & AddDep @Foo (constructor (\_ -> makeIOFoo))
    & AddDep @Bar (constructor makeBar)
deps :: Deps IO
deps = fixEnv deps_
 :}
>>> :{
 bar (dep deps) "this is bar"
:}
this is bar

Constructor with accumulator

data AccumConstructor (accum :: Type) (deps :: Type) component Source #

A generalized Constructor which produces, in addition to the result value, an accum value which is then aggregated across all components and fed back along with the completed environment.

Like Constructor, AccumConstructor should be the final phase.

Instances

Instances details
Monoid accum => Category (AccumConstructor accum :: Type -> Type -> TYPE LiftedRep) Source # 
Instance details

Defined in Dep.Constructor

Methods

id :: forall (a :: k). AccumConstructor accum a a #

(.) :: forall (b :: k) (c :: k) (a :: k). AccumConstructor accum b c -> AccumConstructor accum a b -> AccumConstructor accum a c #

Monoid accum => Arrow (AccumConstructor accum) Source #

Mostly useful for arr, which builds an AccumConstructor out of a regular function. The produced accumulator will be mempty.

Instance details

Defined in Dep.Constructor

Methods

arr :: (b -> c) -> AccumConstructor accum b c #

first :: AccumConstructor accum b c -> AccumConstructor accum (b, d) (c, d) #

second :: AccumConstructor accum b c -> AccumConstructor accum (d, b) (d, c) #

(***) :: AccumConstructor accum b c -> AccumConstructor accum b' c' -> AccumConstructor accum (b, b') (c, c') #

(&&&) :: AccumConstructor accum b c -> AccumConstructor accum b c' -> AccumConstructor accum b (c, c') #

Monoid accum => Applicative (AccumConstructor accum deps) Source #

pure lifts a component that doesn't require any dependencies. The produced accumulator will be mempty.

Instance details

Defined in Dep.Constructor

Methods

pure :: a -> AccumConstructor accum deps a #

(<*>) :: AccumConstructor accum deps (a -> b) -> AccumConstructor accum deps a -> AccumConstructor accum deps b #

liftA2 :: (a -> b -> c) -> AccumConstructor accum deps a -> AccumConstructor accum deps b -> AccumConstructor accum deps c #

(*>) :: AccumConstructor accum deps a -> AccumConstructor accum deps b -> AccumConstructor accum deps b #

(<*) :: AccumConstructor accum deps a -> AccumConstructor accum deps b -> AccumConstructor accum deps a #

Functor (AccumConstructor accum deps) Source # 
Instance details

Defined in Dep.Constructor

Methods

fmap :: (a -> b) -> AccumConstructor accum deps a -> AccumConstructor accum deps b #

(<$) :: a -> AccumConstructor accum deps b -> AccumConstructor accum deps a #

accumConstructor :: forall accum deps component. (accum -> deps -> (accum, component)) -> AccumConstructor accum deps component Source #

Turn an environment-consuming function into an AccumConstructor that can be slotted into some field of a Phased environment. The function also consumes and produces a monoidal accumulator.

accumConstructor_ Source #

Arguments

:: forall accum deps component. Monoid accum 
=> (accum -> deps -> component)

Consumes the accumulator but doesn't produce it (returns the mempty accumulator.)

-> AccumConstructor accum deps component 

_accumConstructor Source #

Arguments

:: forall accum deps component. (deps -> (accum, component))

Doesn't consume the accumulator but produces it.

-> AccumConstructor accum deps component 

_accumConstructor_ Source #

Arguments

:: forall accum deps component. Monoid accum 
=> (deps -> component)

Neither consumes nor produces the accumulator, like a Constructor.

-> AccumConstructor accum deps component 

Equivalent to arr.

lmapAccumConstructor Source #

Arguments

:: forall accum deps deps' component. Typeable component 
=> (TypeRep -> deps -> deps')

Modifies the environment, with access to the TypeRep of the component.

-> AccumConstructor accum deps' component 
-> AccumConstructor accum deps component 

Change the dependency environment seen by the component.

The accumulator remains unchanged.

fixEnvAccum Source #

Arguments

:: (Phased deps_, Typeable deps_, Typeable m, Monoid accum, Typeable accum) 
=> deps_ (AccumConstructor accum (deps_ Identity m)) m

Environment where each field is wrapped in an AccumConstructor

-> (accum, deps_ Identity m)

Fully constructed accumulator and environment, ready for use.

A generalized fixEnv which threads a monoidal accumulator along with the environment.

Sometimes, we need constructors to produce a monoidal value along with the component. Think for example about some kind of composable startup action for the component.

And on the input side, some constructors need access to the monoidal value accumulated across all components. Think for example about a component which publishes diagnostics coming from all other components.

Control.Arrow re-exports

arr :: Arrow a => (b -> c) -> a b c #

Lift a function to an arrow.