cabal-detailed-quickcheck-0.2.0.1: QuickCheck for Cabal tests
Copyrightⓒ Anselm Schüler 2022
LicenseMIT
MaintainerAnselm Schüler <mail@anselmschueler.com>
Stabilitystable
PortabilityPortable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Distribution.TestSuite.QuickCheck

Description

This module allows you to easily make Cabal tests for the detailed-0.9 interface. See the docs. It sets sensible option declarations for the tests.

This module re-uses record names from Distribution.TestSuite and Test.QuickCheck. It is recommended that you enable the DisambiguateRecordFields extension in GHC and/or import the module qualified. For many basic tests, you don’t need to import Distribution.TestSuite.

To make a test, simply construct a PropertyTest and call getPropertyTest on it.

A simple sample test suite:

module Tests (tests) where
import Distribution.TestSuite.QuickCheck
import Test.QuickCheck
tests = [
  getPropertyTest PropertyTest {
    name = "addition-is-commutative",
    tags = [],
    property = \a b -> a + b === b + a
    }
  ]

The tests you get as a result support several parameters:

Property nameValid valuesEffect
silent booleans If true, all output is disabled. Sets verbosity to Silent. See chatty. Disabling Silent raises the verbosity to Chatty if it is not already higher.
chatty booleans If true, the default amount of output is emitted by QuickCheck. Sets verbosity to Chatty. See chatty. Note that setting this verbosity option to false does not undo setting it to true, but lowers the verbosity by one level if it is not already lower.
verbose booleans If true, prints checked values as output. Sets verbosity to Verbose. See verbose. Note that setting this verbosity option to false does not undo setting it to true, but lowers the verbosity by one level if it is not already lower.
verboseShrinking booleans If true, prints all checked and shrunk values as output. See verboseShrinking.
verbosity Silent, Chatty, or VerboseSets the verbosity to the desired level.
maxDiscardRatio positive integerMaximum number of discarded tests per successful test before giving up. See maxDiscardRatio.
noShrinking booleans Disables shrinking of test cases. See noShrinking.
shrinkingbooleansOpposite of noShrinking.
maxShrinks nonnegative integerMaximum number of shrinks before giving up or zero to disable shrinking. See maxShrinks.
maxSuccess positive integerMaximum number of successful tests before succeeding. See maxSuccess.
maxSize positive integerSize to use for the biggest test cases. See maxSize.
sizeScale positive integerScales all sizes by a number. See mapSize.
replay tuple of QCGen and nonnegative integer or emptyReplays a previous test case. Pass a string representing a tuple of the usedSeed and usedSize values of a test case. Use empty string to disable.

You can set default values by using getPropertyTestWith You can access these values in your test by using getPropertyTestUsing. Do both with getPropertyTestWithUsing.

Synopsis

Create tests

getPropertyTest :: Testable prop => PropertyTest prop -> Test Source #

Get a Cabal Test from a PropertyTest

getPropertyTestWith Source #

Arguments

:: Testable prop 
=> TestArgs

The arguments for the test

-> PropertyTest prop 
-> Test 

Get a Cabal Test from a PropertyTest with custom TestArgs

getPropertyTestUsing Source #

Arguments

:: Testable prop 
=> PropertyTest (TestArgs -> prop)

A property test whose property takes a TestArgs argument

-> Test 

Get a Cabal Test from a PropertyTest that takes the test arguments and returns a Testable value

getPropertyTestWithUsing Source #

Arguments

:: Testable prop 
=> TestArgs

The arguments for the test

-> PropertyTest (TestArgs -> prop)

A property test whose property takes a TestArgs argument

-> Test 

Get a Cabal Test with custom TestArgs from a PropertyTest that takes the test arguments and returns a testable value

getPropertyTests :: Testable prop => [PropertyTest prop] -> [Test] Source #

Get a list of Tests from a list of PropertyTests

propertyTestGroup :: Testable prop => String -> [PropertyTest prop] -> Test Source #

Get a named test group from a list of PropertyTests. These are assumed to be able to run in parallel. See testGroup and Group.

Argument data types

data PropertyTest prop Source #

Property test declaration with metadata

Constructors

PropertyTest 

Fields

  • name :: String

    Name of the test, for Cabal. See See Cabal’s name.

  • tags :: [String]

    Tags of the test, for Cabal. See Cabal’s tags.

  • property :: prop

    Property to check. This should usually be or return an instance of Testable.

data TestArgs Source #

Arguments for altering property test behaviour. These can be altered in the final Cabal Test using setOption.

Constructors

TestArgs 

Fields

data Verbosity Source #

Datatype for setting the verbosity of tests

Constructors

Silent

QuickCheck prints nothing. This sets chatty = False.

Chatty

Print basic statistics. This sets chatty = True.

Verbose

Print every test case. This applies verbose.

Instances

Instances details
Bounded Verbosity Source # 
Instance details

Defined in Distribution.TestSuite.QuickCheck

Enum Verbosity Source # 
Instance details

Defined in Distribution.TestSuite.QuickCheck

Read Verbosity Source # 
Instance details

Defined in Distribution.TestSuite.QuickCheck

Show Verbosity Source # 
Instance details

Defined in Distribution.TestSuite.QuickCheck

Eq Verbosity Source # 
Instance details

Defined in Distribution.TestSuite.QuickCheck

Ord Verbosity Source #

Silent < Chatty < Verbose

Instance details

Defined in Distribution.TestSuite.QuickCheck

Functions for using arguments

argsToTestArgs :: Args -> TestArgs Source #

Transform a QuickCheck Args value to a TestArgs value, defaulting all missing properties

argsToTestArgs = argsToTestArgsWith stdTestArgs

argsToTestArgsWith :: TestArgs -> Args -> TestArgs Source #

Transform a QuickCheck Args value to a TestArgs value, with fallbacks for missing properties given by the first argument.

testArgsToArgs :: TestArgs -> Args Source #

Recover arguments passed to quickCheck from a TestArgs

stdTestArgs :: TestArgs Source #

Default arguments for property tests