tasty-sugar-1.3.0.2: Tests defined by Search Using Golden Answer References
Safe HaskellSafe-Inferred
LanguageHaskell2010

Test.Tasty.Sugar

Description

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

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 [TestTree]. This is passed the general Sweets, the specific Expectation for the tests that should be created, and a numeric iteration indicating the Expectation 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 the Sweets (such as parameters or associated sets). It is also possible to suppress the generation of any tests for a particular Expectation by returning an empty list from the mkTestFun.

Types

Input

data CUBE #

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.

Constructors

CUBE 

Fields

  • inputDir :: FilePath

    The original directory in which the sample files can be found. This is provided for backward-compatibility, but the use of the inputDirs alternative is recommended.

  • inputDirs :: [FilePath]

    The directories in which the sample files that drive the testing exist. When specified as a relative filepath (suggested) then a directory is relative to the cabal file.

  • rootName :: GlobPattern

    The name of the "root" file for each test scenario. The contents of this file are opaque to 'tasty-sweet' and are interpreted by the tests themselves. Each "root" file is the kernel for a set of test cases.

    The root file should not be specified with any path element, it should exist in one of the inputDirs location and it can be specified as a glob pattern.

    The corresponding expected results files will be identified by finding files which match a portion of this name with a "{separator}{expectedSuffix}" appended to it.

  • expectedSuffix :: FileSuffix

    The expected suffix for a target pattern for running a test. There may be multiple files specifying expected results for a test (see the validParams below), but a particular test case is comprised of a source file along with a corresponding "expected result" file that is the name of the source file with the expectedSuffix suffix. The suffix should not contain any glob match characters. Note that the suffix is the text that comes after one of the separators below.

    The expectedSuffix *may* start with one of the characters in separators. If this occurs, then the suffix will only be considered if preceeded by that specific separator; otherwise any of the separators may be used prior to the expectedSuffix.

  • separators :: Separators

    The separators specify the characters which separate the expected suffix from the rootName, and which also separate the various parameters (if any, see validParams below). Any one of the separators in this list can be used, and a file can used a mixture of the separators in the filename.

    It is also valid to specify no separators, in which case the rootName and expectedSuffix are directly concatenated. This is not a typical usage, however.

    The default separators (returned by mkCUBE) are ".-" meaning that extensions (and parameters) can be separated from the base name by either a period or a dash.

  • associatedNames :: [(String, FileSuffix)]

    The associatedNames specifies other files that are associated with a particular test configuration. These files are optional and not all of them appear, but different suffixes may be associated here with a general name. When a test is being generated, any associatedNames that were found will be passed to the test generator for use as supplemental data.

    Specified as a list of tuples, where each tuple is the (arbitrary) name of the associated file type, and the file type suffix (with no period or other separator).

  • validParams :: [ParameterPattern]

    The validParams can be used to specify various parameters that may be present in the filename.

    For example, tests might be parameterized by which C compiler ("gcc" or "clang") was used, which target architecture ("x86_64" or "ppc" or "arm"), and which optimization level. The values for these parameters appear in any order in the filenames of any file (other than the rootName) delineated by any of the separators. Not all parameter values are required to appear.

    The following are valid examples:

    foo-gcc-ppc-O3.o
    foo-clang.x86_64.o
    foo.O0-clang.o

    The sugar matching code will attempt to identify the various parameter values appearing in the _EXPECTED_ filename which correspond to the same values in the _ROOT_ filename and provide that information to the test generation process to allow the generated test to be customized to the available set of parameters.

    The associatedNames provided to the test generator will be constrained to those associated names that match the parameter values explicit in the expected name, and called for each combination of unspecified parameter values present in associated names.

    There may actually be multiple sets of parameterized files for each rootName file: the test generator will be called for each set of parameters.

    Each entry in the validParams specifies the name of the parameter and the set of values; one (and only one) parameter may have existential values rather than pre-determined values, as indicated by a Nothing for the parameter value set. Valid parameter values are *not* matched with file globbing (they must be explicit and precise matches) and they cannot be blank (the lack of a parameter is handled automatically rather than an explicit blank value).

Instances

Instances details
Read CUBE 
Instance details

Defined in Test.Tasty.Sugar.Types

Show CUBE 
Instance details

Defined in Test.Tasty.Sugar.Types

Methods

showsPrec :: Int -> CUBE -> ShowS #

show :: CUBE -> String #

showList :: [CUBE] -> ShowS #

Pretty CUBE 
Instance details

Defined in Test.Tasty.Sugar.Types

Methods

pretty :: CUBE -> Doc ann #

prettyList :: [CUBE] -> Doc ann #

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.

mkCUBE :: CUBE #

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.

Instances

Instances details
Show CandidateFile 
Instance details

Defined in Test.Tasty.Sugar.Types

Eq CandidateFile 
Instance details

Defined in Test.Tasty.Sugar.Types

Output

data Sweets #

Each identified test input set is represented as a Sweets object.. a Specifications With Existing Expected Testing Samples.

Constructors

Sweets 

Fields

  • rootBaseName :: String

    The base of the root path for matching to expected. This has no path elements, no extensions and no parameters. It can be useful to use to compare to other fields in the expected Expectation list of this structure. Note that if the root file matched had parameters as part of the filename, those are not present in this rootBaseName.

  • rootMatchName :: String

    Matched root. This is the name of the matched file, (no path elements) that matched the rootName in the input CUBE. This includes any extension or parameter substitutions. This is often the best name to use for displaying this matched item.

  • rootFile :: FilePath

    The full actual filepath of the matched root, with all path elements, extensions, parameters, and suffixes present. This is most useful to open or otherwise access the file.

  • cubeParams :: [ParameterPattern]

    parameters for match

  • expected :: [Expectation]

    all expected files and associated

Instances

Instances details
Show Sweets 
Instance details

Defined in Test.Tasty.Sugar.Types

Eq Sweets 
Instance details

Defined in Test.Tasty.Sugar.Types

Methods

(==) :: Sweets -> Sweets -> Bool #

(/=) :: Sweets -> Sweets -> Bool #

Pretty Sweets 
Instance details

Defined in Test.Tasty.Sugar.Types

Methods

pretty :: Sweets -> Doc ann #

prettyList :: [Sweets] -> Doc ann #

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.

Constructors

Expectation 

Fields

Instances

Instances details
Show Expectation 
Instance details

Defined in Test.Tasty.Sugar.Types

Eq Expectation

Equality comparisons of two Expectation objects ignores the order of the expParamsMatch and associated fields.

Instance details

Defined in Test.Tasty.Sugar.Types

Pretty Expectation 
Instance details

Defined in Test.Tasty.Sugar.Types

Methods

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.

Constructors

Explicit String

This parameter value was explicitly specified in the filename of the expected file.

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 Expectation is created for each possible parameter value, identifying each as Assumed.

NotSpecified

This parameter value was not specified in the filename for the expected file. In addition, the associated ParameterPattern specified no defined values (i.e. Nothing), so it is not possible to identify any actual values. Instead, the Expectation generated for this expected file will supply this NotSpecified for this type of parameter.

Instances

Instances details
Show ParamMatch 
Instance details

Defined in Test.Tasty.Sugar.Types

Eq ParamMatch 
Instance details

Defined in Test.Tasty.Sugar.Types

Ord ParamMatch 
Instance details

Defined in Test.Tasty.Sugar.Types

Pretty ParamMatch 
Instance details

Defined in Test.Tasty.Sugar.Types

Methods

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.