mockcat-0.2.0.0: Simple mock function library for test in Haskell.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Test.MockCat.Mock

Description

This module provides bellow functions.

  • Create mocks that can be stubbed and verified.
  • Create stub function.
  • Verify applied mock function.
Synopsis

Documentation

createMock :: MockBuilder params fun verifyParams => MonadIO m => params -> m (Mock fun verifyParams) Source #

Create a mock. From this mock, you can generate stub functions and verify the functions.

 import Test.Hspec
 import Test.MockCat
 ...
 it "stub & verify" do
   -- create a mock
   m <- createMock $ "value" |> True
   -- stub function
   let f = stubFn m
   -- assert
   f "value" `shouldBe` True
   -- verify
   m `shouldApplyTo` "value"
 

If you do not need verification and only need stub functions, you can use mockFun.

createNamedMock :: MockBuilder params fun verifyParams => MonadIO m => MockName -> params -> m (Mock fun verifyParams) Source #

Create a named mock. If the test fails, this name is used. This may be useful if you have multiple mocks.

 import Test.Hspec
 import Test.MockCat
 ...
 it "named mock" do
   m <- createNamedMock "mock" $ "value" |> True
   stubFn m "value" `shouldBe` True
 

createStubFn :: MockBuilder params fun verifyParams => MonadIO m => params -> m fun Source #

Create a stub function. import Test.Hspec import Test.MockCat ... it "stub function" do f <- createStubFn $ "value" |> True f "value" `shouldBe` True

createNamedStubFn :: MockBuilder params fun verifyParams => MonadIO m => String -> params -> m fun Source #

Create a named stub function.

stubFn :: Mock fun v -> fun Source #

Extract the stub function from the mock.

shouldApplyTo :: Verify params input => Mock fun params -> input -> IO () Source #

Verifies that the function has been applied to the expected arguments.

shouldApplyTimes :: (VerifyCount countType params a, Eq params) => Mock fun params -> countType -> a -> IO () Source #

Verify the number of times a function has been applied to an argument.

import Test.Hspec
import Test.MockCat
...
it "verify to applied times." do
  m <- createMock $ "value" |> True
  print $ stubFn m "value"
  print $ stubFn m "value"
  m `shouldApplyTimes` (2 :: Int) `to` "value" 

shouldApplyInOrder :: VerifyOrder params input => Mock fun params -> [input] -> IO () Source #

Verify functions are applied in the expected order.

import Test.Hspec
import Test.MockCat
import Prelude hiding (any)
...
it "verify order of apply" do
  m <- createMock $ any |> True |> ()
  print $ stubFn m "a" True
  print $ stubFn m "b" True
  m `shouldApplyInOrder` ["a" |> True, "b" |> True]

shouldApplyInPartialOrder :: VerifyOrder params input => Mock fun params -> [input] -> IO () Source #

Verify that functions are applied in the expected order.

Unlike shouldApplyInOrder, not all applications need to match exactly.

As long as the order matches, the verification succeeds.

shouldApplyTimesGreaterThanEqual :: VerifyCount CountVerifyMethod params a => Eq params => Mock fun params -> Int -> a -> IO () Source #

shouldApplyTimesLessThanEqual :: VerifyCount CountVerifyMethod params a => Eq params => Mock fun params -> Int -> a -> IO () Source #

shouldApplyTimesGreaterThan :: VerifyCount CountVerifyMethod params a => Eq params => Mock fun params -> Int -> a -> IO () Source #

shouldApplyTimesLessThan :: VerifyCount CountVerifyMethod params a => Eq params => Mock fun params -> Int -> a -> IO () Source #

to :: (a -> IO ()) -> a -> IO () Source #