mockcat: Simple mock function library for test in Haskell.

[ library, mit, testing ] [ Propose Tags ]

mockcat is simple mock library for test in Haskell.

mockcat provides so-called stubbing and verification functions.

Stub functions can return values of Pure Types as well as value of Monadic Types.

Example:

f <- createStubFn $ "expected arg" |> "return value"
print $ f "expected arg" -- "return value"

For more please see the README on GitHub at https://github.com/pujoheadsoft/mockcat#readme


[Skip to Readme]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.1.0.0, 0.2.0.0, 0.2.1.0, 0.3.0.0, 0.3.1.0, 0.4.0.0
Change log CHANGELOG.md
Dependencies base (>=4.7 && <5), template-haskell (>=2.18 && <2.23), text (>=2.0 && <2.2) [details]
License MIT
Copyright 2024 funnycat
Author funnycat <pujoheadsoft@gmail.com>
Maintainer funnycat <pujoheadsoft@gmail.com>
Category Testing
Home page https://github.com/pujoheadsoft/mockcat#readme
Bug tracker https://github.com/pujoheadsoft/mockcat/issues
Source repo head: git clone https://github.com/pujoheadsoft/mockcat
Uploaded by funnycat at 2024-07-26T15:40:54Z
Distributions NixOS:0.2.1.0, Stackage:0.4.0.0
Downloads 94 total (45 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2024-07-26 [all 1 reports]

Readme for mockcat-0.1.0.0

[back to package description]

🐈Mocking library for Haskell🐈‍

Test

日本語版 README はこちら

mockcat is a simple mocking library that supports testing in Haskell.

It mainly provides two features:

  • Creating stub functions
  • Verifying if the expected arguments were applied

Stub functions can return not only monadic values but also pure values.

{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE TypeApplications #-}
import Test.Hspec
import Test.MockCat

spec :: Spec
spec = do
  it "Example of usage" do
    -- Create a Mock (applying “value” returns the pure value True)
    mock <- createMock $ "value" |> True

    -- Extract the stub function from the mock
    let stubFunction = stubFn mock

    -- Verify the results of applying an argument
    stubFunction "value" `shouldBe` True

    -- Verify if the expected value ("value") was applied
    mock `shouldApplyTo` "value"

Stub Functions

Simple Stub Functions

To create stub functions, use the createStubFn function.

{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE TypeApplications #-}
import Test.Hspec
import Test.MockCat

spec :: Spec
spec = do
  it "can create a stub function" do
    -- Create
    f <- createStubFn $ "param1" |> "param2" |> pure @IO ()

    -- Apply
    actual <- f "param1" "param2"

    -- Verify
    actual `shouldBe` ()

To createStubFn, you pass the expected arguments concatenated with |>. The final value after |> is the return value of the function.

If unexpected arguments are applied to the stub function, an error occurs.

uncaught exception: ErrorCall
Expected arguments were not applied to the function.
  expected: "value"
  but got: "valuo"

Named Stub Functions

You can name stub functions.

{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE TypeApplications #-}
import Test.Hspec
import Test.MockCat

spec :: Spec
spec = do
  it "named stub" do
    f <- createNamedStubFun "named stub" $ "x" |> "y" |> True
    f "x" "z" `shouldBe` True

If the expected arguments are not applied, the error message will include this name.

uncaught exception: ErrorCall
Expected arguments were not applied to the function `named stub`.
  expected: "x","y"
  but got: "x","z"

Flexible Stub Functions

You can create a flexible stub function by giving the createStubFn function a conditional expression instead of a specific value.
This allows you to return expected values for arbitrary values, strings matching specific patterns, etc.

any

any matches any value.

{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE TypeApplications #-}
import Test.Hspec
import Test.MockCat
import Prelude hiding (any)

spec :: Spec
spec = do
  it "any" do
    f <- createStubFn $ any |> "return value"
    f "something" `shouldBe` "return value"

Since a function with the same name is defined in Prelude, we use import Prelude hiding (any).

Condition Expressions

Using the expect function, you can handle arbitrary condition expressions.
The expect function takes a condition expression and a label.
The label is used in the error message if the condition is not met.

{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE TypeApplications #-}
import Test.Hspec
import Test.MockCat

spec :: Spec
spec = do
  it "expect" do
    f <- createStubFn $ expect (> 5) "> 5" |> "return value"
    f 6 `shouldBe` "return value"

Condition Expressions without Labels

expect_ is a label-free version of expect.
The error message will show [some condition].

{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE TypeApplications #-}
import Test.Hspec
import Test.MockCat

spec :: Spec
spec = do
  it "expect_" do
    f <- createStubFn $ expect_ (> 5) |> "return value"
    f 6 `shouldBe` "return value"

Condition Expressions using Template Haskell

Using expectByExp, you can handle condition expressions as values of type Q Exp.
The error message will include the string representation of the condition expression.

{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TemplateHaskell #-}
import Test.Hspec
import Test.MockCat

spec :: Spec
spec = do
  it "expectByExpr" do
    f <- createStubFn $ $(expectByExpr [|(> 5)|]) |> "return value"
    f 6 `shouldBe` "return value"

Stub Functions that Return Different Values for Each Applied Argument

By applying a list in the form of x |> y to the createStubFn function,
you can create stub functions that return different values for each applied argument.

{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE TypeApplications #-}
import Test.Hspec
import Test.MockCat
import Prelude hiding (and)

spec :: Spec
spec = do
  it "multi" do
    f <-
      createStubFn
        [ "a" |> "return x",
          "b" |> "return y"
        ]
    f "a" `shouldBe` "return x"
    f "b" `shouldBe` "return y"

Verification

Verify if the Expected Arguments were Applied

You can verify if the expected arguments were applied using the shouldApplyTo function. To perform the verification, create a mock using the createMock function instead of the createStubFn function. In this case, use the stubFn function to extract the stub function from the mock.

{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE TypeApplications #-}
import Test.Hspec
import Test.MockCat

spec :: Spec
spec = do
  it "stub & verify" do
    -- create a mock
    mock <- createMock $ "value" |> True
    -- stub function
    let stubFunction = stubFn mock
    -- assert
    stubFunction "value" `shouldBe` True
    -- verify
    mock `shouldApplyTo` "value"

Verify the Number of Times the Expected Arguments were Applied

You can verify the number of times the expected arguments were applied using the shouldApplyTimes function.

{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE TypeApplications #-}
import Test.Hspec
import Test.MockCat

spec :: Spec
spec = do
  it "shouldApplyTimes" do
    m <- createMock $ "value" |> True
    print $ stubFn m "value"
    print $ stubFn m "value"
    m `shouldApplyTimes` (2 :: Int) `to` "value"

Verify if the Arguments were Applied in the Expected Order

You can verify if the arguments were applied in the expected order using the shouldApplyInOrder function.

{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE TypeApplications #-}
import Test.Hspec
import Test.MockCat

spec :: Spec
spec = do
  it "shouldApplyInOrder" do
    m <- createMock $ any |> True |> ()
    print $ stubFn m "a" True
    print $ stubFn m "b" True
    m
      `shouldApplyInOrder` [ "a" |> True,
                             "b" |> True
                           ]

Verify if the Arguments were Applied in the Expected Partial Order

The shouldApplyInOrder function strictly verifies the order of application,
but the shouldApplyInPartialOrder function can verify if the order of application matches partially.

{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE TypeApplications #-}
import Test.Hspec
import Test.MockCat

spec :: Spec
spec = do
  it "shouldApplyInPartialOrder" do
    m <- createMock $ any |> True |> ()
    print $ stubFn m "a" True
    print $ stubFn m "b" True
    print $ stubFn m "c" True
    m
      `shouldApplyInPartialOrder` [ "a" |> True,
                                    "c" |> True
                                  ]