quickcheck-property-comb: Combinators for Quickcheck Property construction and diagnostics

[ library, public-domain, testing ] [ Propose Tags ] [ Report a vulnerability ]

These are simple monads that aim to reduce the pain of composing invariants/properties, and the documenting of those invariants for determining the cause of failure. Specifically, they provide a tool for effective diagnostic for invariants with changing post-conditions, leading to a faster cause-of-failure diagnosis.

Example case for invariants on a data structure Consumers.

data (Ord l) => Consumers l =
  Consumers {
    introduced :: S.Set l,
    met :: M.Map (S.Set l) Bool,
    disjoints :: Disjoints l
  }

introduced_in_disjoint :: Inv (Consumers l)
introduced_in_disjoint = do
  doc "all at quantity are a singleton subset in disjoints"
  subsets       <- (map S.singleton) . S.toList . introduced <$> cause
  disjoint_sets <- disjoints <$> cause
  return . and . map ((flip S.member) disjoint_sets) $ subsets

disjoint_sizes ::  Inv (Disjoints l)
disjoint_sizes = do
 doc . unlines $
   [ "the intersection of introduced and disjoints are the only allowed",
    "singleton sets in disjoints"
     ]
 disjoints' <- cause
 -- Do the checking
 return False

disjoints_eq :: Inv (Disjoints l)
disjoints_eq = do
  doc "disjoint sets are equal in size"
  -- ..
  return True

disjoints_inv :: Invariants (Disjoints l)
disjoints_inv= do
  sat disjoints_eq
  sat disjoints_sizes

inv_consumers :: Invariants (Consumers l)
inv_consumers = do
  satcomp disjoints disjoints_inv
  satcomp met met_inv
  sat introduced_in_disjoint

And to run the Consumer invariant on generated cases:

prop_testedFunction :: Arg -> Property
prop_testedFunction arg =
 let consumers = testedFunction arg in
   runInvariants consumers inv_consumers

[Skip to Readme]

Modules

  • Test
    • QuickCheck
      • Property
        • Test.QuickCheck.Property.Comb

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.1.0.0, 0.1.0.1, 0.1.0.2
Dependencies base (>=4.5 && <4.6), mtl (>=2.1 && <2.2), QuickCheck (>=2.5 && <=2.6) [details]
License LicenseRef-PublicDomain
Author John Feltz
Maintainer [email protected]
Category Testing
Home page http://www.github.com/jfeltz/quickcheck-property-comb
Uploaded by jfeltz at 2013-12-26T14:30:48Z
Distributions
Reverse Dependencies 1 direct, 0 indirect [details]
Downloads 2266 total (7 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs not available [build log]
All reported builds failed as of 2016-12-19 [all 5 reports]

Readme for quickcheck-property-comb-0.1.0.1

[back to package description]

quickcheck-property-comb

These are combinators, based on the Reader and Writer Monads, to allow for fast and painless Quickcheck property/invariant construction.

Why?

Quickcheck is a tool used to test cases based on constructed Properties, or essentially functions taking a data structure and returning a boolean True or False.

However when running tests, the only way to document their failing case is through labeling them after binding, e.g.:

inv1, inv2, inv3 :: Foo -> Bool 
..
fooInvariants :: Foo -> Property 
fooInvariants f = 
    conjoin . map property $ 
      conjoin $ zipWith toLabeled
        ["foo should be even", "foo should contain 3 bar", "all bar should not equal foo"] 
        [inv1 f, inv2 f, inv3 f]

This gets unwieldy fast as the complexity of the data-structure increases, so quickcheck-property-comb provides the following:

  • Monadically unifies composition of invariants and the documenting of those invariants for determining cause of failure.
  • Effective diagnostics for invariants with changing post-conditions, leading to faster cause-of-failure diagnosis.

Example use

data (Ord l) => QuantityConsumers l =
  QuantityConsumers {
    atQuantity :: S.Set l,
    qcMet :: M.Map (S.Set l) Bool,
    qcDisjoints :: Disjoints l
  }

disjoint_sizes ::  Inv (Disjoints l)
disjoint_sizes = do
  doc . unlines $
    [
     "the intersection of all at quantity and disjoints are the only allowed",
     "singleton sets in disjoints"
    ]
  disjoints <- cause 
  -- Do some checking on disjoints 
  return False

disjoints_eq :: Inv (Disjoints l)
disjoints_eq = do
  doc "the solution state domain and sets formed by partition are equal"
  ..
  return False

disjoints :: Invariants (Disjoints l)
disjoints = do
  sat disjoints_eq
  sat disjoints_sizes

at_quantity_in_disjoint :: Inv (QuantityConsumers l)
at_quantity_in_disjoint = do
  doc "all at quantity are a singleton subset in disjoints"

  subsets       <- (map S.singleton) . S.toList . atQuantity <$> cause
  disjoint_sets <- fromDisjoints <$>  cause

  return . and . map ((flip S.member) disjoint_sets) $ subsets

inv_quantity_consumers :: Invariants (QuantityConsumers l)
inv_quantity_consumers = do
  satcomp qcDisjoints disjoints
  sat at_quantity_in_disjoint

-- Then to create the final property
prop_quantity_consumers :: QuantityConsumers l -> Property
prop_quantity_consumers q = runInvariants q inv_quantity_consumers