dep-t-0.6.1.0: Dependency injection for records-of-functions.
Safe HaskellNone
LanguageHaskell2010

Control.Monad.Dep.Class

Description

This module provides definitions that let us translate record-of-functions code of the form:

>>> :{
 type HasLogger :: (Type -> Type) -> Type -> Constraint
 class HasLogger d e | e -> d where
   logger :: e -> String -> d ()
 type HasRepository :: (Type -> Type) -> Type -> Constraint
 class HasRepository d e | e -> d where
   repository :: e -> Int -> d ()
 mkControllerIO :: (HasLogger IO e, HasRepository IO e) => Int -> ReaderT e IO String
 mkControllerIO x = do
   e <- ask
   liftIO $ logger e "I'm going to insert in the db!"
   liftIO $ repository e x
   return "view"
:}

into the more polymorphic form:

>>> :{
 mkController :: MonadDep [HasLogger, HasRepository] d e m => Int -> m String
 mkController x = do
   e <- ask
   liftD $ logger e "I'm going to insert in the db!"
   liftD $ repository e x
   return "view"
:}

which can also be given the equivalent signature:

>>> :{
   mkController' :: (HasLogger d e, HasRepository d e, LiftDep d m, MonadReader e m) => Int -> m String
   mkController' = mkController
:}   

The new code can be used as a drop-in replacement of the old one:

>>> :{
   mkControllerIO' :: (HasLogger IO e, HasRepository IO e) => Int -> ReaderT e IO String
   mkControllerIO' = mkController'
:}

Notice that in the new code effects taken from the environment record are lifted using liftD instead of lift or liftIO.

Synopsis

Reader-like monads carrying dependencies in their environment

type family MonadDep (dependencies :: [(Type -> Type) -> Type -> Constraint]) (d :: Type -> Type) (e :: Type) (m :: Type -> Type) where ... Source #

MonadDep is not its own typeclass, but MonadReader plus some supplementary constraints.

A MonadDep dependencies d e m is a MonadReader e m where the environment e provides some dependencies with effects in the monad d, additionally requiring that the effects can be lifted back to the monad m by using liftD.

The dependencies are specified as a type-level list of two-parameter HasX typeclasses. Those typeclasses should expect the effect monad d as its first parameter.

Writing code polymorphic over MonadDep lets us execute it in both ReaderT and DepT contexts.

Equations

MonadDep '[] d e m = (LiftDep d m, MonadReader e m) 
MonadDep (dependency ': dependencies) d e m = (dependency d e, MonadDep dependencies d e m) 

Lifting effects from dependencies

class Monad d => LiftDep d m where Source #

Auxiliary typeclass for monads that can be lifted to other monads.

Its intended use is lifting monadic actions found in some reader-like environment.

Note: The RIO monad from rio could be given a LiftDept IO RIO instance; it's not done here to avoid increasing the dependency footprint.

Methods

liftD :: d x -> m x Source #

Instances

Instances details
Monad m => LiftDep m (ReaderT e m) Source #

The simplest case: we can d-lift the base monad sitting just below a ReaderT.

(Perhaps this could be extended to any monad transformer, but let's leave it simple for now.)

Instance details

Defined in Control.Monad.Dep.Class

Methods

liftD :: m x -> ReaderT e m x Source #

Monad m => LiftDep (DepT e_ m) (DepT e_ m) Source #

DepT can be d-lifted to itself.

Instance details

Defined in Control.Monad.Dep

Methods

liftD :: DepT e_ m x -> DepT e_ m x Source #

(Monad m, Coercible newtyped (e_ (DepT e_ m))) => LiftDep (DepT e_ m) (ReaderT newtyped m) Source #

DepT can be d-lifted to a ReaderT in which the environment record containing further DepT actions has been hidden behind a newtype.

This can be useful to "deceive" a function into using an environment possessing different instances than the instances seen by the function's dependencies.

Instance details

Defined in Control.Monad.Dep

Methods

liftD :: DepT e_ m x -> ReaderT newtyped m x Source #

Helpers

useEnv :: forall d e m r. (LiftDep d m, MonadReader e m) => (e -> d r) -> m r Source #

Avoids repeated calls to liftD when all the effects in a function come from the environment.