dep-t-dynamic-0.1.0.0: A dynamic environment for dependency injection.
Safe HaskellNone
LanguageHaskell2010

Dep.SimpleChecked

Description

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

An example of a failed check:

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

A checked environment

data CheckedEnv phases m Source #

A dependency injection environment for components with effects in the monad m. Parameterized by Applicative phases, and the type m of the effect monad.

Instances

Instances details
Semigroup (CheckedEnv phases 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.SimpleChecked

Methods

(<>) :: CheckedEnv phases m -> CheckedEnv phases m -> CheckedEnv phases m #

sconcat :: NonEmpty (CheckedEnv phases m) -> CheckedEnv phases m #

stimes :: Integral b => b -> CheckedEnv phases m -> CheckedEnv phases m #

Monoid (CheckedEnv phases m) Source #

mempty is for creating the empty environment.

Instance details

Defined in Dep.SimpleChecked

Methods

mempty :: CheckedEnv phases m #

mappend :: CheckedEnv phases m -> CheckedEnv phases m -> CheckedEnv phases m #

mconcat :: [CheckedEnv phases m] -> CheckedEnv phases m #

checkedDep Source #

Arguments

:: forall r_ rs mcs phases m. (All Typeable rs, All Typeable mcs, Typeable r_, Typeable phases, Typeable m, HasAll rs m (DynamicEnv Identity m), Monad m, MonadSatisfiesAll mcs m) 
=> (forall e n. (HasAll rs n e, Monad m, MonadSatisfiesAll mcs n) => (phases `Compose` Constructor e) (r_ n))

The wrapped component

-> CheckedEnv phases m

The environment in which to insert

-> CheckedEnv phases 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 (phases Compose Constructor e) value, an implementation of the component that comes wrapped in some Applicative. Notice that this value must be sufficiently polymorphic.

getUnchecked :: CheckedEnv phases m -> (DepGraph, DynamicEnv (phases `Compose` Constructor (DynamicEnv Identity m)) m) Source #

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

checkEnv :: CheckedEnv phases m -> Either (HashSet SomeDepRep) (DepGraph, DynamicEnv (phases `Compose` Constructor (DynamicEnv Identity m)) 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
Semigroup DepGraph Source # 
Instance details

Defined in Dep.Dynamic.Internal

Monoid 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"