typeable-mock-0.1.0.1: Mock functions and expressions anywhere.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Test.TypeableMock

Synopsis

Mocks and mock configuration

data Mock Source #

Constructors

forall x.Typeable x => Mock 

Instances

Instances details
Show Mock Source # 
Instance details

Defined in Test.TypeableMock

Methods

showsPrec :: Int -> Mock -> ShowS #

show :: Mock -> String #

showList :: [Mock] -> ShowS #

data MockConfig Source #

Mock configuration. When running production, use the defaultMockConfig without adding mocks to it - it would call the real functions.

The key or type of the mock created in a test suite may accidentally mismatch the key or type at the place where a mock is used. Silently calling the real functions would make the test suite fragile. So, when running on a test suite, protect against the mismatches by requiring that the mocks are present. Set mcShouldFailOnNotFound to return True or allow a few special cases:

testMockConfig = defaultMockConfig {
  mcShouldFailOnNotFound = \\key tRep -> key ``notElem`` whitelist where
    -- Functions that are allowed to be called during tests.
    whitelist = ["readFile"]
}

Constructors

MockConfig 

Fields

Instances

Instances details
Show MockConfig Source # 
Instance details

Defined in Test.TypeableMock

Creating and calling mocks

makeMock :: (Function f args (m x) Typeable, Typeable f, Typeable x, MonadIO m) => String -> f -> IO Mock Source #

Wraps the function into a Mock. For successful lookup at the call site, the type of the passed function must match the type of the mocked function.

If the mocked function has polymorphic arguments, such as print :: Show a => a -> IO (), create a mock for each case. For example, if an app prints Int and Strings, create two mocks:

mockConf <- addMocksToConfig defaultConf <$> sequence
  [ makeMock "print" (const $ pure () :: Int -> IO ()),
  , makeMock "print" (const $ pure () :: String -> IO ())
  ]

For mocking functions with many arguments it is convenient to use constN and asTypeOf. Using asTypeOf lets you omit the type annotation. These definitions create the same mock:

makeMock "someAction" ((\_ _ _ -> pure "result") :: Arg1 -> Arg2 -> Arg3 -> SomeMonad ())
makeMock "someAction" (constN $ pure "result" :: Arg1 -> Arg2 -> Arg3 -> SomeMonad ())
makeMock "someAction" (constN $ pure "result" `asTypeOf` someAction)

lookupMockFunction :: forall f. Typeable f => MockConfig -> String -> Maybe f Source #

A helper function to lookup the function. Likely you want to write a wrapper that retrieves the MockConfig from the environment.

withMock :: String -> f -> AppMonad f
withMock key f = do
  mockConf <- getMockConfig <$> getEnv
  pure $ fromMaybe f (lookupMockFunction mockConf key)

withMock "getSomething" getSomething >>= \f -> f someArg

constN :: forall f (args :: [Type]) a. Function f args a (EmptyConstraint :: Type -> Constraint) => a -> f #

Constant function for an arbitrary number of arguments.

let const2 = constN :: x -> a -> b -> x
>>> zipWith3 (constN 1) [1..10] [1..5] ["a", "b", "c"] :: [Int]
[1,1,1]

Checking calls

data ActualVal Source #

Constructors

forall a.Typeable a => ActualVal a 

data ExpectedVal Source #

Description of what value for mock call the assertions expect

Constructors

AnyVal 
forall a.(Typeable a, Show a, Eq a) => ExpectedVal a 
forall a.(Typeable a, Show a) => PredicateVal (a -> Bool) 

Instances

Instances details
Eq ExpectedVal Source # 
Instance details

Defined in Test.TypeableMock

Show ExpectedVal Source # 
Instance details

Defined in Test.TypeableMock

lookupMock :: HasCallStack => MockConfig -> String -> Mock Source #

Find a mock by name. If there are several mocks under the same name, use lookupMockTyped.

lookupMockTyped :: forall t. (HasCallStack, Typeable t) => MockConfig -> String -> Maybe Mock Source #

Find a mock by name and type.

useMockConvert Source #

Arguments

:: (Monad m, Typeable mock) 
=> m MockConfig

Get mock config from the context | Convert the mock function. Usually it is id or unwrapping function for an existential type like MockMonadIO.

-> (mock -> f) 
-> String

Key of the mock

-> f

The function that is being mocked

-> m f 

Build helpers using mocks in your application with this. The conversion is for the case when the type of a function stored in mock does not match the mocked function. Usually this is a case for a newtype wrapper over a polymorphic monad like MockMonadIO.

assertHasCalls :: HasCallStack => [ExpectedCallRecord] -> Mock -> IO () Source #

Assert that all expected calls were made in the given order.

mock <- lookupMockInEnv "name"  -- user-defined helper function for your app env
liftIO $ assertHasCalls [expectCall "arg1" "arg2"] mock

assertNotCalled :: HasCallStack => Mock -> IO () Source #

Assert the mock was never called.

assertAnyCall :: HasCallStack => ExpectedCallRecord -> Mock -> IO () Source #

Assert that the expected call happened at least once.

getCalls :: Mock -> IO [ActualCallRecord] Source #

Get list of calls. Use together with callMatches when the existing assert* functions are not flexible enough.

expectCall :: Function f args ExpectedCallRecord ((Show & Eq) & Typeable) => f Source #

Use this to create ExpectedCallRecord

Examples:

expectCall "email@example.com" True

withResult :: (Show a, Eq a, Typeable a) => ExpectedCallRecord -> a -> ExpectedCallRecord Source #

Assert that mock returned the given result. Sometimes it is more convenient than checking arguments.

callMatches :: HasCallStack => ActualCallRecord -> ExpectedCallRecord -> Bool Source #

The expected call record matches the actual one. Note that it throws error for the logic bugs when a mismatch is caused by wrong number of arguments or wrong types.

resetMockCallRecords :: Mock -> IO () Source #

Reuse the mocks between the test items

resetAllCallRecords :: MockConfig -> IO () Source #

Reuse the mocks between the test items

Mocking polymorphic monads

It is common to have the application logic live in a polymorphic monad that is constrained with several type classes. However, only the monomorphic types have an instance of Typeable and can be mocked. The solution is to wrap a polymorphic function with a concrete existential type.

The library provides MockMonadIO that lets you write a mock fitting in any context that has MonadIO.

Define a mock and add it to the config:

makeMock (const $ pure "getSomething" :: Int -> MockMonadIO String)

Then use it at the call site. Before calling the mock, you need to unwrap the existential type. It is a good idea to define your own helpers for getting the mock config and mock lookup. That would make calling mocks much more concise. See more at examples/App.hs.

Here is a verbose example that expands both retrieving and transforming the mock.

insideAppPolymorphicMonad :: (HasEnv m, MonadIO m) => Int -> m ()
insideAppPolymorphicMonad arg = do
  mockConf <- getMockConfig <$> getEnv
  let mock = lookupMockFunction mockConf "getSomething"
  (maybe unMockMonadIO1 getSomething mock) arg

With your own helpers it can look like this:

insideAppPolymorphicMonad :: (HasEnv m, MonadIO m) => Int -> m ()
insideAppPolymorphicMonad arg = do
  myMockHelper unMockMonadIO1 getSomething mock >>= \f -> f arg

newtype MockMonadIO a Source #

Helper for making polymorphic mock functions.

Constructors

MockMonadIO 

Fields

Instances

Instances details
Monad MockMonadIO Source # 
Instance details

Defined in Test.TypeableMock

Methods

(>>=) :: MockMonadIO a -> (a -> MockMonadIO b) -> MockMonadIO b #

(>>) :: MockMonadIO a -> MockMonadIO b -> MockMonadIO b #

return :: a -> MockMonadIO a #

Functor MockMonadIO Source # 
Instance details

Defined in Test.TypeableMock

Methods

fmap :: (a -> b) -> MockMonadIO a -> MockMonadIO b #

(<$) :: a -> MockMonadIO b -> MockMonadIO a #

Applicative MockMonadIO Source # 
Instance details

Defined in Test.TypeableMock

Methods

pure :: a -> MockMonadIO a #

(<*>) :: MockMonadIO (a -> b) -> MockMonadIO a -> MockMonadIO b #

liftA2 :: (a -> b -> c) -> MockMonadIO a -> MockMonadIO b -> MockMonadIO c #

(*>) :: MockMonadIO a -> MockMonadIO b -> MockMonadIO b #

(<*) :: MockMonadIO a -> MockMonadIO b -> MockMonadIO a #

MonadIO MockMonadIO Source # 
Instance details

Defined in Test.TypeableMock

Methods

liftIO :: IO a -> MockMonadIO a #

fromMockMonadIO :: forall m x args f' f. (MonadIO m, Function f' args (MockMonadIO x) EmptyConstraint, Function f args (m x) EmptyConstraint) => f' -> f Source #

Changes the return type of a function from MockMonadIO x to m x. The m must be a concrete type at the call site. If the caller is in a polymorphic monad, use one of the unMockMonadION instead.

unMockMonadIO1 :: (a -> MockMonadIO x) -> forall m. MonadIO m => a -> m x Source #

The family of functions unMockMonadION is specialized with the number of arguments. Unlike fromMockMonadIO, the monad m can be polymorphic at the call site.

unMockMonadIO2 :: (a -> b -> MockMonadIO x) -> forall m. MonadIO m => a -> b -> m x Source #

unMockMonadIO3 :: (a -> b -> c -> MockMonadIO x) -> forall m. MonadIO m => a -> b -> c -> m x Source #

unMockMonadIO4 :: (a -> b -> c -> d -> MockMonadIO x) -> forall m. MonadIO m => a -> b -> c -> d -> m x Source #

unMockMonadIO5 :: (a -> b -> c -> d -> e -> MockMonadIO x) -> forall m. MonadIO m => a -> b -> c -> d -> e -> m x Source #

Advanced polymorphic mocks

If your mock needs to be aware of a custom class to return a result, and be able to called from polymorphic code, make your own wrapper similar to MockMonadIO. For example:

newtype MockMonadHasMyEnv a = MockMonadHasMyEnv {
  unMockMonadHasMyEnv :: forall m. (MonadIO m, HasMyEnv m) => m a
}
makeMock (\a -> getMyEnv >>= makeFakeResult ... :: Int -> MockMonadHasMyEnv String)