prednote-0.8.0.0: Build and evaluate trees of predicates

Safe HaskellNone

Data.Prednote.TestTree

Contents

Description

Helps you build a tree of tests that run against a series of items. This is best illustrated with an example.

Let's say that you have a list of Int. You want to make sure that every Int in the list is odd and that every Int is greater than zero. You also want to make sure that at least 5 Ints in the list are greater than 20.

Pdct from Data.Prednote.Pdct will help you, but only so much: a Pdct can test individual Int, but by itself it will not help you run a check against a whole list of Int. Of course you can build such a test fairly easily with any and all, but what if you want to view the results of the tests verbosely? That's where this module comes in.

 {-# LANGUAGE OverloadedStrings #-}
 import System.Console.Rainbow
 import Data.Prednote.TestTree
 import Data.Prednote.Pdct

 isOdd :: Pdct Int
 isOdd = operand "is odd" odd

 greaterThan0 :: Pdct Int
 greaterThan0 = operand "greater than zero" (> 0)

 greaterThan20 :: Pdct Int
 greaterThan20 = operand "greater than 20" (> 20)

 myOpts :: TestOpts Int
 myOpts = TestOpts
   { tIndentAmt = 2
   , tPassVerbosity = TrueSubjects
   , tFailVerbosity = TrueSubjects
   , tGroupPred = const True
   , tTestPred = const True
   , tShowSkippedTests = True
   , tGroupVerbosity = AllGroups
   , tSubjects = mySubjects
   , tStopOnFail = False
   }

 mySubjects :: [Int]
 mySubjects = [2, 4, 6, 8, 10, 18, 19, 20, 21, 22, 24, 26]

 tests :: [TestTree Int]
 tests = [ isOdd, greaterThan0, greaterThan20 ]

 main :: IO ()
 main = do
   let (cks, passed, failed) = runTests myOpts 0 tests
   t <- termFromEnv
   printChunks t cks
   putStrLn $ "number of tests passed: " ++ show passed
   putStrLn $ "number of tests failed: " ++ show failed

Synopsis

The TestTree

type Name = TextSource

The name of a test or of a group.

type TestFunc aSource

Arguments

 = IndentAmt 
-> Verbosity

Use this verbosity for tests that pass

-> Verbosity

Use this verbosity for tests that fail

-> [a] 
-> Level 
-> (Pass, [Chunk]) 

A test is a function of this type. The function must make chunks in a manner that respects the applicable verbosity.

data TestTree a Source

A tree of tests.

Constructors

TestTree Name (Payload a) 

data Payload a Source

Constructors

Group [TestTree a] 
Test (TestFunc a) 

test :: Name -> TestFunc a -> TestTree aSource

Creates tests.

Tests

eachSubjectMustBeTrue :: Name -> (a -> Text) -> Pdct a -> TestTree aSource

Passes if every subject is True.

nSubjectsMustBeTrue :: Name -> (a -> Text) -> Int -> Pdct a -> TestTree aSource

Passes if at least n subjects are True.

Grouping tests

group :: Name -> [TestTree a] -> TestTree aSource

Creates groups of tests.

Simple test runners

data Verbosity Source

How verbose to be when reporting the results of tests. It would be possible to have many more knobs to control this behavior; this implementation is a compromise and hopefully provides enough verbosity settings without being too complex.

Constructors

Silent

Show nothing at all

PassFail

Show only whether the test passed or failed

FalseSubjects

Show subjects that are False. In addition, shows all evaluation steps that led to the subject being False; however, does not show discarded evaluation steps. Does not show True subjects at all.

TrueSubjects

Show subjects that are True. (This is cumulative, so False subjects are shown too, as they would be using FalseSubjects.) Shows all evaluation steps that led to the subject being True; however, does not show discarded evaluation steps.

Discards

Shows discarded subjects. Cumulative, so also does what FalseSubjects and TrueSubjects do. Also shows all discarded evaluation steps for all subjects.

data GroupVerbosity Source

How verbose to be when showing names of groups.

Constructors

NoGroups

Show no group names at all. However, groups will still be indented.

ActiveGroups

Show groups that are not skipped.

AllGroups

Show all groups, and indicate which groups are skipped.

type Level = IntSource

How many levels of indentation to use. Typically you will start this at zero. It is incremented by one for each level as functions descend through the tree.

runTests :: TestOpts a -> Level -> [TestTree a] -> ([Chunk], PassCount, FailCount)Source

Runs each test in a list of tests (though each test might not run if tStopOnFail is True.) Reports on how many passed and how many failed. (if tStopOnFail is True, the FailCount will never exceed 1.)

Showing the test tree

showTestTree :: IndentAmt -> Level -> TestTree a -> [Chunk]Source

Shows a tree, without evaluating it.

Tree evaluator

data TestOpts a Source

Options for running tests.

Constructors

TestOpts 

Fields

tIndentAmt :: Int

Indent each level by this many spaces

tPassVerbosity :: Verbosity

Use this verbosity for tests that pass

tFailVerbosity :: Verbosity

Use this verbosity for tests that fail

tGroupPred :: Name -> Bool

Groups are run only if this predicate returns True.

tTestPred :: Name -> Bool

Tests are run only if this predicate returns True.

tShowSkippedTests :: Bool

Some tests might be skipped; see tTestPred. This controls whether you want to see a notification of tests that were skipped. (Does not affect skipped groups; see tGroupVerbosity for that.)

tGroupVerbosity :: GroupVerbosity

Show group names? Even if you do not show the names of groups, tests within the group will still be indented.

tSubjects :: [a]

The subjects to test

tStopOnFail :: Bool

If True, then tests will stop running immediately after a single test fails. If False, all tests are always run.

type ShortCircuit = BoolSource

True if the tree returned a result without completely evaluating all parts of the tree. This can occur if tStopOnFail is True and one of the tests in the tree failed.

evalTreeSource

Arguments

:: TestOpts a

Most options

-> Level

The tree will indented by this many levels; typically you will want to start this at 0.

-> TestTree a 
-> (ShortCircuit, [Either [Chunk] (Pass, [Chunk])])

The first element of the tuple is True if the tree was not fully evaluated. This can happen if tStopOnFail is True and one of the tests in the tree failed. The second element of the tuple is a list of Either; each element of the list will be a Left if that component of the tree was not a test, or a Right if that element was a test. The Right will contain a tuple, where the first element indicates whether the test passed or failed, and the second element is the list of Chunk.

Evaluates a tree. This function is the basis of runTests, which is typically a bit easier to use.