| Stability | unstable |
|---|---|
| Safe Haskell | None |
| Language | Haskell2010 |
Test.Hspec.Core.Spec
Description
This module provides access to Hspec's internals. It is less stable than
other parts of the API. For most users Test.Hspec is more suitable!
Synopsis
- it :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a)
- specify :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a)
- describe :: HasCallStack => String -> SpecWith a -> SpecWith a
- context :: HasCallStack => String -> SpecWith a -> SpecWith a
- pending :: HasCallStack => Expectation
- pendingWith :: HasCallStack => String -> Expectation
- xit :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a)
- xspecify :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a)
- xdescribe :: HasCallStack => String -> SpecWith a -> SpecWith a
- xcontext :: HasCallStack => String -> SpecWith a -> SpecWith a
- focus :: SpecWith a -> SpecWith a
- fit :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a)
- fspecify :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a)
- fdescribe :: HasCallStack => String -> SpecWith a -> SpecWith a
- fcontext :: HasCallStack => String -> SpecWith a -> SpecWith a
- parallel :: SpecWith a -> SpecWith a
- sequential :: SpecWith a -> SpecWith a
- type Spec = SpecWith ()
- type SpecWith a = SpecM a ()
- newtype SpecM a r = SpecM (WriterT (Endo Config, [SpecTree a]) (ReaderT Env IO) r)
- runSpecM :: SpecWith a -> IO (Endo Config, [SpecTree a])
- fromSpecList :: [SpecTree a] -> SpecWith a
- runIO :: IO r -> SpecM a r
- mapSpecForest :: ([SpecTree a] -> [SpecTree b]) -> SpecM a r -> SpecM b r
- mapSpecItem :: (ActionWith a -> ActionWith b) -> (Item a -> Item b) -> SpecWith a -> SpecWith b
- mapSpecItem_ :: (Item a -> Item b) -> SpecWith a -> SpecWith b
- modifyParams :: (Params -> Params) -> SpecWith a -> SpecWith a
- modifyConfig :: (Config -> Config) -> SpecWith a
- getSpecDescriptionPath :: SpecM a [String]
- class Example e where
- type Arg e
- evaluateExample :: e -> Params -> (ActionWith (Arg e) -> IO ()) -> ProgressCallback -> IO Result
- data Params = Params {}
- defaultParams :: Params
- type ActionWith a = a -> IO ()
- type Progress = (Int, Int)
- type ProgressCallback = Progress -> IO ()
- data Result = Result {}
- data ResultStatus
- data Location = Location {}
- data FailureReason
- safeEvaluate :: IO Result -> IO Result
- safeEvaluateExample :: Example e => e -> Params -> (ActionWith (Arg e) -> IO ()) -> ProgressCallback -> IO Result
- type SpecTree a = Tree (IO ()) (Item a)
- data Tree c a
- data Item a = Item {
- itemRequirement :: String
- itemLocation :: Maybe Location
- itemIsParallelizable :: Maybe Bool
- itemIsFocused :: Bool
- itemAnnotations :: Annotations
- itemExample :: Params -> (ActionWith a -> IO ()) -> ProgressCallback -> IO Result
- specGroup :: HasCallStack => String -> [SpecTree a] -> SpecTree a
- specItem :: (HasCallStack, Example e) => String -> e -> SpecTree (Arg e)
- bimapTree :: (a -> b) -> (c -> d) -> Tree a c -> Tree b d
- bimapForest :: (a -> b) -> (c -> d) -> [Tree a c] -> [Tree b d]
- filterTree :: (a -> Bool) -> Tree c a -> Maybe (Tree c a)
- filterForest :: (a -> Bool) -> [Tree c a] -> [Tree c a]
- filterTreeWithLabels :: ([String] -> a -> Bool) -> Tree c a -> Maybe (Tree c a)
- filterForestWithLabels :: ([String] -> a -> Bool) -> [Tree c a] -> [Tree c a]
- pruneTree :: Tree c a -> Maybe (Tree c a)
- pruneForest :: [Tree c a] -> [Tree c a]
- location :: HasCallStack => Maybe Location
- focusForest :: [SpecTree a] -> [SpecTree a]
- type HasCallStack = ?callStack :: CallStack
- type Expectation = Assertion
Defining a spec
it :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a) Source #
The it function creates a spec item.
A spec item consists of:
- a textual description of a desired behavior
- an example for that behavior
describe "absolute" $ do
it "returns a positive number when given a negative number" $
absolute (-1) == 1 optionally accepts an argument Example a, which is then given
to the test body. This is useful for provisioning resources for a test which
are created and cleaned up outside the test itself. See Arg aArg for details.
Note that this function is often on the scene of nasty type errors due to GHC failing
to infer the type of do notation in the test body.
It can be helpful to use
TypeApplications
to explicitly specify the intended Example type.
specify :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a) Source #
specify is an alias for it.
describe :: HasCallStack => String -> SpecWith a -> SpecWith a Source #
The describe function combines a list of specs into a larger spec.
context :: HasCallStack => String -> SpecWith a -> SpecWith a Source #
context is an alias for describe.
pending :: HasCallStack => Expectation Source #
pending can be used to mark a spec item as pending.
If you want to textually specify a behavior but do not have an example yet, use this:
describe "fancyFormatter" $ do
it "can format text in a way that everyone likes" $
pendingpendingWith :: HasCallStack => String -> Expectation Source #
pendingWith is similar to pending, but it takes an additional string
argument that can be used to specify the reason for why the spec item is pending.
xspecify :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a) Source #
xspecify is an alias for xit.
xcontext :: HasCallStack => String -> SpecWith a -> SpecWith a Source #
xcontext is an alias for xdescribe.
Focused spec items
During a test run, when a spec contains focused spec items, all other spec items are ignored.
fit :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a) Source #
fit is an alias for fmap focus . it
fspecify :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a) Source #
fspecify is an alias for fit.
fdescribe :: HasCallStack => String -> SpecWith a -> SpecWith a Source #
fdescribe is an alias for fmap focus . describe
fcontext :: HasCallStack => String -> SpecWith a -> SpecWith a Source #
fcontext is an alias for fdescribe.
parallel :: SpecWith a -> SpecWith a Source #
parallel marks all spec items of the given spec to be safe for parallel
evaluation.
sequential :: SpecWith a -> SpecWith a Source #
sequential marks all spec items of the given spec to be evaluated sequentially.
The SpecM monad
type SpecWith a = SpecM a () Source #
A represents a test or group of tests that require an SpecWith aa
value to run.
In the common case, a Spec is a which requires SpecWith ()() and
can thus be executed with hspec.
To supply an argument to SpecWith tests to turn them into Spec, use
functions from Test.Hspec.Core.Hooks such as
around, before,
mapSubject and similar.
Values of this type are created by it,
describe and similar.
A writer monad for SpecTree forests.
This is used by describe and is used
to construct the forest of spec items.
It allows for dynamically generated spec trees, for example, by using data
obtained by performing IO actions with runIO.
runIO :: IO r -> SpecM a r Source #
Run an IO action while constructing the spec tree.
SpecM is a monad to construct a spec tree, without executing any spec
items itself. runIO allows you to run IO actions during this construction phase.
The IO action is always run when the spec tree is constructed (e.g. even
when --dry-run is specified).
If you do not need the result of the IO action to construct the spec tree,
beforeAll may be more suitable for your use case.
mapSpecItem :: (ActionWith a -> ActionWith b) -> (Item a -> Item b) -> SpecWith a -> SpecWith b Source #
Deprecated: Use mapSpecItem_ instead.
getSpecDescriptionPath :: SpecM a [String] Source #
Get the path of describe labels, from the root all the way in to the
call-site of this function.
Example
>>>:{runSpecM $ do describe "foo" $ do describe "bar" $ do getSpecDescriptionPath >>= runIO . print :} ["foo","bar"]
Since: 2.10.0
A type class for examples
class Example e where Source #
A type class for examples, that is to say, test bodies as used in
it and similar functions.
Associated Types
The argument type that is needed to run this Example.
If Arg is (), no argument is required and the Example can be run
as-is.
The value of Arg is the difference between Spec
(aka ), which can be executed, and
SpecWith (), which cannot be executed without
turning it into SpecWith aSpec first.
To supply an argument to examples, use the functions in
Test.Hspec.Core.Hooks such as around,
before, mapSubject and
similar.
type Arg e = ()
Methods
Arguments
| :: e | The example being evaluated |
| -> Params | QuickCheck/SmallCheck settings |
| -> (ActionWith (Arg e) -> IO ()) | Hook: takes an This is used to implement |
| -> ProgressCallback | Callback for composite tests like QuickCheck to report their progress. |
| -> IO Result |
Evaluates an example.
evaluateExample is expected to execute the test body inside the IO action
passed to the hook. It's often necessary to use an IORef to pass data
out like whether the test succeeded to the outer IO action so it can be
returned as a Result.
Example:
newtype MyAction = MyAction (Int -> IO Bool)
instance Example MyAction where
type Arg MyAction = Int
evaluateExample (MyAction act) _params hook _progress = do
result <- newIORef (Result "" Success)
hook $ arg -> do
-- e.g. determines if arg is 42
ok <- act arg
let result' = Result "" $ if ok then Success else Failure Nothing NoReason
writeIORef result result'
readIORef result
Instances
QuickCheck and SmallCheck related parameters.
Constructors
| Params | |
Fields | |
type ActionWith a = a -> IO () Source #
type ProgressCallback = Progress -> IO () Source #
Callback used by composite test items that contain many tests to report their progress towards finishing them all.
This is used, for example, to report how many QuickCheck examples are finished.
The result of running an example
Constructors
| Result | |
Fields | |
Instances
| Show Result Source # | |||||
| Example Result Source # | |||||
Defined in Test.Hspec.Core.Example Associated Types
Methods evaluateExample :: Result -> Params -> (ActionWith (Arg Result) -> IO ()) -> ProgressCallback -> IO Result Source # | |||||
| Example (a -> Result) Source # | |||||
Defined in Test.Hspec.Core.Example Associated Types
Methods evaluateExample :: (a -> Result) -> Params -> (ActionWith (Arg (a -> Result)) -> IO ()) -> ProgressCallback -> IO Result Source # | |||||
| type Arg Result Source # | |||||
Defined in Test.Hspec.Core.Example | |||||
| type Arg (a -> Result) Source # | |||||
Defined in Test.Hspec.Core.Example | |||||
data ResultStatus Source #
Instances
| Exception ResultStatus Source # | |
Defined in Test.Hspec.Core.Example Methods toException :: ResultStatus -> SomeException # fromException :: SomeException -> Maybe ResultStatus # displayException :: ResultStatus -> String # | |
| Show ResultStatus Source # | |
Defined in Test.Hspec.Core.Example Methods showsPrec :: Int -> ResultStatus -> ShowS # show :: ResultStatus -> String # showList :: [ResultStatus] -> ShowS # | |
Location is used to represent source locations.
Constructors
| Location | |
Fields
| |
data FailureReason Source #
Constructors
| NoReason | |
| Reason String | |
| ColorizedReason String | |
| ExpectedButGot (Maybe String) String String | |
| Error (Maybe String) SomeException |
Instances
| Show FailureReason Source # | |
Defined in Test.Hspec.Core.Example Methods showsPrec :: Int -> FailureReason -> ShowS # show :: FailureReason -> String # showList :: [FailureReason] -> ShowS # | |
| NFData FailureReason Source # | |
Defined in Test.Hspec.Core.Example Methods rnf :: FailureReason -> () # | |
safeEvaluateExample :: Example e => e -> Params -> (ActionWith (Arg e) -> IO ()) -> ProgressCallback -> IO Result Source #
Internal representation of a spec tree
type SpecTree a = Tree (IO ()) (Item a) Source #
A tree is used to represent a spec internally. The tree is parameterized over the type of cleanup actions and the type of the actual spec items.
Internal tree data structure
Instances
| Foldable (Tree c) Source # | |
Defined in Test.Hspec.Core.Tree Methods fold :: Monoid m => Tree c m -> m # foldMap :: Monoid m => (a -> m) -> Tree c a -> m # foldMap' :: Monoid m => (a -> m) -> Tree c a -> m # foldr :: (a -> b -> b) -> b -> Tree c a -> b # foldr' :: (a -> b -> b) -> b -> Tree c a -> b # foldl :: (b -> a -> b) -> b -> Tree c a -> b # foldl' :: (b -> a -> b) -> b -> Tree c a -> b # foldr1 :: (a -> a -> a) -> Tree c a -> a # foldl1 :: (a -> a -> a) -> Tree c a -> a # elem :: Eq a => a -> Tree c a -> Bool # maximum :: Ord a => Tree c a -> a # minimum :: Ord a => Tree c a -> a # | |
| Traversable (Tree c) Source # | |
| Functor (Tree c) Source # | |
| (Show c, Show a) => Show (Tree c a) Source # | |
| (Eq c, Eq a) => Eq (Tree c a) Source # | |
Item is used to represent spec items internally. A spec item consists of:
- a textual description of a desired behavior
- an example for that behavior
- additional meta information
Everything that is an instance of the Example type class can be used as an
example, including QuickCheck properties, Hspec expectations and HUnit
assertions.
Constructors
| Item | |
Fields
| |
specGroup :: HasCallStack => String -> [SpecTree a] -> SpecTree a Source #
The specGroup function combines a list of specs into a larger spec.
specItem :: (HasCallStack, Example e) => String -> e -> SpecTree (Arg e) Source #
The specItem function creates a spec item.
bimapForest :: (a -> b) -> (c -> d) -> [Tree a c] -> [Tree b d] Source #
pruneForest :: [Tree c a] -> [Tree c a] Source #
focusForest :: [SpecTree a] -> [SpecTree a] Source #
Marks an entire spec forest as focused if nothing in it is already focused.
Re-exports
type HasCallStack = ?callStack :: CallStack #
Request a CallStack.
NOTE: The implicit parameter ?callStack :: CallStack is an
implementation detail and should not be considered part of the
CallStack API, we may decide to change the implementation in the
future.
Since: base-4.9.0.0
type Expectation = Assertion #