Safe Haskell | None |
---|---|
Language | Haskell98 |
- type SnapTesting b a = StateT (Handler b b (), (Snaplet b, InitializerState b), OutputStream TestResult) IO a
- data TestResult
- data Sentiment a
- data TestResponse
- data SnapTestingConfig = SnapTestingConfig {
- reportGenerators :: [InputStream TestResult -> IO ()]
- defaultConfig :: SnapTestingConfig
- runSnapTests :: SnapTestingConfig -> Handler b b () -> SnapletInit b b -> SnapTesting b () -> IO ()
- consoleReport :: InputStream TestResult -> IO ()
- linuxDesktopReport :: InputStream TestResult -> IO ()
- name :: Text -> SnapTesting b () -> SnapTesting b ()
- should :: SnapTesting b TestResult -> SnapTesting b ()
- shouldNot :: SnapTesting b TestResult -> SnapTesting b ()
- css :: Applicative m => Text -> m CssSelector
- val :: Applicative m => a -> m a
- get :: Text -> SnapTesting b TestResponse
- get' :: Text -> Map ByteString [ByteString] -> SnapTesting b TestResponse
- post :: Text -> Map ByteString [ByteString] -> SnapTesting b TestResponse
- params :: [(ByteString, ByteString)] -> Map ByteString [ByteString]
- equal :: (Show a, Eq a) => a -> a -> TestResult
- beTrue :: Bool -> TestResult
- succeed :: TestResponse -> TestResult
- notfound :: TestResponse -> TestResult
- redirect :: TestResponse -> TestResult
- redirectTo :: TestResponse -> Text -> TestResult
- haveText :: TestResponse -> Text -> TestResult
- haveSelector :: TestResponse -> CssSelector -> TestResult
- changes :: (Show a, Eq a) => (a -> a) -> Handler b b a -> SnapTesting b c -> SnapTesting b ()
- data FormExpectations a
- = Value a
- | ErrorPaths [Text]
- form :: (Eq a, Show a) => FormExpectations a -> Form Text (Handler b b) a -> Map Text Text -> SnapTesting b ()
- cleanup :: Handler b b () -> SnapTesting b () -> SnapTesting b ()
- eval :: Handler b b a -> SnapTesting b a
- modifySite :: (Handler b b () -> Handler b b ()) -> SnapTesting b a -> SnapTesting b a
- quickCheck :: Testable prop => prop -> SnapTesting b ()
Types
type SnapTesting b a = StateT (Handler b b (), (Snaplet b, InitializerState b), OutputStream TestResult) IO a Source
The main type for this library, where b
is your application state,
often called App
. This is a State monad on top of IO, where the State carries
your application (or, more specifically, a top-level handler), and stream of test results
to be reported as passing or failing.
data TestResult Source
TestResult is a a flattened tree structure that reflects the structure of your tests, and is the data that is passed to report generators.
data TestResponse Source
A TestResponse is the result of making a request. Many predicates operate on these types of responses, and custom predicates can be written against them.
data SnapTestingConfig Source
The configuration that is passed to the test runner, currently just a list of report generators, that are each passed a stream of results, and can do any side effecting thing with them.
SnapTestingConfig | |
|
Configuration
defaultConfig :: SnapTestingConfig Source
The default configuration just prints results to the console, using the consoleReport
.
Running tests
:: SnapTestingConfig | Configuration for test runner |
-> Handler b b () | Site that requests are run against (often route routes, where routes are your sites routes). |
-> SnapletInit b b | Site initializer |
-> SnapTesting b () | Block of tests |
-> IO () |
Run a set of tests, putting the results through the specified report generators
consoleReport :: InputStream TestResult -> IO () Source
Prints test results to the console. For example:
/auth/new_user success PASSED creates a new account PASSED
linuxDesktopReport :: InputStream TestResult -> IO () Source
Sends the test results to desktop notifications on linux. Prints how many tests passed and failed.
Labeling
:: Text | Name of block |
-> SnapTesting b () | Block of tests |
-> SnapTesting b () |
Labels a block of tests with a descriptive name, to be used in report generation.
Applying Predicates
should :: SnapTesting b TestResult -> SnapTesting b () Source
This takes a TestResult and writes it to the test log, so it is processed by the report generators.
shouldNot :: SnapTesting b TestResult -> SnapTesting b () Source
This is similar to should
, but it asserts that the test should fail, and
inverts the corresponding message sentiment.
Helpers for running tests
css :: Applicative m => Text -> m CssSelector Source
Constructor for CSS selectors
val :: Applicative m => a -> m a Source
A constructor for pure values (this is just a synonym for pure
from Applicative
).
Getting Responses
:: Text | The url to request. |
-> Map ByteString [ByteString] | The parameters to send. |
-> SnapTesting b TestResponse |
Runs a GET request, with a set of parameters.
:: Text | The url to request. |
-> Map ByteString [ByteString] | The parameters to send. |
-> SnapTesting b TestResponse |
Creates a new POST request, with a set of parameters.
:: [(ByteString, ByteString)] | Pairs of parameter and value. |
-> Map ByteString [ByteString] |
A helper to construct parameters.
Predicates on values
equal :: (Show a, Eq a) => a -> a -> TestResult Source
Checks that the handler evaluates to the given value.
beTrue :: Bool -> TestResult Source
Helper to bring the results of other tests into the test suite.
Predicates on Responses
succeed :: TestResponse -> TestResult Source
Checks that the given request results in a success (200) code.
notfound :: TestResponse -> TestResult Source
Checks that the given request results in a not found (404) code.
redirect :: TestResponse -> TestResult Source
Checks that the given request results in a redirect (3**) code.
:: TestResponse | Request to run |
-> Text | URL it should redirect to |
-> TestResult |
Checks that the given request results in a redirect to a specific url.
haveText :: TestResponse -> Text -> TestResult Source
Asserts that a response (which should be Html) has given text.
haveSelector :: TestResponse -> CssSelector -> TestResult Source
Assert that a response (which should be Html) has a given selector.
Stateful value tests
:: (Show a, Eq a) | |
=> (a -> a) | Change function |
-> Handler b b a | Monadic value |
-> SnapTesting b c | Test block to run. |
-> SnapTesting b () |
Checks that the monadic value given changes by the function specified after the given test block is run.
For example, if you wanted to make sure that account creation was creating new accounts:
changes (+1) countAccounts (post "/auth/new_user" $ params [ ("new_user.name", "Jane") , ("new_user.email", "jdoe@c.com") , ("new_user.password", "foobar")])
Stateful form tests
data FormExpectations a Source
A data type for tests against forms.
Value a | The value the form should take (and should be valid) |
ErrorPaths [Text] | The error paths that should be populated |
:: (Eq a, Show a) | |
=> FormExpectations a | If the form should succeed, Value a is what it should produce. If failing, ErrorPaths should be all the errors that are triggered. |
-> Form Text (Handler b b) a | The form to run |
-> Map Text Text | The parameters to pass |
-> SnapTesting b () |
Test against digestive-functors forms.
Run actions after block
:: Handler b b () | Action to run after tests |
-> SnapTesting b () | Tests to run |
-> SnapTesting b () |
Runs an action after a block of tests, usually used to remove database state.
Evaluating arbitrary actions
Create helpers
:: (Handler b b () -> Handler b b ()) | Site modification function |
-> SnapTesting b a | Tests to run |
-> SnapTesting b a |
Given a site to site function (like, generating a random user and logging in), run the given block of test with the modified state.
Integrate with QuickCheck
quickCheck :: Testable prop => prop -> SnapTesting b () Source
Allows you to run a quickcheck test. All 100 test passing counts as a pass, any failure a failure. Currently the reporting is really bad (you don't see what the failing example is).