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

Dep.Dynamic

Description

This module provies a dynamic version of a dependency injection environment.

You don't need to declare beforehand what fields exist in the environment, you can simply add them using insertDep.

I might be useful for quick prototyping, or for when there is a big number of components and putting all of them in a conventional record would slow compilation.

A fixEnv-based example:

>>> :{
 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 :: DynamicEnv (Constructor (DynamicEnv Identity IO)) IO
 env = mempty 
     & insertDep @Foo (constructor (\_ -> makeIOFoo))
     & insertDep @Bar (constructor makeBar) 
 envReady :: DynamicEnv Identity IO
 envReady = fixEnv env
:}
>>> :{
 bar (dep envReady) "this is bar"
:}
this is bar

The same example using DepT and component:

>>> :{
 env' :: DynamicEnv Identity (DepT (DynamicEnv Identity) IO)
 env' = mempty 
      & insertDep @Foo (Identity (component (\_ -> makeIOFoo)))
      & insertDep @Bar (Identity (component makeBar))
:}
>>> :{
 runFromDep (pure env') bar "this is bar"
:}
this is bar

Components are found by type. Use Dep.Tagged to disambiguate components of the same type.

It's not checked at compilation time that the dependencies for all components in the environment are also present in the environment. A DynamicEnv exception will be thrown at run time whenever a component tries to find a dependency that doesn't exist:

>>> :{
 badEnv :: DynamicEnv Identity IO
 badEnv = mempty
:}
>>> :{
 bar (dep badEnv) "this is bar"
:}
*** Exception: DepNotFound (Bar IO)

See Checked and SimpleChecked for safer (but still dynamically typed) approaches.

See also InductiveEnv for a strongly-typed variant.

Synopsis

A dynamic environment

data DynamicEnv (h :: Type -> Type) (m :: Type -> Type) Source #

A dependency injection environment for components with effects in the monad m.

The components are wrapped in an Applicative phase h, which will be Identity for "ready-to-be-used" environments.

Instances

Instances details
Phased DynamicEnv Source #

In liftH2, mismatches in key sets are resolved by working with their intersection, like how the Apply instance for Data.Map in the "semigroupoids" package works.

Instance details

Defined in Dep.Dynamic

Methods

traverseH :: forall h f g (m :: Type -> Type). (Applicative f, Typeable f, Typeable g, Typeable h, Typeable m) => (forall x. Typeable x => h x -> f (g x)) -> DynamicEnv h m -> f (DynamicEnv g m) #

liftA2H :: forall a f f' (m :: Type -> Type). (Typeable a, Typeable f, Typeable f', Typeable m) => (forall x. Typeable x => a x -> f x -> f' x) -> DynamicEnv a m -> DynamicEnv f m -> DynamicEnv f' m #

(Typeable r_, Typeable m) => Has r_ m (DynamicEnv Identity m) Source #

DynamicEnv has a Has instance for every possible component. If the component is not actually in the environment, DepNotFound is thrown.

Instance details

Defined in Dep.Dynamic

Methods

dep :: DynamicEnv Identity m -> r_ m #

Monoid (DynamicEnv h m) Source #

mempty is for creating the empty environment.

Instance details

Defined in Dep.Dynamic

Methods

mempty :: DynamicEnv h m #

mappend :: DynamicEnv h m -> DynamicEnv h m -> DynamicEnv h m #

mconcat :: [DynamicEnv h m] -> DynamicEnv h m #

Semigroup (DynamicEnv h m) Source #

In (<>), the entry for the left map is kept.

Instance details

Defined in Dep.Dynamic

Methods

(<>) :: DynamicEnv h m -> DynamicEnv h m -> DynamicEnv h m #

sconcat :: NonEmpty (DynamicEnv h m) -> DynamicEnv h m #

stimes :: Integral b => b -> DynamicEnv h m -> DynamicEnv h m #

insertDep :: forall r_ h m. (Typeable r_, Typeable h, Typeable m) => h (r_ m) -> DynamicEnv h m -> DynamicEnv h m Source #

Insert a record component wrapped in the environment's phase parameter h.

deleteDep :: forall (r_ :: (Type -> Type) -> Type) h m. Typeable r_ => DynamicEnv h m -> DynamicEnv h m Source #

The record type to delete is supplied through a type application.

newtype DepNotFound Source #

Exception thrown by dep when the component we are looking for is not present in the environment.

Constructors

DepNotFound TypeRep 

data SomeDepRep where Source #

The type rep of a parameterizable record type. Similar to SomeTypeRep but for types of a more specific kind.

Constructors

SomeDepRep :: forall (a :: (Type -> Type) -> Type). !(TypeRep a) -> SomeDepRep 

depRep :: forall (r_ :: (Type -> Type) -> Type). Typeable r_ => SomeDepRep Source #

Produce a SomeDepRep by means of a type application.

Re-exports

mempty :: Monoid a => a #

Identity of mappend

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

type family Bare x where ... #

This type family clears newtypes like Compose, Identity and Constant from a composite type, leaving you with a newtypeless nested type as result.

The idea is that it might be easier to construct values of the "bare" version of a composite type, and later coerce them to the newtyped version using fromBare.

This is mainly intended for defining the nested Applicative "phases" of components that live in a Phased environment. It's an alternative to functions like bindPhase and skipPhase.

Equations

Bare (Compose outer inner x) = Bare (outer (Bare (inner x))) 
Bare (Identity x) = x 
Bare (Const x k2) = x 
Bare (Constant x k2) = x 
Bare other = other 

fromBare :: Coercible phases (Bare phases) => Bare phases -> phases #

Convert a value from its bare version to the newtyped one, usually as a step towards inserting it into a Phased environment.

>>> :{
type Phases = IO `Compose` IO `Compose` IO
wrapped :: Phases Int = fromBare $ pure $ pure $ pure 3
:}
>>> :{
type Phases = Constructor Int
wrapped :: Phases Int
wrapped = fromBare $ succ
:}
>>> :{
type Phases = IO `Compose` Constructor Int
wrapped :: Phases Int
wrapped = fromBare $ pure $ succ
:}

toBare :: Coercible phases (Bare phases) => phases -> Bare phases #

Convert from the newtyped value to the bare one. fromBare tends to be more useful.