webdriver-w3c-0.0.2: Bindings to the WebDriver API

Copyright2018 Automattic Inc.
LicenseGPL-3
MaintainerNathan Bloomfield (nbloomf@gmail.com)
Stabilityexperimental
PortabilityPOSIX
Safe HaskellSafe
LanguageHaskell2010

Web.Api.WebDriver.Assert

Contents

Description

In this module we define assertions as first class objects and some helper functions for creating and manipulating them.

Synopsis

Assertions

data Assertion Source #

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.

Instances
Eq Assertion Source # 
Instance details

Defined in Web.Api.WebDriver.Assert

Show Assertion Source # 
Instance details

Defined in Web.Api.WebDriver.Assert

success Source #

Arguments

:: AssertionStatement

Statement being asserted (the what)

-> AssertionComment

An additional comment (the why)

-> Assertion 

Construct a successful assertion.

failure Source #

Arguments

:: AssertionStatement

Statement being asserted (the what)

-> AssertionComment

An additional comment (the why)

-> Assertion 

Construct a failed assertion.

data AssertionResult Source #

Type representing the result (success or failure) of an evaluated assertion.

isSuccess :: Assertion -> Bool Source #

Detects successful assertions.

printAssertion :: Assertion -> String Source #

Basic string representation of an assertion.

The Assert Class

class Assert m where Source #

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 # 
Instance details

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.

summarize :: [Assertion] -> AssertionSummary Source #

Summarize a list of Assertions.

printSummary :: AssertionSummary -> IO () Source #

Very basic string representation of an AssertionSummary.

Basic Assertions

assertSuccessIf Source #

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.

assertSuccess Source #

Arguments

:: (Monad m, Assert m) 
=> AssertionComment

An additional comment (the why)

-> m () 

Assertion that always succeeds.

assertFailure Source #

Arguments

:: (Monad m, Assert m) 
=> AssertionComment

An additional comment (the why)

-> m () 

Assertion that always fails.

assertTrue Source #

Arguments

:: (Monad m, Assert m) 
=> Bool 
-> AssertionComment

An additional comment (the why)

-> m () 

Succeeds if Bool is True.

assertFalse Source #

Arguments

:: (Monad m, Assert m) 
=> Bool 
-> AssertionComment

An additional comment (the why)

-> m () 

Succeeds if Bool is False.

assertEqual Source #

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.

assertNotEqual Source #

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.

assertIsSubstring Source #

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.

assertIsNotSubstring Source #

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.