Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Provides test identification by Search Using Golden Answer References. This is similar in principle to Tasty.KAT and Tasty.Golden, but with different input selection processes. The intent is that there are multiple different test scenarios, which may all originate with the same input, and that all scenarios are specified by the presence of an "expected" result file along with optional support files.
A CUBE
object is provided to the findSugar
function
which returns an array of Sweets
that describe test
configurations.
The sugarOptions
should be added to the tasty Options
specification, and the sugarIngredients
provides additional
ingredients for the sugar testing (e.g. the ability to use
--showsearch and see the scan and identification of tests).
The withSugarGroups
function can be used to drive the test
invocations and group the Sweets
by parameter values.
Example:
import qualified Test.Tasty as T import Test.Tasty.Hunit ( testCase, (@?=) ) import Test.Tasty.Sugar import Numeric.Natural sugarCube = mkCUBE { inputDirs = [ "test/samples", "test/expected" ] , rootName = "*.c" , associatedNames = [ ("inputs", "inp") ] , expectedSuffix = "exp" } ingredients = T.includingOptions sugarOptions : sugarIngredients [sugarCube] <> T.defaultIngredients main = do testSweets <- findSugar sugarCube T.defaultMainWithIngredients ingredients . T.testGroup "sweet tests" =<< withSugarGroups testSweets T.testGroup mkTest mkTest :: Sweets -> Natural -> Expectation -> IO [T.TestTree] mkTest s n e = do exp <- reads <$> readFile $ expectedFile e return [ testCase (rootMatchName s <> " #" <> show n) $ do Just inpF <- lookup "inputs" $ associated e result <- testSomething inpF result @?= exp ]
See the README for more information.
Synopsis
- sugarOptions :: [OptionDescription]
- sugarIngredients :: [CUBE] -> [Ingredient]
- findSugar :: MonadIO m => CUBE -> m [Sweets]
- findSugarIn :: CUBE -> [CandidateFile] -> ([Sweets], Doc ann)
- withSugarGroups :: MonadIO m => [Sweets] -> (String -> [a] -> a) -> (Sweets -> Natural -> Expectation -> m [a]) -> m [a]
- data CUBE = CUBE {}
- type Separators = String
- type ParameterPattern = (String, Maybe [String])
- mkCUBE :: CUBE
- data CandidateFile = CandidateFile {}
- makeCandidate :: CUBE -> FilePath -> [String] -> FilePath -> CandidateFile
- findCandidates :: CUBE -> FilePath -> IO [Either String CandidateFile]
- data Sweets = Sweets {}
- data Expectation = Expectation {}
- type Association = (String, FilePath)
- type NamedParamMatch = (String, ParamMatch)
- data ParamMatch
- paramMatchVal :: String -> ParamMatch -> Bool
- getParamVal :: ParamMatch -> Maybe String
- sweetsKVITable :: [Sweets] -> KVITable FilePath
- sweetsTextTable :: [CUBE] -> [Sweets] -> Text
Tasty Options and Ingredients
sugarOptions :: [OptionDescription] Source #
Specify the Sugar-specific Tasty command-line options
sugarIngredients :: [CUBE] -> [Ingredient] Source #
Provides the Tasty Ingredients that can be used to inform the testing process.
Test Generation Functions
findSugar :: MonadIO m => CUBE -> m [Sweets] Source #
Returns a list of the discovered test configurations (Sweets) that should be run. This function is used to get the list of possible test configurations that is passed with the withSugarGroups function to generate the actual tests.
findSugarIn :: CUBE -> [CandidateFile] -> ([Sweets], Doc ann) Source #
Given a list of filepaths and a CUBE, returns the list of matching test Sweets that should be run, and an explanation of the search process (describing unmatched possibilities as well as valid test configurations).
This is a low-level function; the findSugar and withSugarGroups are the recommended interface functions to use for writing tests.
withSugarGroups :: MonadIO m => [Sweets] -> (String -> [a] -> a) -> (Sweets -> Natural -> Expectation -> m [a]) -> m [a] Source #
The withSugarGroups
is the primary function used to run tests.
Given a list of Sweets
returned by findSugar
, a function to
mark a group of tests (usually Tasty.testGroup
), and a function
to generate a number of tests from a Sweets
and a specific
Expectation
, this will iterate over the supplied Sweets
and
call the test generator for each valid test configuration.
Note that Sweets
contains all expectations ([Expectation]
), but
the passed Expectation
is the only one that should be tested for
this set of generated tests.
withSugarGroups sweets groupFun mkTestFun
where
groupFun
is the function to group a set of tests with a specific name. Typically this can just be 'tasty.testGroup'mkTestFun
is the function to create any specific tests for the specified expectation. The output type is usually a[
. This is passed the generalTestTree
]Sweets
, the specificExpectation
for the tests that should be created, and a numeric iteration indicating theExpectation
number within this group. The iteration number can be used for differentiation against the other tests, but there is no determinate relationship to elements of theSweets
(such as parameters or associated sets). It is also possible to suppress the generation of any tests for a particularExpectation
by returning an empty list from themkTestFun
.
Types
Input
Specifies the parameters and patterns to use when searching for
samples to build tests from. The mkCUBE
function should be used
to obtain a CUBE
structure initialized with overrideable
defaults.
The primary elements to specify are the rootName
and the
expectedSuffix
. With these two specifications (and possibly the
inputDirs
) the Sugar
functionality will be similar to
a "golden" testing package.
The validParams
is an optional feature that is useful when
multiple expected results files are generated from a single
rootName
, differing by the specified parameters.
The associatedNames
is an optional feature that is useful for
when there are other files to be associated with a test in addition
to the rootFile
and the expectedFile
.
CUBE | |
|
type Separators = String #
Separators for the path and suffix specifications. Any separator is accepted in any position between parameters and prior to the expected suffix. The synonym name is primarily used to indicate where this separators specification is intended to be used.
type ParameterPattern = (String, Maybe [String]) #
Parameters are specified by their name and a possible list of valid values. If there is no list of valid values, any value is accepted for that parameter position. Parameters are listed in the order that they should appear in the filenames to be matched.
Generates the default CUBE
configuration; callers should override
individual fields as appropriate. This is the preferred way to initialize a
CUBE if defaults are to be used for various fields:
- inputDirs: [ "test/samples" ]
- inputDir: "test/samples"
- separators: .-
- rootName: *
- expectedSuffix: exp
data CandidateFile #
Internally, this keeps the association between a possible file and the input directory it came from. The "file" portion is relative to the input directory.
CandidateFile | |
|
Instances
Show CandidateFile | |
Defined in Test.Tasty.Sugar.Types showsPrec :: Int -> CandidateFile -> ShowS # show :: CandidateFile -> String # showList :: [CandidateFile] -> ShowS # | |
Eq CandidateFile | |
Defined in Test.Tasty.Sugar.Types (==) :: CandidateFile -> CandidateFile -> Bool # (/=) :: CandidateFile -> CandidateFile -> Bool # |
makeCandidate :: CUBE -> FilePath -> [String] -> FilePath -> CandidateFile #
Create a CandidateFile entry for this top directory, sub-paths, and filename. In addition, any Explicit parameters with known values that appear in the filename are captured. Note that:
- There may be multiple possible matches for a single parameter (e.g. the value is repeated in the name or path, or an undefind value (Nothing) parameter could have multiple possible values extracted from the filename.
- File name matches are preferred over sub-path matches and will occlude the latter.
- All possible filename portions and sub-paths will be suggested for non-value
- parameters (validParams with Nothing).
findCandidates :: CUBE -> FilePath -> IO [Either String CandidateFile] #
Output
Each identified test input set is represented as a Sweets
object.. a Specifications With Existing Expected Testing Samples.
Sweets | |
|
data Expectation #
The Expectation
represents a valid test configuration based on
the set of provided files. The Expectation
consists of an
expected file which matches the rootFile
in the containing
Sweets
data object. The expectedFile
field is the name of the
file containing expected output, the expParamsMatch
field
specifies the ParameterPattern
matching values for this expected
file, and the associated
field provides a list of files
associated with this expected file.
Expectation | |
|
Instances
Show Expectation | |
Defined in Test.Tasty.Sugar.Types showsPrec :: Int -> Expectation -> ShowS # show :: Expectation -> String # showList :: [Expectation] -> ShowS # | |
Eq Expectation | Equality comparisons of two |
Defined in Test.Tasty.Sugar.Types (==) :: Expectation -> Expectation -> Bool # (/=) :: Expectation -> Expectation -> Bool # | |
Pretty Expectation | |
Defined in Test.Tasty.Sugar.Types pretty :: Expectation -> Doc ann # prettyList :: [Expectation] -> Doc ann # |
type Association = (String, FilePath) #
The Association
specifies the name of the associated file entry
and the actual filepath of that associated file.
type NamedParamMatch = (String, ParamMatch) #
The NamedParamMatch
specifies the parameter name and the
corresponding value for the expected file found. These can be
extracted from the name of the expected file and the set of
ParameterPattern
entries, but they are presented in an associated
list format for easy utilization by the invoked test target.
data ParamMatch #
Indicates the matching parameter value for this identified
expected test. If the parameter value is explicitly specified in
the expected filename, it is an Explicit
entry, otherwise it is
Assumed
(for each of the valid ParameterPattern
values) or
NotSpecified if there are no known ParameterPattern
values.
NotSpecified | This parameter value was not specified in the filename for the
expected file. In addition, the associated |
Assumed String | This parameter value was not specified in the filename of the
expected file, so the value is being synthetically supplied.
This is used for parameters that have known values but none is
present: an |
Explicit String | This parameter value was explicitly specified in the filename of the expected file. |
Instances
Show ParamMatch | |
Defined in Test.Tasty.Sugar.Types showsPrec :: Int -> ParamMatch -> ShowS # show :: ParamMatch -> String # showList :: [ParamMatch] -> ShowS # | |
Eq ParamMatch | |
Defined in Test.Tasty.Sugar.Types (==) :: ParamMatch -> ParamMatch -> Bool # (/=) :: ParamMatch -> ParamMatch -> Bool # | |
Ord ParamMatch | |
Defined in Test.Tasty.Sugar.Types compare :: ParamMatch -> ParamMatch -> Ordering # (<) :: ParamMatch -> ParamMatch -> Bool # (<=) :: ParamMatch -> ParamMatch -> Bool # (>) :: ParamMatch -> ParamMatch -> Bool # (>=) :: ParamMatch -> ParamMatch -> Bool # max :: ParamMatch -> ParamMatch -> ParamMatch # min :: ParamMatch -> ParamMatch -> ParamMatch # | |
Pretty ParamMatch | |
Defined in Test.Tasty.Sugar.Types pretty :: ParamMatch -> Doc ann # prettyList :: [ParamMatch] -> Doc ann # |
paramMatchVal :: String -> ParamMatch -> Bool #
The paramMatchVal
function is used to determine if a specific
value matches the corresponding ParamMatch
getParamVal :: ParamMatch -> Maybe String #
If there is a value associated with this parameter, return the value, regardless of whether it is Explicit or Assumed. A wildcard is a Nothing return.
Reporting
sweetsKVITable :: [Sweets] -> KVITable FilePath #
Converts a set of discovered Sweets into a KVITable; this is usually done in order to render the KVITable in a readable format.
sweetsTextTable :: [CUBE] -> [Sweets] -> Text #
Converts a set of discovered Sweets directly into a text-based table for shoing to the user.