hedgehog-classes: Hedgehog will eat your typeclass bugs

[ bsd3, library, testing ] [ Propose Tags ]

This library provides Hedgehog properties to ensure that typeclass instances adhere to the set of laws that they are supposed to. There are other libraries that do similar things, such as `genvalidity-hspec` and checkers. This library differs from other solutions by not introducing any new typeclasses that the user needs to learn, and otherwise minimal API overhead.

This library is directly inspired by `quickcheck-classes`.


[Skip to Readme]

Modules

[Index] [Quick Jump]

Flags

Manual Flags

NameDescriptionDefault
aeson

You can disable the use of the aeson package using `-f-aeson`.

This may be useful for accelerating builds in sandboxes for expert users.

Enabled
comonad

You can disable the use of the comonad package using `-f-comonad`.

This may be useful for accelerating builds in sandboxes for expert users.

Enabled
semirings

You can disable the use of the semirings package using `-f-semirings`.

This may be useful for accelerating builds in sandboxes for expert users.

Enabled
primitive

You can disable the use of the primitive package using `-f-primitive`.

This may be useful for accelerating builds in sandboxes for expert users.

Enabled
vector

You can disable the use of the vector package using `-f-vector`.

This may be useful for accelerating builds in sandboxes for expert users.

Enabled

Use -f <flag> to enable a flag, or -f -<flag> to disable that flag. More info

Downloads

Note: This package has metadata revisions in the cabal description newer than included in the tarball. To unpack the package including the revisions, use 'cabal get'.

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.1.0.0, 0.1.1.0, 0.1.2, 0.2, 0.2.0.1, 0.2.1, 0.2.2, 0.2.3, 0.2.4, 0.2.4.1, 0.2.5, 0.2.5.1, 0.2.5.2, 0.2.5.3, 0.2.5.4 (info)
Change log CHANGELOG.md
Dependencies aeson (>=0.9 && <2.3), base (>=4.12 && <4.20), binary (>=0.8 && <0.9), comonad (>=5.0 && <5.1), containers (>=0.5 && <0.7), hedgehog (>=1 && <1.5), pretty-show (>=1.9 && <1.11), primitive (>=0.6.4 && <0.9), semirings (>=0.2 && <0.8), silently (>=1.2 && <1.3), transformers (>=0.5 && <0.7), vector (>=0.12 && <0.14), wl-pprint-annotated (>=0.0 && <0.2) [details]
License BSD-3-Clause
Copyright 2020 chessai
Author chessai
Maintainer chessai1996@gmail.com
Revised Revision 3 made by chessai at 2023-11-23T15:40:40Z
Category Testing
Home page https://github.com/hedgehogqa/haskell-hedgehog-classes
Bug tracker https://github.com/hedgehogqa/haskell-hedgehog-classes/issues
Source repo head: git clone https://github.com/hedgehogqa/haskell-hedgehog-classes.git
Uploaded by chessai at 2022-12-17T04:37:06Z
Distributions Arch:0.2.5.4, LTSHaskell:0.2.5.4, NixOS:0.2.5.4, Stackage:0.2.5.4
Downloads 5664 total (51 in the last 30 days)
Rating 2.0 (votes: 1) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs uploaded by user
Build status unknown [no reports yet]

Readme for hedgehog-classes-0.2.5.4

[back to package description]

hedgehog-classes Hackage

Hedgehog will eat your typeclass bugs.

Motivation

hedgehog-classes is a wrapper around Hedgehog that aims to provide a simple, straightforward API for testing common typeclass laws quickly, while providing good error messages to help debug any failing tests. It is inspired by the quickcheck-classes library.

API Overview

The API of hedgehog-classes is dead simple. There are three parts.

The first part is a datatype, called 'Laws', which looks like this:

data Laws = Laws
  { lawsTypeclass :: String
  , lawsProperties :: [(String,Property)]
  }

It is a typeclass name along with a list of named property tests.

The second part of hedgehog-classes are the functions, which follow a simple structure. All functions in hedgehog-classes have one of the following three type signatures, based on the kind of the type which the corresponding typeclass parameterises (Nullary, Unary, or Binary). Note that they all return a 'Laws', only the inputs are different. Below, 'Ctx' refers to the typeclass in question:

-- Typeclasses that have kind 'Type -> Constraint', e.g. 'Eq'
tcLaw :: (Ctx a, Eq a, Show a) => Gen a -> Laws

-- Typeclasses that have kind '(Type -> Type) -> Constraint', e.g. 'Functor'
tcLaw1 ::
  ( Ctx f
  , forall x. Eq x => Eq (f x)
  , forall x. Show x => Show (f x)
  ) => (forall x. Gen x -> Gen (f x)) -> Laws

-- Typeclasses that have kind '(Type -> Type -> Type) -> Constraint', e.g. 'Bifunctor'
tcLaw2 ::
  ( Ctx f
  , forall x y. (Eq x, Eq y) => Eq (f x y)
  , forall x y. (Show x, Show y) => Show (f x y)
  ) => (forall x y. Gen x -> Gen y -> Gen (f x y)) -> Laws

The third and last part of hedgehog-classes are the three convenience functions used to run your tests. They all return an IO Bool, where True is returned if all the tests pass, and False otherwise. They are as following:

-- Test a single typeclasses' laws.
lawsCheck :: Laws -> IO Bool

-- Test multiple typeclass laws for a single type.
lawsCheckOne :: Gen a -> [Gen a -> Laws] -> IO Bool

-- Test mutliple typeclass laws for multiple types.
-- The argument is pairs of type names and their associated laws to test.
lawsCheckMany :: [(String, [Laws])] -> IO Bool

That is all there is to using hedgehog-classes in your test suite. For usage examples, see the haddocks.

Distributing your own Laws

hedgehog-classes also exports some functions which you may find useful for writing functions that allow users to test the laws of typeclasses you define in your own libraries, along with utilities for providing custom error messages. They can be found here.

Example error messages

Below is an example of an error message one might get from a failed test from hedgehog-classes:

alt text

alt text

Similar libraries

There are a number of libraries that have similar goals to hedgehog-classes:

Supported Typeclasses

  • base
    • Alternative
    • Applicative
    • Arrow
    • Bifoldable
    • Bifunctor
    • Bitraversable
    • Bits/FiniteBits
    • Category
    • Contravariant
    • Enum
    • Eq
    • Foldable
    • Functor
    • Generic
    • Integral
    • Monad
    • MonadIO
    • MonadPlus
    • MonadZip
    • Ord
    • Semigroup
    • Show
    • ShowRead
    • Storable
    • Traversable
  • aeson
    • ToJSON
    • ToJSON/FromJSON
  • comonad
    • Comonad
  • semirings
    • Semiring
    • Ring
  • primitive
    • Prim

Some typeclasses can have additional laws, which are not part of their sufficient definition. A common example is commutativity of a monoid. In such cases where this is sensible, hedgehog-classes provides functions such commutativeMonoidLaws, commutativeSemigroupLaws, etc. hedgehog-classes also tests that foldl'/foldr' actually accumulate strictly. There are other such cases that are documented on Hackage.

Support will be added for the typeclasses from semigroupoids.

Support will be added for the Semiring/Ring typeclasses from semirings.

Building

Currently, you need GHC >= 8.5 to build this (because of -XQuantifiedConstraints). Some CPP can be used to make this buildable with older GHCs, I just have not done so yet. I would gladly take a PR that does so, but only for GHC 8.2.2 and newer.

To use this library for testing, just add it to a test stanza of your cabal file.

To use this library to export your own Laws functions which you wish to distribute, add it to the library stanza of your cabal file.

Improvements

There are a number of improvements that can be made to the API of hedgehog-classes:

  • Traversable needs better error messages, without exposing library internals.
  • Arrow Laws 5/6/7 need names.
  • Some laws could use better names, as some of them I had to make up.
  • ixLaws can accidentally be extremely inefficient and I'm not sure how to fix that.
  • The test suite is incomplete.
  • There is no 'bad' test suite, for testing error messages.
  • There could be spelling mistakes/grammatical errors/inconsistencies in the custom error messages.

You can help fix any of the above by opening an issue/PR! Thanks.