dep-t-dynamic-0.1.1.0: A dynamic environment for dependency injection.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Dep.Checked

Description

NOTE: This module can only be used when your dependencies live in the DepT monad. Use SimpleChecked instead when dependencies are handled in an Constructor phase.

This module provides an environment which tracks the dependencies of components that are added to it, allowing you to check if all dependencies are satisfied before running the program logic.

>>> :{
 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)
 env :: CheckedEnv Identity (DynamicEnv Identity) IO
 env = mempty 
     & checkedDep @Foo @'[]    @'[MonadIO] (Identity (component \_ -> makeIOFoo))
     & checkedDep @Bar @'[Foo] @'[]        (Identity (component makeBar)) 
 envReady :: DynamicEnv Identity (DepT (DynamicEnv Identity) IO)
 envReady = 
   let Right (_, checked) = checkEnv env
    in checked
:}
>>> :{
 runFromDep (pure envReady) bar "this is bar"
:}
this is bar

An example of a failed check:

>>> :{
 badEnv :: CheckedEnv Identity (DynamicEnv Identity) IO
 badEnv = mempty 
     & checkedDep @Bar @'[Foo] @'[] (Identity (component makeBar)) 
:}
>>> :{
 let Left missing = checkEnv badEnv
  in missing
:}
fromList [Foo]
Synopsis

A checked environment

data CheckedEnv h me_ m Source #

A dependency injection environment for components with effects in the monad (DepT me_ m). Parameterized by an Applicative phase h, the environment type constructor me_ used by the DepT transformer, and the type m of the base monad.

Instances

Instances details
Monoid (CheckedEnv h me_ m) Source #

mempty is for creating the empty environment.

Instance details

Defined in Dep.Checked

Methods

mempty :: CheckedEnv h me_ m #

mappend :: CheckedEnv h me_ m -> CheckedEnv h me_ m -> CheckedEnv h me_ m #

mconcat :: [CheckedEnv h me_ m] -> CheckedEnv h me_ m #

Semigroup (CheckedEnv h me_ m) Source #

(<>) might result in over-restrictive dependency graphs, because dependencies for colliding components are kept even as only one of the components is kept.

Instance details

Defined in Dep.Checked

Methods

(<>) :: CheckedEnv h me_ m -> CheckedEnv h me_ m -> CheckedEnv h me_ m #

sconcat :: NonEmpty (CheckedEnv h me_ m) -> CheckedEnv h me_ m #

stimes :: Integral b => b -> CheckedEnv h me_ m -> CheckedEnv h me_ m #

checkedDep Source #

Arguments

:: forall r_ rs mcs h me_ m. (All Typeable rs, All Typeable mcs, Typeable r_, Typeable h, Typeable me_, Typeable m, HasAll rs (DepT me_ m) (me_ (DepT me_ m)), forall s_ z n. Has s_ n (DynamicEnv Identity n) => Has s_ n (me_ n), Monad m, MonadSatisfiesAll mcs (DepT me_ m)) 
=> (forall e_ n. (HasAll rs (DepT e_ n) (e_ (DepT e_ n)), Monad n, MonadSatisfiesAll mcs (DepT e_ n)) => h (r_ (DepT e_ n)))

The wrapped component

-> CheckedEnv h me_ m

The environment in which to insert

-> CheckedEnv h me_ m 

Add a component to a CheckedEnv.

TYPE APPLICATIONS REQUIRED. You must provide three types using TypeApplications:

  • The type r_ of the parameterizable record we want to add to the environment.
  • The type-level list rs of the components the r_ value depends on (might be empty).
  • The type-level list mcs of the constraints the r_ value requires from the base monad (might be empty).

It's impossible to add a component without explicitly listing all its dependencies.

In addition, you must also provide the h (r_ (DepT e_ n)) value, an implementation of the component that comes wrapped in some Applicative. Notice that this value must be sufficiently polymorphic.

The QuantifiedConstraint says that, whatever the environment the DepT uses, if DynamicEnv Identity n has a Has constraint, the DepT environment must also have that constraint. This is trivially true when they are the same type, but may also be true when the DepT environment wraps the DynamicEnv and defines passthrough Has instances.

getUnchecked :: CheckedEnv h me_ m -> (DepGraph, DynamicEnv h (DepT me_ m)) Source #

Extract the underlying DynamicEnv along with the dependency graph, without checking that all dependencies are satisfied.

checkEnv :: CheckedEnv h me_ m -> Either (HashSet SomeDepRep) (DepGraph, DynamicEnv h (DepT me_ m)) Source #

Either fail with a the set of missing dependencies, or succeed and produce the the underlying DynamicEnv along with the dependency graph.

The dependency graph

data DepGraph Source #

A summary graph of dependencies. If the required dependencies are not a subset of the provided ones, the environment is not yet complete.

The graph datatypes come from the algebraic-graphs package.

Constructors

DepGraph 

Fields

Instances

Instances details
Monoid DepGraph Source # 
Instance details

Defined in Dep.Dynamic.Internal

Semigroup DepGraph Source # 
Instance details

Defined in Dep.Dynamic.Internal

data SomeMonadConstraintRep where Source #

The type rep of a constraint over a monad. Similar to SomeTypeRep but for types of a more specific kind.

Constructors

SomeMonadConstraintRep :: forall (a :: (Type -> Type) -> Constraint). !(TypeRep a) -> SomeMonadConstraintRep 

monadConstraintRep :: forall (mc :: (Type -> Type) -> Constraint). Typeable mc => SomeMonadConstraintRep Source #

Produce a SomeMonadConstraintRep by means of a type application.

Re-exports

mempty :: Monoid a => a #

Identity of mappend

>>> "Hello world" <> mempty
"Hello world"