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

Control.Monad.Dep.Has

Description

This module provides a general-purpose Has class favoring a style in which the components of the environment, instead of being bare functions, are themselves records or newtypes containing functions.

In this style, the functions that are "invoked" from the environment are actually record field selectors. These selectors guide the Has class to find the correct records in the environment.

>>> :{
 type Logger :: (Type -> Type) -> Type
 newtype Logger d = Logger {log :: String -> d ()}
 instance Dep Logger where
   type DefaultFieldName Logger = "logger"
 --
 data Repository d = Repository
   { select :: String -> d [Int],
     insert :: [Int] -> d ()
   }
 instance Dep Repository where
   type DefaultFieldName Repository = "repository"
 --
 newtype Controller d = Controller {serve :: Int -> d String}
 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)
 :}

Has can be used in combination with MonadDep, like this:

>>> :{
 mkController :: MonadDep [Has Logger, Has Repository] d env m => Controller m
 mkController =
   Controller \url -> 
     useEnv \(asCall -> call) -> do
       call log "I'm going to insert in the db!"
       call select "select * from ..."
       call insert [1, 2, 3, 4]
       return "view"
:}

Has can also be used independently of MonadReader or MonadDep. Here for example the environment is passed as a plain function argument, and m doesn't have any constraint other than Monad:

>>> :{
 mkController' :: (Monad m, Has Logger m env, Has Repository m env) => env -> Controller m
 mkController' (asCall -> call) =
   Controller \url -> do
     call log "I'm going to insert in the db!"
     call select "select * from ..."
     call insert [1, 2, 3, 4]
     return "view"
:}
Synopsis

A general-purpose Has

class Has r_ (m :: Type -> Type) (env :: Type) | env -> m where Source #

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

Minimal complete definition

Nothing

Methods

dep :: env -> r_ m Source #

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

The hope is that using a selector function on the resulting record will fix the record's type without the need for type annotations.

(This will likely not play well with RecordDotSyntax. See also this import alias trick for avoiding name collisions.)

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

Instances

Instances details
(FieldsFindableByType (env_ m), HasField (FindFieldByType (env_ m) (r_ m)) (env_ m) u, Coercible u (r_ m)) => Has r_ m (Autowired (env_ m)) Source # 
Instance details

Defined in Control.Monad.Dep.Env

Methods

dep :: Autowired (env_ m) -> r_ m Source #

(Dep r_, HasField (DefaultFieldName r_) (env_ m) u, Coercible u (r_ m)) => Has r_ m (TheDefaultFieldName (env_ m)) Source # 
Instance details

Defined in Control.Monad.Dep.Env

Methods

dep :: TheDefaultFieldName (env_ m) -> r_ m Source #

(HasField name (env_ m) u, Coercible u (r_ m)) => Has r_ m (TheFieldName name (env_ m)) Source # 
Instance details

Defined in Control.Monad.Dep.Env

Methods

dep :: TheFieldName name (env_ m) -> r_ m Source #

InductiveEnvFind r_ m rs => Has r_ m (InductiveEnv rs Identity m) Source #

Works by searching on the list of types.

Instance details

Defined in Control.Monad.Dep.Env

Methods

dep :: InductiveEnv rs Identity m -> r_ m Source #

call helper

asCall :: forall env m. env -> forall r_ x. Has r_ m env => (r_ m -> x) -> x Source #

Transforms an environment with suitable Has instances into a "helper" function that looks in the environment for the arguments of other functions. Typically, the "helped" functions will be record field selectors.

In practice, this means that you can write call foo instead of foo (dep env).

Using asCall in a view pattern avoids having to name the environment.

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 #