License | BSD-3 |
---|---|
Maintainer | autotaker@gmail.com |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- protocol :: ProtocolM f a -> IO (ProtocolEnv f)
- data ProtocolM f a
- data ProtocolEnv f
- data Call f m
- data CallArgs f m
- data CallId
- type IsMethodName f m = (Typeable (f m), Ord (f m), Show (f m))
- lookupMock :: forall f m. (IsMethodName f m, Show (AsTuple (Args m)), TupleLike (Args m), Method m, MonadIO (Base m)) => f m -> ProtocolEnv f -> m
- lookupMockWithShow :: forall f m. (IsMethodName f m, Method m, MonadIO (Base m)) => (Args m -> String) -> f m -> ProtocolEnv f -> m
- decl :: IsMethodName f m => Call f m -> ProtocolM f CallId
- whenArgs :: ArgsMatcher (Args m) => f m -> EachMatcher (Args m) -> CallArgs f m
- thenMethod :: Behave x => Condition x -> MethodOf x -> x
- thenAction :: (Behave x, Method (MethodOf x)) => Condition x -> Base (MethodOf x) (Ret (MethodOf x)) -> x
- thenReturn :: (Behave x, Method (MethodOf x)) => Condition x -> Ret (MethodOf x) -> x
- dependsOn :: Call f m -> [CallId] -> Call f m
- verify :: ProtocolEnv f -> IO ()
Documentation
protocol :: ProtocolM f a -> IO (ProtocolEnv f) Source #
Build ProtocolEnv
from Protocol DSL.
data ProtocolEnv f Source #
provides mock methods, where ProtocolEnv
ff
is a GADT functor that
represents the set of dependent methods.
:: forall f m. (IsMethodName f m, Show (AsTuple (Args m)), TupleLike (Args m), Method m, MonadIO (Base m)) | |
=> f m | name of method |
-> ProtocolEnv f | |
-> m |
Get the mock method by method name. Return a unstubed method (which throws exception for every call) if the behavior of the method is unspecified by ProtocolEnv
:: forall f m. (IsMethodName f m, Method m, MonadIO (Base m)) | |
=> (Args m -> String) | show function for the argument of method |
-> f m | name of method |
-> ProtocolEnv f | |
-> m |
Get the mock method by method name. Return a unstubed method (which throws exception for every call) if the behavior of the method is unspecified by ProtocolEnv. Use this function only if you want to customize show implementation for the argument of the method.
decl :: IsMethodName f m => Call f m -> ProtocolM f CallId Source #
Declare a method call specification. It returns the call id of the method call.
whenArgs :: ArgsMatcher (Args m) => f m -> EachMatcher (Args m) -> CallArgs f m Source #
Specify the argument condition of a method call
thenMethod :: Behave x => Condition x -> MethodOf x -> x Source #
Specify behavior from a pair of a condition and a method.
thenAction :: (Behave x, Method (MethodOf x)) => Condition x -> Base (MethodOf x) (Ret (MethodOf x)) -> x Source #
Specify behavior that executes an action for a call
thenReturn :: (Behave x, Method (MethodOf x)) => Condition x -> Ret (MethodOf x) -> x Source #
Specify behavior that return a constant value for a call
dependsOn :: Call f m -> [CallId] -> Call f m Source #
Specify on which method calls the call depends.
verify :: ProtocolEnv f -> IO () Source #
Verify that all method calls specified by Protocol DSL are fired.