method-0.1.0.0: rebindable methods for improving testability
LicenseBSD-3
Maintainerautotaker@gmail.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Control.Method

Description

 
Synopsis

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

Minimal complete definition

Nothing

Associated Types

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 Args method = Nil

type Ret method :: Type Source #

Return type of the method

Ret  (a1 -> ... -> an -> m b) = b

Methods

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

default curryMethod :: (method ~ Base method a, Args method ~ Nil, Ret method ~ a) => (Args method -> Base method (Ret method)) -> method Source #

Instances

Instances details
Method [a] Source # 
Instance details

Defined in Control.Method

Associated Types

type Base [a] :: Type -> Type Source #

type Args [a] Source #

type Ret [a] Source #

Methods

uncurryMethod :: [a] -> Args [a] -> Base [a] (Ret [a]) Source #

curryMethod :: (Args [a] -> Base [a] (Ret [a])) -> [a] Source #

Method (Maybe a) Source # 
Instance details

Defined in Control.Method

Associated Types

type Base (Maybe a) :: Type -> Type Source #

type Args (Maybe a) Source #

type Ret (Maybe a) Source #

Methods

uncurryMethod :: Maybe a -> Args (Maybe a) -> Base (Maybe a) (Ret (Maybe a)) Source #

curryMethod :: (Args (Maybe a) -> Base (Maybe a) (Ret (Maybe a))) -> Maybe a Source #

Method (IO a) Source # 
Instance details

Defined in Control.Method

Associated Types

type Base (IO a) :: Type -> Type Source #

type Args (IO a) Source #

type Ret (IO a) Source #

Methods

uncurryMethod :: IO a -> Args (IO a) -> Base (IO a) (Ret (IO a)) Source #

curryMethod :: (Args (IO a) -> Base (IO a) (Ret (IO a))) -> IO a Source #

Method (Identity a) Source # 
Instance details

Defined in Control.Method

Associated Types

type Base (Identity a) :: Type -> Type Source #

type Args (Identity a) Source #

type Ret (Identity a) Source #

Method b => Method (a -> b) Source # 
Instance details

Defined in Control.Method

Associated Types

type Base (a -> b) :: Type -> Type Source #

type Args (a -> b) Source #

type Ret (a -> b) Source #

Methods

uncurryMethod :: (a -> b) -> Args (a -> b) -> Base (a -> b) (Ret (a -> b)) Source #

curryMethod :: (Args (a -> b) -> Base (a -> b) (Ret (a -> b))) -> a -> b Source #

Method (Either e a) Source # 
Instance details

Defined in Control.Method

Associated Types

type Base (Either e a) :: Type -> Type Source #

type Args (Either e a) Source #

type Ret (Either e a) Source #

Methods

uncurryMethod :: Either e a -> Args (Either e a) -> Base (Either e a) (Ret (Either e a)) Source #

curryMethod :: (Args (Either e a) -> Base (Either e a) (Ret (Either e a))) -> Either e a Source #

Method (ST s a) Source # 
Instance details

Defined in Control.Method

Associated Types

type Base (ST s a) :: Type -> Type Source #

type Args (ST s a) Source #

type Ret (ST s a) Source #

Methods

uncurryMethod :: ST s a -> Args (ST s a) -> Base (ST s a) (Ret (ST s a)) Source #

curryMethod :: (Args (ST s a) -> Base (ST s a) (Ret (ST s a))) -> ST s a Source #

Monad m => Method (MaybeT m a) Source # 
Instance details

Defined in Control.Method

Associated Types

type Base (MaybeT m a) :: Type -> Type Source #

type Args (MaybeT m a) Source #

type Ret (MaybeT m a) Source #

Methods

uncurryMethod :: MaybeT m a -> Args (MaybeT m a) -> Base (MaybeT m a) (Ret (MaybeT m a)) Source #

curryMethod :: (Args (MaybeT m a) -> Base (MaybeT m a) (Ret (MaybeT m a))) -> MaybeT m a Source #

Method (RIO env a) Source # 
Instance details

Defined in Control.Method

Associated Types

type Base (RIO env a) :: Type -> Type Source #

type Args (RIO env a) Source #

type Ret (RIO env a) Source #

Methods

uncurryMethod :: RIO env a -> Args (RIO env a) -> Base (RIO env a) (Ret (RIO env a)) Source #

curryMethod :: (Args (RIO env a) -> Base (RIO env a) (Ret (RIO env a))) -> RIO env a Source #

Monad m => Method (ExceptT e m a) Source # 
Instance details

Defined in Control.Method

Associated Types

type Base (ExceptT e m a) :: Type -> Type Source #

type Args (ExceptT e m a) Source #

type Ret (ExceptT e m a) Source #

Methods

uncurryMethod :: ExceptT e m a -> Args (ExceptT e m a) -> Base (ExceptT e m a) (Ret (ExceptT e m a)) Source #

curryMethod :: (Args (ExceptT e m a) -> Base (ExceptT e m a) (Ret (ExceptT e m a))) -> ExceptT e m a Source #

Monad m => Method (StateT s m a) Source # 
Instance details

Defined in Control.Method

Associated Types

type Base (StateT s m a) :: Type -> Type Source #

type Args (StateT s m a) Source #

type Ret (StateT s m a) Source #

Methods

uncurryMethod :: StateT s m a -> Args (StateT s m a) -> Base (StateT s m a) (Ret (StateT s m a)) Source #

curryMethod :: (Args (StateT s m a) -> Base (StateT s m a) (Ret (StateT s m a))) -> StateT s m a Source #

Monad m => Method (ReaderT r m a) Source # 
Instance details

Defined in Control.Method

Associated Types

type Base (ReaderT r m a) :: Type -> Type Source #

type Args (ReaderT r m a) Source #

type Ret (ReaderT r m a) Source #

Methods

uncurryMethod :: ReaderT r m a -> Args (ReaderT r m a) -> Base (ReaderT r m a) (Ret (ReaderT r m a)) Source #

curryMethod :: (Args (ReaderT r m a) -> Base (ReaderT r m a) (Ret (ReaderT r m a))) -> ReaderT r m a Source #

Monad m => Method (StateT s m a) Source # 
Instance details

Defined in Control.Method

Associated Types

type Base (StateT s m a) :: Type -> Type Source #

type Args (StateT s m a) Source #

type Ret (StateT s m a) Source #

Methods

uncurryMethod :: StateT s m a -> Args (StateT s m a) -> Base (StateT s m a) (Ret (StateT s m a)) Source #

curryMethod :: (Args (StateT s m a) -> Base (StateT s m a) (Ret (StateT s m a))) -> StateT s m a Source #

(Monad m, Monoid w) => Method (WriterT w m a) Source # 
Instance details

Defined in Control.Method

Associated Types

type Base (WriterT w m a) :: Type -> Type Source #

type Args (WriterT w m a) Source #

type Ret (WriterT w m a) Source #

Methods

uncurryMethod :: WriterT w m a -> Args (WriterT w m a) -> Base (WriterT w m a) (Ret (WriterT w m a)) Source #

curryMethod :: (Args (WriterT w m a) -> Base (WriterT w m a) (Ret (WriterT w m a))) -> WriterT w m a Source #

(Monad m, Monoid w) => Method (WriterT w m a) Source # 
Instance details

Defined in Control.Method

Associated Types

type Base (WriterT w m a) :: Type -> Type Source #

type Args (WriterT w m a) Source #

type Ret (WriterT w m a) Source #

Methods

uncurryMethod :: WriterT w m a -> Args (WriterT w m a) -> Base (WriterT w m a) (Ret (WriterT w m a)) Source #

curryMethod :: (Args (WriterT w m a) -> Base (WriterT w m a) (Ret (WriterT w m a))) -> WriterT w m a Source #

(Monoid w, Monad m) => Method (AccumT w m a) Source # 
Instance details

Defined in Control.Method

Associated Types

type Base (AccumT w m a) :: Type -> Type Source #

type Args (AccumT w m a) Source #

type Ret (AccumT w m a) Source #

Methods

uncurryMethod :: AccumT w m a -> Args (AccumT w m a) -> Base (AccumT w m a) (Ret (AccumT w m a)) Source #

curryMethod :: (Args (AccumT w m a) -> Base (AccumT w m a) (Ret (AccumT w m a))) -> AccumT w m a Source #

Monad m => Method (WriterT w m a) Source # 
Instance details

Defined in Control.Method

Associated Types

type Base (WriterT w m a) :: Type -> Type Source #

type Args (WriterT w m a) Source #

type Ret (WriterT w m a) Source #

Methods

uncurryMethod :: WriterT w m a -> Args (WriterT w m a) -> Base (WriterT w m a) (Ret (WriterT w m a)) Source #

curryMethod :: (Args (WriterT w m a) -> Base (WriterT w m a) (Ret (WriterT w m a))) -> WriterT w m a Source #

Monad m => Method (SelectT r m a) Source # 
Instance details

Defined in Control.Method

Associated Types

type Base (SelectT r m a) :: Type -> Type Source #

type Args (SelectT r m a) Source #

type Ret (SelectT r m a) Source #

Methods

uncurryMethod :: SelectT r m a -> Args (SelectT r m a) -> Base (SelectT r m a) (Ret (SelectT r m a)) Source #

curryMethod :: (Args (SelectT r m a) -> Base (SelectT r m a) (Ret (SelectT r m a))) -> SelectT r m a Source #

Monad m => Method (ContT r m a) Source # 
Instance details

Defined in Control.Method

Associated Types

type Base (ContT r m a) :: Type -> Type Source #

type Args (ContT r m a) Source #

type Ret (ContT r m a) Source #

Methods

uncurryMethod :: ContT r m a -> Args (ContT r m a) -> Base (ContT r m a) (Ret (ContT r m a)) Source #

curryMethod :: (Args (ContT r m a) -> Base (ContT r m a) (Ret (ContT r m a))) -> ContT r m a Source #

(Monad m, Monoid w) => Method (RWST r w s m a) Source # 
Instance details

Defined in Control.Method

Associated Types

type Base (RWST r w s m a) :: Type -> Type Source #

type Args (RWST r w s m a) Source #

type Ret (RWST r w s m a) Source #

Methods

uncurryMethod :: RWST r w s m a -> Args (RWST r w s m a) -> Base (RWST r w s m a) (Ret (RWST r w s m a)) Source #

curryMethod :: (Args (RWST r w s m a) -> Base (RWST r w s m a) (Ret (RWST r w s m a))) -> RWST r w s m a Source #

(Monad m, Monoid w) => Method (RWST r w s m a) Source # 
Instance details

Defined in Control.Method

Associated Types

type Base (RWST r w s m a) :: Type -> Type Source #

type Args (RWST r w s m a) Source #

type Ret (RWST r w s m a) Source #

Methods

uncurryMethod :: RWST r w s m a -> Args (RWST r w s m a) -> Base (RWST r w s m a) (Ret (RWST r w s m a)) Source #

curryMethod :: (Args (RWST r w s m a) -> Base (RWST r w s m a) (Ret (RWST r w s m a))) -> RWST r w s m a Source #

Monad m => Method (RWST r w s m a) Source # 
Instance details

Defined in Control.Method

Associated Types

type Base (RWST r w s m a) :: Type -> Type Source #

type Args (RWST r w s m a) Source #

type Ret (RWST r w s m a) Source #

Methods

uncurryMethod :: RWST r w s m a -> Args (RWST r w s m a) -> Base (RWST r w s m a) (Ret (RWST r w s m a)) Source #

curryMethod :: (Args (RWST r w s m a) -> Base (RWST r w s m a) (Ret (RWST r w s m a))) -> RWST r w s m a Source #

class TupleLike a where Source #

Associated Types

type AsTuple a Source #

Methods

fromTuple :: AsTuple a -> a Source #

toTuple :: a -> AsTuple a Source #

Instances

Instances details
TupleLike Nil Source # 
Instance details

Defined in Control.Method.Internal

Associated Types

type AsTuple Nil Source #

TupleLike (a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil))))))) Source # 
Instance details

Defined in Control.Method.Internal

Associated Types

type AsTuple (a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil))))))) Source #

Methods

fromTuple :: AsTuple (a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil))))))) -> a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil)))))) Source #

toTuple :: (a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil))))))) -> AsTuple (a :* (b :* (c :* (d :* (e :* (f :* (g :* Nil))))))) Source #

TupleLike (a :* (b :* (c :* (d :* (e :* (f :* Nil)))))) Source # 
Instance details

Defined in Control.Method.Internal

Associated Types

type AsTuple (a :* (b :* (c :* (d :* (e :* (f :* Nil)))))) Source #

Methods

fromTuple :: AsTuple (a :* (b :* (c :* (d :* (e :* (f :* Nil)))))) -> a :* (b :* (c :* (d :* (e :* (f :* Nil))))) Source #

toTuple :: (a :* (b :* (c :* (d :* (e :* (f :* Nil)))))) -> AsTuple (a :* (b :* (c :* (d :* (e :* (f :* Nil)))))) Source #

TupleLike (a :* (b :* (c :* (d :* (e :* Nil))))) Source # 
Instance details

Defined in Control.Method.Internal

Associated Types

type AsTuple (a :* (b :* (c :* (d :* (e :* Nil))))) Source #

Methods

fromTuple :: AsTuple (a :* (b :* (c :* (d :* (e :* Nil))))) -> a :* (b :* (c :* (d :* (e :* Nil)))) Source #

toTuple :: (a :* (b :* (c :* (d :* (e :* Nil))))) -> AsTuple (a :* (b :* (c :* (d :* (e :* Nil))))) Source #

TupleLike (a :* (b :* (c :* (d :* Nil)))) Source # 
Instance details

Defined in Control.Method.Internal

Associated Types

type AsTuple (a :* (b :* (c :* (d :* Nil)))) Source #

Methods

fromTuple :: AsTuple (a :* (b :* (c :* (d :* Nil)))) -> a :* (b :* (c :* (d :* Nil))) Source #

toTuple :: (a :* (b :* (c :* (d :* Nil)))) -> AsTuple (a :* (b :* (c :* (d :* Nil)))) Source #

TupleLike (a :* (b :* (c :* Nil))) Source # 
Instance details

Defined in Control.Method.Internal

Associated Types

type AsTuple (a :* (b :* (c :* Nil))) Source #

Methods

fromTuple :: AsTuple (a :* (b :* (c :* Nil))) -> a :* (b :* (c :* Nil)) Source #

toTuple :: (a :* (b :* (c :* Nil))) -> AsTuple (a :* (b :* (c :* Nil))) Source #

TupleLike (a :* (b :* Nil)) Source # 
Instance details

Defined in Control.Method.Internal

Associated Types

type AsTuple (a :* (b :* Nil)) Source #

Methods

fromTuple :: AsTuple (a :* (b :* Nil)) -> a :* (b :* Nil) Source #

toTuple :: (a :* (b :* Nil)) -> AsTuple (a :* (b :* Nil)) Source #

TupleLike (a :* Nil) Source # 
Instance details

Defined in Control.Method.Internal

Associated Types

type AsTuple (a :* Nil) Source #

Methods

fromTuple :: AsTuple (a :* Nil) -> a :* Nil Source #

toTuple :: (a :* Nil) -> AsTuple (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

liftJoin :: Method method => Base method method -> method Source #

Generalization of join function