Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Specifies the base tasty-sweet types and common class instance definitions for those types.
Synopsis
- type FileSuffix = String
- data CUBE = CUBE {}
- type ParameterPattern = (String, Maybe [String])
- type Separators = String
- mkCUBE :: CUBE
- prettyAssocNames :: [(String, String)] -> Maybe (Doc ann)
- prettyParamPatterns :: [ParameterPattern] -> Maybe (Doc ann)
- data CandidateFile = CandidateFile {}
- candidateToPath :: CandidateFile -> FilePath
- data Sweets = Sweets {}
- type Association = (String, FilePath)
- type NamedParamMatch = (String, ParamMatch)
- data Expectation = Expectation {}
- data ParamMatch
- paramMatchVal :: String -> ParamMatch -> Bool
- isExplicit :: ParamMatch -> Bool
- getExplicit :: ParamMatch -> Maybe String
- getParamVal :: ParamMatch -> Maybe String
- data SweetExplanation = SweetExpl {}
Documentation
type FileSuffix = String Source #
This is the type used to specify file suffixes. The synonym name is primarily used to indicate where this suffix specification is used.
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 ParameterPattern = (String, Maybe [String]) Source #
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.
type Separators = String Source #
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.
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
prettyAssocNames :: [(String, String)] -> Maybe (Doc ann) Source #
Pretty printing for a set of associated names
prettyParamPatterns :: [ParameterPattern] -> Maybe (Doc ann) Source #
Pretty printing for a list of parameter patterns
data CandidateFile Source #
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
Show CandidateFile Source # | |
Defined in Test.Tasty.Sugar.Types showsPrec :: Int -> CandidateFile -> ShowS # show :: CandidateFile -> String # showList :: [CandidateFile] -> ShowS # | |
Eq CandidateFile Source # | |
Defined in Test.Tasty.Sugar.Types (==) :: CandidateFile -> CandidateFile -> Bool # (/=) :: CandidateFile -> CandidateFile -> Bool # |
candidateToPath :: CandidateFile -> FilePath Source #
This converts a CandidatFile into a regular FilePath for access
Each identified test input set is represented as a Sweets
object.. a Specifications With Existing Expected Testing Samples.
Sweets | |
|
type Association = (String, FilePath) Source #
The Association
specifies the name of the associated file entry
and the actual filepath of that associated file.
type NamedParamMatch = (String, ParamMatch) Source #
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 Expectation Source #
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 Source # | |
Defined in Test.Tasty.Sugar.Types showsPrec :: Int -> Expectation -> ShowS # show :: Expectation -> String # showList :: [Expectation] -> ShowS # | |
Eq Expectation Source # | Equality comparisons of two |
Defined in Test.Tasty.Sugar.Types (==) :: Expectation -> Expectation -> Bool # (/=) :: Expectation -> Expectation -> Bool # | |
Pretty Expectation Source # | |
Defined in Test.Tasty.Sugar.Types pretty :: Expectation -> Doc ann # prettyList :: [Expectation] -> Doc ann # |
data ParamMatch Source #
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.
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 |
NotSpecified | This parameter value was not specified in the filename for the
expected file. In addition, the associated |
Instances
Show ParamMatch Source # | |
Defined in Test.Tasty.Sugar.Types showsPrec :: Int -> ParamMatch -> ShowS # show :: ParamMatch -> String # showList :: [ParamMatch] -> ShowS # | |
Eq ParamMatch Source # | |
Defined in Test.Tasty.Sugar.Types (==) :: ParamMatch -> ParamMatch -> Bool # (/=) :: ParamMatch -> ParamMatch -> Bool # | |
Ord ParamMatch Source # | |
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 Source # | |
Defined in Test.Tasty.Sugar.Types pretty :: ParamMatch -> Doc ann # prettyList :: [ParamMatch] -> Doc ann # |
paramMatchVal :: String -> ParamMatch -> Bool Source #
The paramMatchVal
function is used to determine if a specific
value matches the corresponding ParamMatch
isExplicit :: ParamMatch -> Bool Source #
Predicate test returning true for Explicit param values.
getExplicit :: ParamMatch -> Maybe String Source #
Extracts explicit value or Nothing
getParamVal :: ParamMatch -> Maybe String Source #
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.
data SweetExplanation Source #
The SweetExplanation
is the data type that contains the
description of the findSugar
process and
results.
Instances
Pretty SweetExplanation Source # | |
Defined in Test.Tasty.Sugar.Types pretty :: SweetExplanation -> Doc ann # prettyList :: [SweetExplanation] -> Doc ann # |