License | BSD-3 |
---|---|
Maintainer | autotaker@gmail.com |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- type family Has a env where ...
- getL :: forall a env. Has a env => Lens' env a
- type family Has1 f env where ...
- runIF :: forall f env a. Has1 f env => (forall env'. f env' -> RIO env' a) -> RIO env a
- class Environment env where
- newtype Extends env = Extends env
- deriveEnv :: Name -> Q [Dec]
- class Interface (iface :: k -> Type) where
- mapBaseRIO :: (Interface iface, IBase iface ~ RIO) => (env -> env') -> iface env' -> iface env
Getting Fields
If a method depends on some value of type T
,
use
constraints, and get the value from the environment
with Has
T envview
.getL
newtype ServerName = ServerName String printServerName :: (Has
ServerName env) => RIO env () printServerName = do ServerName n <- viewgetL
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.
Has a env = HasAux a env (FindEnv a env (Addr 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'
Has1 f env = Has1Aux f env (FindEnv1 f env (Addr 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
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 adding Extend T
as a field.
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 !ConnectionPoolderiveEnv
''BaseEnv data ExtEnv = ExtEnv !(Extends BaseEnv) !(UserRepo ExtEnv)deriveEnv
''ExtEnv
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 (Extends baseEnv) userRepoImpl
runRIO extEnv $ do
printServerName
forM_ users $ usernm -> do
user <- signup usernm "password"
liftIO $ print user
class Environment env where Source #
Nothing
Super env
represents the inheritance relation between environments.
Wrapper that represents the super environment.
Extends env |
Instances
Eq env => Eq (Extends env) Source # | |
Ord env => Ord (Extends env) Source # | |
Defined in Control.Env.Hierarchical.Internal | |
Show env => Show (Extends env) Source # | |
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) instanceInterface
AuthHandler where typeIBase
AuthHandler = RIO data AuthEnv env = AuthEnv !(UserRepo (AutheEnv env)) !(Extends env)deriveEnv
''AuthEnv authHandlerImpl :: (Has
ConnectionPool env) => AuthHandler env authHandlerImpl =mapBaseRIO
(AuthEnv userRepoImpl . Extends) 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 parameterk
, 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)
Nothing