License | BSD-3 |
---|---|
Maintainer | autotaker@gmail.com |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- class Monad (Base method) => Method method where
- class TupleLike a where
- decorate :: (Method method, MonadUnliftIO (Base method)) => (Args method -> Base method a) -> (a -> Either SomeException (Ret method) -> Base method ()) -> (a -> method) -> method
- decorate_ :: (Method method, MonadUnliftIO (Base method)) => (Args method -> Base method ()) -> (Either SomeException (Ret method) -> Base method ()) -> method -> method
- decorateBefore_ :: Method method => (Args method -> Base method ()) -> method -> method
- invoke :: (MonadReader env (Base method), Method method) => SimpleGetter env method -> method
- liftJoin :: Method method => Base method method -> method
Usage
This module provides dependency injection and decoration for monadic functions (called methods).
Dependency Injection
For example, assume that we are implementing signin function, which checks user's password.
First, let's create an interface to access database.
type UserRepository env = UserRepository { findById :: UserId ->RIO
env (Maybe User) create :: User ->RIO
env UserId }
And add Has-pattern typeclass.
It's better to user SimpleGetter
instead of Lens
,
because we rarely modify the interface.
class HasUserRepository env where
userRepositoryL :: SimpleGetter
env (UserRepository env)
In signup
function, call findById
method via invoke
.
signin :: HasUserRepository env => UserId -> Password -> RIO env (Maybe User) signin userId pass = do muser <- invoke (userRepositoryL . to findById) userId pure $ do user <- muser guard (authCheck user pass) pure user
In production code, inject UserRepository
implementation which
accesses database
userRepositoryImpl :: UserRepository env userRepositoryImpl = UserRepository { findById = ..., create = ... } data ProductionEnv = ProductionEnv instance HasUserRepository ProductionEnv where userRepositoryL = to $ const userRepositoryImpl
In test code, inject UserRepository
mock implementation.
userRepositoryMock :: UserRepository env userRepositoryMock = UserRepository { findById = userId -> pure $ Just (User userId "password123") createUser = user -> pure $ Just "example" } data TestEnv = TestEnv instance HasUserRepository TestEnv where userRepositoryL = to $ const userRepositoryMock test :: Spec test = describe "signin" $ do it "return user for correct password" $ do runRIO TestEnv (signin "example" "password123")`shouldReturn`
Just (User "example" "password123") it "return Nothing for incorrect password" $ do runRIO TestEnv (signin "example" "wrong")`shouldReturn`
Nothing
Decorating methods
By using decorate
, decorate_
, or decorateBefore_
function,
we can insert hooks before/after calling methods
Example to insert logging feature
>>>
let f x y = pure (replicate x y) :: IO [String]
>>>
let before args = putStrLn $ "args: " ++ show (toTuple args)
>>>
let after res = putStrLn $ "ret: " ++ show res
>>>
let decorateF = decorate_ before after f
>>>
decorateF 2 "foo"
args: (2,"foo") ret: Right ["foo","foo"] ["foo","foo"]
Another example to decorate method with transaction management
transactional :: (Method method, MonadUnliftIO (Base method)) => (Connection -> method) -> method transactional = decorate before after where before = do conn <- liftIO $ getConnection cInfo begin conn pure conn after conn (Left _) = liftIO $ rollback conn after conn (Right _) = liftIO $ commit conn
References
class Monad (Base method) => Method method where Source #
Method a is a function of the form
a1 -> a2 -> ... -> an -> m b
where m
is Monad
Typical monads in transformers package are supported.
If you want to support other monads (for example M
),
add the following boilerplate.
instance Method (M a) where Base (M a) = M Ret (M a) = a
Caution Function monad (-> r)
cannot be an instance of Method
Nothing
type Base method :: Type -> Type Source #
Underling monad
Base (a1 -> ... -> an -> m b) = m
type Args method :: Type Source #
Arguments tuple of the method
Args (a1 -> ... -> an -> m b) = a1 :* ... :* an
type Ret method :: Type Source #
Return type of the method
Ret (a1 -> ... -> an -> m b) = b
uncurryMethod :: method -> Args method -> Base method (Ret method) Source #
Convert method to unary function
default uncurryMethod :: (method ~ Base method a, Args method ~ Nil, Ret method ~ a) => method -> Args method -> Base method (Ret method) Source #
curryMethod :: (Args method -> Base method (Ret method)) -> method Source #
Reconstruct method from unary function
Instances
Method [a] Source # | |
Method (Maybe a) Source # | |
Method (IO a) Source # | |
Method (Identity a) Source # | |
Method b => Method (a -> b) Source # | |
Method (Either e a) Source # | |
Method (ST s a) Source # | |
Monad m => Method (MaybeT m a) Source # | |
Method (RIO env a) Source # | |
Monad m => Method (ExceptT e m a) Source # | |
Monad m => Method (StateT s m a) Source # | |
Monad m => Method (ReaderT r m a) Source # | |
Monad m => Method (StateT s m a) Source # | |
(Monad m, Monoid w) => Method (WriterT w m a) Source # | |
(Monad m, Monoid w) => Method (WriterT w m a) Source # | |
(Monoid w, Monad m) => Method (AccumT w m a) Source # | |
Monad m => Method (WriterT w m a) Source # | |
Monad m => Method (SelectT r m a) Source # | |
Monad m => Method (ContT r m a) Source # | |
(Monad m, Monoid w) => Method (RWST r w s m a) Source # | |
(Monad m, Monoid w) => Method (RWST r w s m a) Source # | |
Monad m => Method (RWST r w s m a) Source # | |
class TupleLike a where Source #
Instances
TupleLike Nil Source # | |
TupleLike (a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil))))))) Source # | |
Defined in Control.Method.Internal | |
TupleLike (a :* (b :* (c :* (d :* (e :* (f :* Nil)))))) Source # | |
Defined in Control.Method.Internal | |
TupleLike (a :* (b :* (c :* (d :* (e :* Nil))))) Source # | |
Defined in Control.Method.Internal | |
TupleLike (a :* (b :* (c :* (d :* Nil)))) Source # | |
TupleLike (a :* (b :* (c :* Nil))) Source # | |
TupleLike (a :* (b :* Nil)) Source # | |
TupleLike (a :* Nil) Source # | |
decorate :: (Method method, MonadUnliftIO (Base method)) => (Args method -> Base method a) -> (a -> Either SomeException (Ret method) -> Base method ()) -> (a -> method) -> method Source #
Insert hooks before/after calling the argument method
decorate_ :: (Method method, MonadUnliftIO (Base method)) => (Args method -> Base method ()) -> (Either SomeException (Ret method) -> Base method ()) -> method -> method Source #
Insert hooks before/after calling the argument method
decorateBefore_ :: Method method => (Args method -> Base method ()) -> method -> method Source #
Insert hooks only before calling the argument method.
Because it's free from MonadUnliftIO
constraint,
any methods are supported.
invoke :: (MonadReader env (Base method), Method method) => SimpleGetter env method -> method Source #
invoke method taken from reader environment