json-assertions-1.0.13: Test that your (Aeson) JSON encoding matches your expectations

Safe HaskellNone
LanguageHaskell2010

Test.JSON.Assertions

Contents

Description

json-assertions is a library for validating that your JSON encoding matches what you are actually expecting. It does this by providing you with a DSL to traverse a JSON document at the same time as you traverse the value that was encoded. As you traverse the JSON document, you are building up assertions (by asserting that you expect certain keys and array indices to exist), and you can also add your own assertions to check the contents of object properties.

JSONTest is an indexed monad, so you will need to enable RebindableSyntax and bring indexed monadic bind into scope:

import Prelude hiding (Monad(..))
import Control.Monad.Indexed ((>>>=), ireturn)
import Test.JSON.Assertions
import Data.Aeson

return :: a -> JSONTest i i a
return = ireturn

(>>=) :: m i j a -> (a -> m j k b) -> m i k b
(>>=) = (>>>=)

You can now write tests as an action in the JSONTest monad. The first index is the type of the object you wish to encode, and the second parameter is the type that the test ends in. For example, consider the following:

data Person = Person { personName :: String }
instance ToJSON Person where
  toJSON p = object [ "name" .= personName p ]

We can write a test to check that the JSON encoding of a Person's name is correct:

personTest :: JSONTest Person String String
personTest = do
  expectedName <- key "name"
  assertEq expectedName

For more information, you may wish to read http://ocharles.org.uk/blog/posts/2013-11-24-using-indexed-free-monads-to-quickcheck-json.html.

Synopsis

Tests and Traversals

key Source #

Arguments

:: String

JSON Key

-> (i -> j)

An associated morphism into a substructure of the test environment

-> JSONTest i j j 

Traverse into the value underneath a specific key in the JSON structure. The return value is the value inside the Haskell value - that is, the result applying the associated morphism.

nth Source #

Arguments

:: Int

JSON array index

-> (i -> j)

An associated morphism into a substructure of the test environment

-> JSONTest i j j 

Traverse the specific index of a JSON array. The return value is the value inside the Haskell value - that is, the result applying the associated morphism.

assertEq :: ToJSON a => a -> JSONTest i i () Source #

Assert that the current JSON value is exactly equal to the result of calling toJSON on a value.

stop :: JSONTest a () r Source #

Using stop discards the indices in the monad, which can help when you need to isum multiple tests that end in different states.

jsonTest :: JSONTest i j a -> JSONTest i () a Source #

Finalize a JSONTest by calling stop at the end.

Test Interpreters

testJSON :: ToJSON i => JSONTest i j a -> i -> [String] Source #

Run a JSONTest against a Haskell value that can be encoded to JSON. Returns a list of strings describing the failed assertions, or the empty list if all assertions were satisfied.

type JSONTest = IxFree JSONF Source #