dep-t-0.6.8.0: Dependency injection for records-of-functions.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Dep.Has

Description

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

>>> :{
 newtype Logger d = Logger {log :: String -> d ()}
 data Repository d = Repository { select :: String -> d [Int], insert :: [Int] -> d () }
 newtype Controller d = Controller {serve :: Int -> d String}
 -- A dependency injection environment that contains the components.
 type Deps :: (Type -> Type) -> Type
 data Deps m = Deps
   { logger :: Logger m,
     repository :: Repository m,
     controller :: Controller m
   }
 instance Has Logger m (Deps m) where dep Deps {logger} = logger
 instance Has Repository m (Deps m) where dep Deps {repository} = repository
 instance Has Controller m (Deps m) where dep Deps {controller} = controller
 :}

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 components in the environment:

>>> :{
 makeController :: (Has Logger m deps, Has Repository m deps, Monad m) => deps -> Controller m
 makeController (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"
:}

By convention, the DI environment parameter is usually called deps. Notice also the use of the (optional) asCall helper.

If we regard makeController above as a component constructor, Has lets us avoid having to define separate positional parameters for each dependency of the constructor. Not only that: it also avoids us having to give names to those parameters, and even having to mention their types (because they are implicit in the record field selectors).

Synopsis
  • class Has (r_ :: (Type -> Type) -> Type) (m :: Type -> Type) (deps :: Type) | deps -> m where
    • dep :: deps -> r_ m
  • type family HasAll rs_ m e where ...
  • asCall :: forall deps m. deps -> forall r_ method. Has r_ m deps => (r_ m -> method) -> method
  • pattern Call :: forall deps m. (forall r_ method. Has r_ m deps => (r_ m -> method) -> method) -> deps
  • class Dep r_ where

A general-purpose Has

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

A generic "Has" class. When partially applied to a parametrizable record-of-functions r_, produces a 2-place constraint saying that the environment deps has the record r_ with effect monad m.

The constraint can be used on its own, or with Control.Monad.Dep.Class.

Minimal complete definition

Nothing

Methods

dep :: deps -> r_ m Source #

Given an environment deps, 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.

See also this import alias trick for avoiding name collisions.

default dep :: (Dep r_, HasField (DefaultFieldName r_) deps u, Coercible u (r_ m)) => deps -> 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 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 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 Dep.Env

Methods

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

Has r_ m (a, r_ m) Source # 
Instance details

Defined in Dep.Has

Methods

dep :: (a, r_ m) -> r_ m Source #

Has r_ m (r_ m, b) Source # 
Instance details

Defined in Dep.Has

Methods

dep :: (r_ m, b) -> 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 Dep.Env

Methods

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

Has r_ m (a, b, r_ m) Source # 
Instance details

Defined in Dep.Has

Methods

dep :: (a, b, r_ m) -> r_ m Source #

Has r_ m (a, r_ m, c) Source # 
Instance details

Defined in Dep.Has

Methods

dep :: (a, r_ m, c) -> r_ m Source #

Has r_ m (r_ m, b, c) Source # 
Instance details

Defined in Dep.Has

Methods

dep :: (r_ m, b, c) -> r_ m Source #

Has r_ m (a, b, c, r_ m) Source # 
Instance details

Defined in Dep.Has

Methods

dep :: (a, b, c, r_ m) -> r_ m Source #

Has r_ m (a, b, r_ m, d) Source # 
Instance details

Defined in Dep.Has

Methods

dep :: (a, b, r_ m, d) -> r_ m Source #

Has r_ m (a, r_ m, c, d) Source # 
Instance details

Defined in Dep.Has

Methods

dep :: (a, r_ m, c, d) -> r_ m Source #

Has r_ m (r_ m, b, c, d) Source # 
Instance details

Defined in Dep.Has

Methods

dep :: (r_ m, b, c, d) -> r_ m Source #

type family HasAll rs_ m e where ... Source #

When partially applied to a type-level list rs_ of parametrizable records-of-functions, produces a 2-place constraint saying that the environment e has all the records rs_ with effect monad m.

Equations

HasAll '[] m e = () 
HasAll (r_ ': rs_) m e = (Has r_ m e, HasAll rs_ m e) 

call helpers

asCall Source #

Arguments

:: forall deps m. deps

Dependency injection context that contains the components.

-> forall r_ method. Has r_ m deps 
=> (r_ m -> method)

Field selector function that extracts a method from a component.

-> method 

A record-of-functions r_ might play the role of a "component" taking part in dependency injection.

Each function field is then a "method". And the record field selectors are functions which take the component and return the method corresponding to that field.

Given a dependency injection environment, asCall produces a reusable helper that returns the the method corresponding to a field selector, on the condition that the selector's record actually exists in the environment.

>>> :{
 data SomeRecord m = SomeRecord { someSelector :: String -> m () }
 data Deps m = Deps
   { someRecord :: SomeRecord m
   }
 instance Has SomeRecord m (Deps m) where
   dep (Deps {someRecord}) = someRecord
 :}

In practice, this just means that you can write call someSelector instead of someSelector (dep deps):

>>> :{
   twoInvocations :: (IO (), IO ())
   twoInvocations =
     let deps :: Deps IO = Deps { someRecord = SomeRecord { someSelector = putStrLn } }
         call = asCall deps
      in (someSelector (dep deps) "foo", call someSelector "foo")
:}

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

>>> :{
   functionThatCalls :: Has SomeRecord m deps => deps -> m ()
   functionThatCalls (asCall -> call) = call someSelector "foo"
:}

pattern Call Source #

Arguments

:: forall deps m. (forall r_ method. Has r_ m deps => (r_ m -> method) -> method) 
-> deps

The dependency injection context that we want to match.

Pattern synonym version of asCall. Slightly more succinct and doesn't require -XViewPatterns. The synonym is unidirectional: it can only be used for matching.

>>> :{
 data SomeRecord m = SomeRecord { someSelector :: String -> m () }
 data Deps m = Deps
   { someRecord :: SomeRecord m
   }
 instance Has SomeRecord m (Deps m) where
   dep (Deps {someRecord}) = someRecord
 functionThatCalls :: Has SomeRecord m deps => deps -> m ()
 functionThatCalls (Call call) = call someSelector "foo"
:}

Component defaults

class Dep r_ Source #

Deprecated: more intrusive than useful

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 #