paramtree-0.1.1: Generate labelled test/benchmark trees from sets of parameters

Copyright(C) 2017 Merijn Verstraaten
LicenseBSD-style (see the file LICENSE)
MaintainerMerijn Verstraaten <merijn@inconsistent.nl>
Stabilityexperimental
Portabilityhaha
Safe HaskellSafe
LanguageHaskell2010

ParamTree

Description

Easily generate a labelled tree of tests/benchmarks from a generation function and sets of parameters to use for each of that functions arguments. Example usecases include criterion benchmark trees or tasty test trees.

Synopsis

Documentation

data Params :: [*] -> * Source #

Sets of parameters to generate the tree from.

type family ParamFun (l :: [*]) r where ... Source #

Type family that converts a type level list into a function type:

ParamFun [Char, Int, Bool] r = Char -> Int -> Bool -> String -> r

Equations

ParamFun '[] r = String -> r 
ParamFun (h ': t) r = h -> ParamFun t r 

growTree Source #

Arguments

:: Maybe String

Groups containing a single entry are skipped and their label is appended to their child, separated by this String if not Nothing.

-> (String -> [a] -> a)

Tree labelling function, e.g. tasty's testGroup or criterion's bgroup

-> String

Label for the root of the tree

-> ParamFun l a

Function that produces leafs, such as tasty tests or criterion benchmarks

-> (Params '[] -> Params l)

Parameter sets to grow tree from

-> a 

Generate a tree from a function that produces a leaf and sets of parameters. Useful for generating tasty TestTrees or criterion benchmark trees from a function and a set of parameter. For example:

import Test.Tasty
import Test.Tasty.HUnit

genTestCase :: Int -> Bool -> Char -> String -> TestTree

params = simpleParam "Int" [1,2]
       . simpleParam "Bool" [True]
       . simpleParam "Char" "xyz"

main :: IO ()
main = defaultMain $ testTree genTestCase params
  where
    testTree = growTree (Just "/") testGroup "my tests"

This generates a tasty TestTree with all combinations of values passed to genTestCase. If the Maybe String argument is provided like in the above example, groups with a single entry, such as "Bool" get collapsed into their parent groups. So instead of a "1 Int" group containing a "True Bool" group they get collapsed into a single "1 Int/True Bool" group, where the "/" separator is the one specified by Just "/"

simpleParam Source #

Arguments

:: (Eq a, Show a) 
=> String

Name of the parameter

-> [a]

Set of values to use

-> Params l 
-> Params (a ': l) 

A simple parameter set. The tree label is a combination of showing the value and the parameter name.

derivedParam Source #

Arguments

:: (Eq r, Show a) 
=> (a -> r)

Parameter derivation function

-> String

Name of the parameter

-> [a]

Set of values to derive from

-> Params l 
-> Params (r ': l) 

A derived parameter set. Useful when the input expected by your function can't be conveniently rendered as a string label. For example:

derivedParam (enumFromTo 0) "My Parameter" [1,2,5]

The above passed enumFromTo 0 1, enumFromTo 0 2, etc. to your function, while labelling them as "1 My Parameter" and "2 My Parameter" respectively.

displayParam :: Eq a => (a -> String) -> String -> [a] -> Params l -> Params (a ': l) Source #

A simple parameter set with a more flexible way of showing values, simpleParam is equivalent to displayParam show.

customParam :: Eq r => (a -> String) -> (a -> r) -> String -> [a] -> Params l -> Params (r ': l) Source #

A completely customisable parameter set, allows specification of how to display values and how to derive values. Equivalencies:

simpleParam = customParam show id

derivedParam = customParam show

displayParam = \f -> customParam f id

paramSets :: [Params r -> Params l] -> Params r -> Params l Source #

Combine multiple sets of parameters into one. Allows a limited amount of control over which combinations appear. For example:

paramSets
    [ simpleParam Bool [True] . simpleParam Char "xy"
    , simpleParam Bool [True,False] . simpleParam Char "a"
    ]

The result is "axy" being used in groups where the "Bool" parameter is True, if the "Bool" parameter is False only "a" is used.