hierarchical-env-0.1.0.0: hierarchical environments for dependency injection
LicenseBSD-3
Maintainerautotaker@gmail.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Control.Env.Hierarchical

Description

 
Synopsis

Getting Fields

If a method depends on some value of type T, use Has T env constraints, and get the value from the environment with view getL.

newtype ServerName = ServerName String
printServerName :: (Has ServerName env) => RIO env ()
printServerName = do
  ServerName n <- view getL
  liftIO $ putStrLn $ "ServerName is " <> n

type family Has a env where ... Source #

Type constraint meaning env contains a as a (including ancestors') field.

An environment env contains unique value for each type T that satisfies Has T env. If you want to depends on multiple values of the same type, please distinguish them by using newtype.

Equations

Has a env = HasAux a env (FindEnv a (Ancestors env)) 

getL :: forall a env. Has a env => Lens' env a Source #

Lens to extract a from env

Invoking interface methods

We call a record type whose fields are methods as an interface.

In the following example, UserRepo is an interface.

Dependency to an interface F is represented as type constraint Has1 F env, methods of the interface can be invoked inside runIF.

data UserRepo env = UserRepo {
  _createUser :: UserName -> RIO env UserId,
  _setPassword :: UserId -> Password -> RIO env ()
}
makeLenses ''UserRepo

data User = User {
  _userName :: UserName,
  _userId :: UserId,
} deriving(Eq, Ord, Show)
makeLenses ''User

signup :: (Has1 UserRepo env) => UserName -> Password -> RIO env User
signup name passwd = runIF $ \userRepo -> do
  userId <- view createUser userRepo name
  view setPassword userRepo userId passwd
  pure User { _userName = name, _userId = userId}

type family Has1 f env where ... Source #

Type constraint meaning env contains f env' for some ancestor env'

Equations

Has1 f env = Has1Aux f env (FindEnv1 f (Ancestors env)) 

runIF :: forall f env a. Has1 f env => (forall env'. f env' -> RIO env' a) -> RIO env a Source #

Run action that depends on an interface f. The action must be polymorphic to env', because it will run in some ancestor environment, which may be different from env,

Injecting dependecies

With universal environments

First, define environment Env that contains all dependencies as fields.

data Env = Env !ServerName !(UserRepo Env)

Then, the following boilerpolate will derive required type constraints. (e.g. Has ServerName Env, Has1 UserRepo Env)

deriveEnv ''Env
type instance Super Env = Root

Now, you can inject dependency by specifying the actual value of Env to the argument of runRIO.

mkUserRepo :: DBConfig -> UserRepo Env
mkUserRepo = ...

runApp :: ServerName -> DBConfig -> [UserName] -> IO ()
runApp serverName dbConfig users = do
  let env = Env serverName (mkUserRepo dbConfig)
  runRIO env $ do
    printServerName
    forM_ users $ userName ->
      user <- signup userName "password"
      print user

With hierarchical environments

Instead of resolving the dependency universally, you can extend environments by specifying the super environment.

In the following example ExtEnv inherits BaseEnv. The extended environment is a nominal sub-type of its super environment, that is,

data BaseEnv = BaseEnv !ServerName !ConnectionPool

deriveEnv ''BaseEnv
type instance Super BaseEnv = Root

data ExtEnv = ExtEnv !BaseEnv !(UserRepo ExtEnv)

deriveEnv ''ExtEnv
type instance Super ExtEnv = BaseEnv

Then, ExtEnv resolves the dependencies.

userRepoImpl :: Has ConnectionPool env => UserRepo env
userRepoImpl = UserRepo createUserImpl setPaswordImpl
  where
  createUserImpl userName = ...
  setPasswordImpl uid passwd = ...

runApp :: ServerName -> ConnectionPool -> [UserName] -> IO ()
runApp serverName pool users = do
  let baseEnv = BaseEnv serverName pool
      extEnv = ExtEnv baseEnv userRepoImpl
  runRIO extEnv $ do
    printServerName
    forM_ users $ usernm -> do
      user <- signup usernm "password"
      liftIO $ print user

data Root Source #

Root environment that does not have any fields.

Instances

Instances details
Environment Root Source # 
Instance details

Defined in Control.Env.Hierarchical.Internal

Associated Types

type Fields1 Root :: [Type -> Type] Source #

type Fields Root :: [Type] Source #

type Super Root Source # 
Instance details

Defined in Control.Env.Hierarchical.Internal

type Super Root = TypeError ('Text "No super environment for Root") :: Type
type Fields1 Root Source # 
Instance details

Defined in Control.Env.Hierarchical.Internal

type Fields1 Root = '[] :: [Type -> Type]
type Fields Root Source # 
Instance details

Defined in Control.Env.Hierarchical.Internal

type Fields Root = '[] :: [Type]

type family Super env Source #

Super env represents the inheritance relation between environments. Every environment must be a descendant of Root.

Instances

Instances details
type Super Root Source # 
Instance details

Defined in Control.Env.Hierarchical.Internal

type Super Root = TypeError ('Text "No super environment for Root") :: Type

Hiding dependencies

Suppose that we are implementing an interface AuthHandler, which handle signin and signup business logic.

data AuthHandler env = AuthHandler {
  _signin :: UserName -> Password -> RIO env User
  _signup :: UserName -> Password -> RIO env User
}
makeLenses ''AuthHandler

The authHandlerImpl depends on another interface UserRepo, which accesses a database to store user information.

data UserRepo env = UserRepo {
 _createUser :: UserName -> RIO env UserId,
 _setPassword :: UserId -> Password -> RIO env ()
}
makeLenses ''UserRepo

userRepoImpl :: (Has ConnectionPool env) => UserRepo env
userRepoImpl = ...

authHandlerImpl :: (Has1 UserRepo env) => AuthHandler env
authHandlerImpl = AuthHandler signinImpl signupImpl

signupImpl :: (Has1 UserRepo env) => UserName -> Password -> RIO env User
signupImpl usernm passwd = ...

signinImpl :: (Has1 UserRepo env) => UserName -> Password -> RIO env User
signinImpl usernm passwd = ...

Assume that UserRepo is a private interface and should not be exported. Let's refactor authHandlerImpl by using mapBaseRIO.

data AuthHandler env = AuthHandler {
  _signin :: UserName -> Password -> RIO env User
  _signup :: UserName -> Password -> RIO env User
} deriving(Generic)

instance Interface AuthHandler where
  type IBase AuthHandler = RIO

data AuthEnv env = AuthEnv !(UserRepo (AutheEnv env)) !env
deriveEnv ''AuthEnv
type instance Super (AuthEnv env) = env

authHandlerImpl :: (Has ConnectionPool env) => AuthHandler env
authHandlerImpl = mapBaseRIO (AuthEnv userRepoImpl) handler
  where
    handler = AuthHandler signinImpl signupImpl

Now, the dependency to UserRepo is resolved in the module and hidden from the signature of authHandlerImpl

class Interface (iface :: k -> Type) where #

Interface is a record whose fields are methods. The instance can be derived via Generic. Here is an example:

  {-# LANGUAGE DeriveGeneric #-}
  {-# LANGUAGE TypeFamilies  #-}
  data FizzBuzz env = FizzBuzz {
    printFizz :: RIO env (),
    printBuzz :: RIO env (),
    printFizzBuzz :: RIO env (),
    printInt :: Int -> RIO env ()
  } deriving(Generic)

  instance Interface FizzBuzz where
    type IBase FizzBuzz = RIO
  

Notes

  • iface takes an (poly-kinded) type parameter k, which is the parameter to specify the base monad.
  • Base monads of each fields must be the same. (Interface cannot contain any fields which are not a method)

Minimal complete definition

Nothing

Associated Types

type IBase (iface :: k -> Type) :: k -> Type -> Type #

IBase iface k is the base monad for each method of the interface.

Methods

mapBase :: forall (p :: k) (q :: k). NT (IBase iface p) (IBase iface q) -> iface p -> iface q #

mapBaseRIO :: (Interface iface, IBase iface ~ RIO) => (env -> env') -> iface env' -> iface env #

Specilized version of mapBase for RIO.