| Copyright | 2018 Automattic Inc. |
|---|---|
| License | GPL-3 |
| Maintainer | Nathan Bloomfield (nbloomf@gmail.com) |
| Stability | experimental |
| Portability | POSIX |
| Safe Haskell | Safe |
| Language | Haskell2010 |
Web.Api.WebDriver.Assert
Description
In this module we define assertions as first class objects and some helper functions for creating and manipulating them.
Synopsis
- data Assertion
- success :: AssertionStatement -> AssertionComment -> Assertion
- failure :: AssertionStatement -> AssertionComment -> Assertion
- newtype AssertionStatement = AssertionStatement {}
- newtype AssertionComment = AssertionComment {}
- data AssertionResult
- isSuccess :: Assertion -> Bool
- printAssertion :: Assertion -> String
- class Assert m where
- data AssertionSummary = AssertionSummary {
- numSuccesses :: Integer
- numFailures :: Integer
- failures :: [Assertion]
- successes :: [Assertion]
- summarize :: [Assertion] -> AssertionSummary
- summarizeAll :: [AssertionSummary] -> AssertionSummary
- printSummary :: AssertionSummary -> IO ()
- assertSuccessIf :: (Monad m, Assert m) => Bool -> AssertionStatement -> AssertionComment -> m ()
- assertSuccess :: (Monad m, Assert m) => AssertionComment -> m ()
- assertFailure :: (Monad m, Assert m) => AssertionComment -> m ()
- assertTrue :: (Monad m, Assert m) => Bool -> AssertionComment -> m ()
- assertFalse :: (Monad m, Assert m) => Bool -> AssertionComment -> m ()
- assertEqual :: (Monad m, Assert m, Eq t, Show t) => t -> t -> AssertionComment -> m ()
- assertNotEqual :: (Monad m, Assert m, Eq t, Show t) => t -> t -> AssertionComment -> m ()
- assertIsSubstring :: (Monad m, Assert m, Eq a, Show a) => [a] -> [a] -> AssertionComment -> m ()
- assertIsNotSubstring :: (Monad m, Assert m, Eq a, Show a) => [a] -> [a] -> AssertionComment -> m ()
- assertIsNamedSubstring :: (Monad m, Assert m, Eq a, Show a) => [a] -> ([a], String) -> AssertionComment -> m ()
- assertIsNotNamedSubstring :: (Monad m, Assert m, Eq a, Show a) => [a] -> ([a], String) -> AssertionComment -> m ()
Assertions
An Assertion consists of the following:
- A human-readable statement being asserted, which may be either true or false.
- A result (either success or failure).
- A comment, representing why the assertion was made, to assist in debugging.
To construct assertions outside this module, use success and failure.
Arguments
| :: AssertionStatement | Statement being asserted (the what) |
| -> AssertionComment | An additional comment (the why) |
| -> Assertion |
Construct a successful assertion.
Arguments
| :: AssertionStatement | Statement being asserted (the what) |
| -> AssertionComment | An additional comment (the why) |
| -> Assertion |
Construct a failed assertion.
newtype AssertionStatement Source #
Human-readable statement which may be true or false.
Constructors
| AssertionStatement | |
Fields | |
Instances
| Eq AssertionStatement Source # | |
Defined in Web.Api.WebDriver.Assert Methods (==) :: AssertionStatement -> AssertionStatement -> Bool # (/=) :: AssertionStatement -> AssertionStatement -> Bool # | |
| Show AssertionStatement Source # | |
Defined in Web.Api.WebDriver.Assert Methods showsPrec :: Int -> AssertionStatement -> ShowS # show :: AssertionStatement -> String # showList :: [AssertionStatement] -> ShowS # | |
| IsString AssertionStatement Source # | |
Defined in Web.Api.WebDriver.Assert Methods fromString :: String -> AssertionStatement # | |
| Arbitrary AssertionStatement Source # | |
Defined in Web.Api.WebDriver.Assert | |
newtype AssertionComment Source #
Human-readable explanation for why an assertion is made.
Constructors
| AssertionComment | |
Fields | |
Instances
| Eq AssertionComment Source # | |
Defined in Web.Api.WebDriver.Assert Methods (==) :: AssertionComment -> AssertionComment -> Bool # (/=) :: AssertionComment -> AssertionComment -> Bool # | |
| Show AssertionComment Source # | |
Defined in Web.Api.WebDriver.Assert Methods showsPrec :: Int -> AssertionComment -> ShowS # show :: AssertionComment -> String # showList :: [AssertionComment] -> ShowS # | |
| IsString AssertionComment Source # | |
Defined in Web.Api.WebDriver.Assert Methods fromString :: String -> AssertionComment # | |
| Arbitrary AssertionComment Source # | |
Defined in Web.Api.WebDriver.Assert | |
data AssertionResult Source #
Type representing the result (success or failure) of an evaluated assertion.
Instances
| Eq AssertionResult Source # | |
Defined in Web.Api.WebDriver.Assert Methods (==) :: AssertionResult -> AssertionResult -> Bool # (/=) :: AssertionResult -> AssertionResult -> Bool # | |
| Show AssertionResult Source # | |
Defined in Web.Api.WebDriver.Assert Methods showsPrec :: Int -> AssertionResult -> ShowS # show :: AssertionResult -> String # showList :: [AssertionResult] -> ShowS # | |
| Arbitrary AssertionResult Source # | |
Defined in Web.Api.WebDriver.Assert | |
printAssertion :: Assertion -> String Source #
Basic string representation of an assertion.
The Assert Class
Assertions are made and evaluated inside some context, represented by the Assert class.
Methods
assert :: Assertion -> m () Source #
Make an assertion. Typically m is a monad, and the Assert instance handles the assertion in m by e.g. logging it, changing state, etc.
Instances
| (Monad eff, Monad (t eff), MonadTrans t) => Assert (WebDriverTT t eff) Source # | |
Defined in Web.Api.WebDriver.Monad Methods assert :: Assertion -> WebDriverTT t eff () Source # | |
Assertion Summaries
data AssertionSummary Source #
Assertions are the most granular kind of "test" this library deals with. Typically we'll be interested in sets of many assertions. A single test case will include one or more assertions, which for reporting purposes we'd like to summarize. The summary for a list of assertions will include the number of successes, the number of failures, and the actual failures. Modeled this way assertion summaries form a monoid, which is handy.
Constructors
| AssertionSummary | |
Fields
| |
Instances
| Eq AssertionSummary Source # | |
Defined in Web.Api.WebDriver.Assert Methods (==) :: AssertionSummary -> AssertionSummary -> Bool # (/=) :: AssertionSummary -> AssertionSummary -> Bool # | |
| Show AssertionSummary Source # | |
Defined in Web.Api.WebDriver.Assert Methods showsPrec :: Int -> AssertionSummary -> ShowS # show :: AssertionSummary -> String # showList :: [AssertionSummary] -> ShowS # | |
| Semigroup AssertionSummary Source # | |
Defined in Web.Api.WebDriver.Assert Methods (<>) :: AssertionSummary -> AssertionSummary -> AssertionSummary # sconcat :: NonEmpty AssertionSummary -> AssertionSummary # stimes :: Integral b => b -> AssertionSummary -> AssertionSummary # | |
| Monoid AssertionSummary Source # | |
Defined in Web.Api.WebDriver.Assert Methods mappend :: AssertionSummary -> AssertionSummary -> AssertionSummary # mconcat :: [AssertionSummary] -> AssertionSummary # | |
summarizeAll :: [AssertionSummary] -> AssertionSummary Source #
Summarize a list of AssertionSummarys.
printSummary :: AssertionSummary -> IO () Source #
Very basic string representation of an AssertionSummary.
Basic Assertions
Arguments
| :: (Monad m, Assert m) | |
| => Bool | |
| -> AssertionStatement | Statement being asserted (the what) |
| -> AssertionComment | An additional comment (the why) |
| -> m () |
Generic boolean assertion; asserts success if Bool is true and failure otherwise.
Arguments
| :: (Monad m, Assert m) | |
| => AssertionComment | An additional comment (the why) |
| -> m () |
Assertion that always succeeds.
Arguments
| :: (Monad m, Assert m) | |
| => AssertionComment | An additional comment (the why) |
| -> m () |
Assertion that always fails.
Arguments
| :: (Monad m, Assert m) | |
| => Bool | |
| -> AssertionComment | An additional comment (the why) |
| -> m () |
Succeeds if Bool is True.
Arguments
| :: (Monad m, Assert m) | |
| => Bool | |
| -> AssertionComment | An additional comment (the why) |
| -> m () |
Succeeds if Bool is False.
Arguments
| :: (Monad m, Assert m, Eq t, Show t) | |
| => t | |
| -> t | |
| -> AssertionComment | An additional comment (the why) |
| -> m () |
Succeeds if the given ts are equal according to their Eq instance.
Arguments
| :: (Monad m, Assert m, Eq t, Show t) | |
| => t | |
| -> t | |
| -> AssertionComment | An additional comment (the why) |
| -> m () |
Succeeds if the given ts are not equal according to their Eq instance.
Arguments
| :: (Monad m, Assert m, Eq a, Show a) | |
| => [a] | |
| -> [a] | |
| -> AssertionComment | An additional comment (the why) |
| -> m () |
Succeeds if the first list is an infix of the second, according to their Eq instance.
Arguments
| :: (Monad m, Assert m, Eq a, Show a) | |
| => [a] | |
| -> [a] | |
| -> AssertionComment | An additional comment (the why) |
| -> m () |
Succeeds if the first list is not an infix of the second, according to their Eq instance.
assertIsNamedSubstring Source #
Arguments
| :: (Monad m, Assert m, Eq a, Show a) | |
| => [a] | |
| -> ([a], String) | |
| -> AssertionComment | An additional comment (the why) |
| -> m () |
Succeeds if the first list is an infix of the second, named list, according to their Eq instance. This is similar to assertIsSubstring, except that the "name" of the second list argument is used in reporting failures. Handy if the second list is very large -- say the source of a webpage.
assertIsNotNamedSubstring Source #
Arguments
| :: (Monad m, Assert m, Eq a, Show a) | |
| => [a] | |
| -> ([a], String) | |
| -> AssertionComment | An additional comment (the why) |
| -> m () |
Succeeds if the first list is not an infix of the second, named list, according to their Eq instance. This is similar to assertIsNotSubstring, except that the "name" of the second list argument is used in reporting failures. Handy if the second list is very large -- say the source of a webpage.