dep-t-0.4.4.0: Reader-like monad transformer for dependency injection.
Safe HaskellNone
LanguageHaskell2010

Control.Monad.Dep.Has

Description

This module provides a generic "Has" class favoring a style in which the components of the environment come wrapped in records or newtypes, instead of being bare functions.

>>> :{
 type Logger :: (Type -> Type) -> Type
 newtype Logger d = Logger {log :: String -> d ()} deriving Generic
 instance Dep Logger where
   type DefaultFieldName Logger = "logger"
 data Repository d = Repository
   { select :: String -> d [Int],
     insert :: [Int] -> d ()
   } deriving Generic
 instance Dep Repository where
   type DefaultFieldName Repository = "repository"
 newtype Controller d = Controller {serve :: Int -> d String} deriving Generic
 instance Dep Controller where
   type DefaultFieldName Controller = "controller"
 type Env :: (Type -> Type) -> Type
 data Env m = Env
   { logger :: Logger m,
     repository :: Repository m,
     controller :: Controller m
   }
 instance Has Logger m (Env m)
 instance Has Repository m (Env m)
 instance Has Controller m (Env m)
 mkController :: forall d e m. MonadDep [Has Logger, Has Repository] d e m => Controller m
 mkController =
   Controller \url -> do
     e <- ask
     liftD $ log (dep e) "I'm going to insert in the db!"
     liftD $ select (dep e) "select * from ..."
     liftD $ insert (dep e) [1, 2, 3, 4]
     return "view"
:}

The adviseRecord and deceiveRecord functions from the companion package "dep-t-advice" can facilitate working with this style of components.

Synopsis

A generic "Has"

class Has r_ d e | e -> d where Source #

A generic "Has" class. When partially applied to a parametrizable record-of-functions r_, produces a 2-place constraint that can be later used with Control.Monad.Dep.Class.

Minimal complete definition

Nothing

Methods

dep :: e -> r_ d Source #

Given an environment e, produce a record-of-functions parameterized by the environment's effect monad d.

The hope is that using a selector function on the resulting record will determine its type without the need for type annotations.

(This will likely not play well with RecordDotSyntax. See also this trick.)

default dep :: (Dep r_, HasField (DefaultFieldName r_) e u, Coercible u (r_ d)) => e -> r_ d Source #

Component defaults

class Dep r_ Source #

Parametrizable records-of-functions can be given an instance of this typeclass to specify the default field name Has expects for the component in the environment record.

This allows defining Has instances with empty bodies, thanks to DefaultSignatures.

Associated Types

type DefaultFieldName r_ :: Symbol Source #