Safe Haskell | None |
---|---|
Language | Haskell98 |
Synopsis
- snap :: Handler b b () -> SnapletInit b b -> SpecWith (SnapHspecState b) -> Spec
- modifySite :: (Handler b b () -> Handler b b ()) -> SpecWith (SnapHspecState b) -> SpecWith (SnapHspecState b)
- modifySite' :: (Handler b b () -> Handler b b ()) -> SnapHspecM b a -> SnapHspecM b a
- afterEval :: Handler b b () -> SpecWith (SnapHspecState b) -> SpecWith (SnapHspecState b)
- beforeEval :: Handler b b () -> SpecWith (SnapHspecState b) -> SpecWith (SnapHspecState b)
- data TestResponse
- newtype RespCode = RespCode Int
- type SnapHspecM b = StateT (SnapHspecState b) IO
- class Factory b a d | a -> b, a -> d, d -> a where
- fields :: d
- save :: d -> SnapHspecM b a
- create :: (d -> d) -> SnapHspecM b a
- reload :: a -> SnapHspecM b a
- delete :: Text -> SnapHspecM b TestResponse
- get :: Text -> SnapHspecM b TestResponse
- get' :: Text -> Params -> SnapHspecM b TestResponse
- post :: Text -> Params -> SnapHspecM b TestResponse
- postJson :: ToJSON tj => Text -> tj -> SnapHspecM b TestResponse
- put :: Text -> Params -> SnapHspecM b TestResponse
- put' :: Text -> Text -> Params -> SnapHspecM b TestResponse
- params :: [(ByteString, ByteString)] -> Params
- restrictResponse :: Text -> TestResponse -> TestResponse
- recordSession :: HasSession b => SnapHspecM b a -> SnapHspecM b a
- class HasSession b where
- sessionShouldContain :: Text -> SnapHspecM b ()
- sessionShouldNotContain :: Text -> SnapHspecM b ()
- eval :: Handler b b a -> SnapHspecM b a
- shouldChange :: (Show a, Eq a) => (a -> a) -> Handler b b a -> SnapHspecM b c -> SnapHspecM b ()
- shouldEqual :: (Show a, Eq a) => a -> a -> SnapHspecM b ()
- shouldNotEqual :: (Show a, Eq a) => a -> a -> SnapHspecM b ()
- shouldBeTrue :: Bool -> SnapHspecM b ()
- shouldNotBeTrue :: Bool -> SnapHspecM b ()
- should200 :: TestResponse -> SnapHspecM b ()
- shouldNot200 :: TestResponse -> SnapHspecM b ()
- should404 :: TestResponse -> SnapHspecM b ()
- shouldNot404 :: TestResponse -> SnapHspecM b ()
- should300 :: TestResponse -> SnapHspecM b ()
- shouldNot300 :: TestResponse -> SnapHspecM b ()
- should300To :: Text -> TestResponse -> SnapHspecM b ()
- shouldNot300To :: Text -> TestResponse -> SnapHspecM b ()
- shouldHaveSelector :: Text -> TestResponse -> SnapHspecM b ()
- shouldNotHaveSelector :: Text -> TestResponse -> SnapHspecM b ()
- shouldHaveText :: Text -> TestResponse -> SnapHspecM b ()
- shouldNotHaveText :: Text -> TestResponse -> SnapHspecM b ()
- data FormExpectations a
- = Value a
- | Predicate (a -> Bool)
- | ErrorPaths [Text]
- form :: (Eq a, Show a) => FormExpectations a -> Form Text (Handler b b) a -> Map Text Text -> SnapHspecM b ()
- data SnapHspecState b = SnapHspecState ResultStatus (Handler b b ()) (Snaplet b) (InitializerState b) (MVar [(Text, Text)]) (Handler b b ()) (Handler b b ())
- setResult :: ResultStatus -> SnapHspecM b ()
- runRequest :: RequestBuilder IO () -> SnapHspecM b TestResponse
- runHandlerSafe :: RequestBuilder IO () -> Handler b b v -> Snaplet b -> InitializerState b -> IO (Either Text Response)
- evalHandlerSafe :: Handler b b v -> Snaplet b -> InitializerState b -> IO (Either Text v)
Running blocks of hspec-snap tests
snap :: Handler b b () -> SnapletInit b b -> SpecWith (SnapHspecState b) -> Spec Source #
The way to run a block of SnapHspecM
tests within an hspec
test suite. This takes both the top level handler (usually `route
routes`, where routes
are all the routes for your site) and the
site initializer (often named app
), and a block of tests. A test
suite can have multiple calls to snap
, though each one will cause
the site initializer to run, which is often a slow operation (and
will slow down test suites).
modifySite :: (Handler b b () -> Handler b b ()) -> SpecWith (SnapHspecState b) -> SpecWith (SnapHspecState b) Source #
This allows you to change the default handler you are running requests against within a block. This is most likely useful for setting request state (for example, logging a user in).
modifySite' :: (Handler b b () -> Handler b b ()) -> SnapHspecM b a -> SnapHspecM b a Source #
This performs a similar operation to modifySite
but in the context
of SnapHspecM
(which is needed if you need to eval
, produce values, and
hand them somewhere else (so they can't be created within f
).
afterEval :: Handler b b () -> SpecWith (SnapHspecState b) -> SpecWith (SnapHspecState b) Source #
Evaluate a Handler action after each test.
beforeEval :: Handler b b () -> SpecWith (SnapHspecState b) -> SpecWith (SnapHspecState b) Source #
Evaluate a Handler action before each test.
Core data types
data TestResponse Source #
The result of making requests against your application. Most
assertions act against these types (for example, should200
,
shouldHaveSelector
, etc).
Instances
Eq TestResponse Source # | |
Defined in Test.Hspec.Snap (==) :: TestResponse -> TestResponse -> Bool # (/=) :: TestResponse -> TestResponse -> Bool # | |
Show TestResponse Source # | |
Defined in Test.Hspec.Snap showsPrec :: Int -> TestResponse -> ShowS # show :: TestResponse -> String # showList :: [TestResponse] -> ShowS # |
type SnapHspecM b = StateT (SnapHspecState b) IO Source #
The main monad that tests run inside of. This allows both access
to the application (via requests and eval
) and to running
assertions (like should404
or shouldHaveText
).
Factory style test data generation
class Factory b a d | a -> b, a -> d, d -> a where Source #
Factory instances allow you to easily generate test data.
Essentially, you specify a default way of constructing a
data type, and allow certain parts of it to be modified (via
the fields
data structure).
An example follows:
data Foo = Foo Int newtype FooFields = FooFields (IO Int) instance Factory App Foo FooFields where fields = FooFields randomIO save f = liftIO f >>= saveFoo . Foo1 main = do create id :: SnapHspecM App Foo create (const $ FooFields (return 1)) :: SnapHspecM App Foo
save :: d -> SnapHspecM b a Source #
create :: (d -> d) -> SnapHspecM b a Source #
reload :: a -> SnapHspecM b a Source #
Requests
delete :: Text -> SnapHspecM b TestResponse Source #
Runs a DELETE request
get :: Text -> SnapHspecM b TestResponse Source #
Runs a GET request.
get' :: Text -> Params -> SnapHspecM b TestResponse Source #
Runs a GET request, with a set of parameters.
post :: Text -> Params -> SnapHspecM b TestResponse Source #
Creates a new POST request, with a set of parameters.
postJson :: ToJSON tj => Text -> tj -> SnapHspecM b TestResponse Source #
Creates a new POST request with a given JSON value as the request body.
put :: Text -> Params -> SnapHspecM b TestResponse Source #
Creates a new PUT request, with a set of parameters, with a default type of "application/x-www-form-urlencoded"
put' :: Text -> Text -> Params -> SnapHspecM b TestResponse Source #
Creates a new PUT request with a configurable MIME/type
:: [(ByteString, ByteString)] | Pairs of parameter and value. |
-> Params |
A helper to construct parameters.
Helpers for dealing with TestResponses
restrictResponse :: Text -> TestResponse -> TestResponse Source #
Restricts a response to matches for a given CSS selector. Does nothing to non-Html responses.
Dealing with session state (EXPERIMENTAL)
recordSession :: HasSession b => SnapHspecM b a -> SnapHspecM b a Source #
class HasSession b where Source #
sessionShouldContain :: Text -> SnapHspecM b () Source #
sessionShouldNotContain :: Text -> SnapHspecM b () Source #
Evaluating application code
eval :: Handler b b a -> SnapHspecM b a Source #
Runs an arbitrary stateful action from your application.
Unit test assertions
shouldChange :: (Show a, Eq a) => (a -> a) -> Handler b b a -> SnapHspecM b c -> SnapHspecM b () Source #
Asserts that a given stateful action will produce a specific different result after an action has been run.
shouldEqual :: (Show a, Eq a) => a -> a -> SnapHspecM b () Source #
Asserts that two values are equal.
shouldNotEqual :: (Show a, Eq a) => a -> a -> SnapHspecM b () Source #
Asserts that two values are not equal.
shouldBeTrue :: Bool -> SnapHspecM b () Source #
Asserts that the value is True.
shouldNotBeTrue :: Bool -> SnapHspecM b () Source #
Asserts that the value is not True (otherwise known as False).
Response assertions
should200 :: TestResponse -> SnapHspecM b () Source #
Asserts that the response is a success (either Html, or Other with status 200).
shouldNot200 :: TestResponse -> SnapHspecM b () Source #
Asserts that the response is not a normal 200.
should404 :: TestResponse -> SnapHspecM b () Source #
Asserts that the response is a NotFound.
shouldNot404 :: TestResponse -> SnapHspecM b () Source #
Asserts that the response is not a NotFound.
should300 :: TestResponse -> SnapHspecM b () Source #
Asserts that the response is a redirect.
shouldNot300 :: TestResponse -> SnapHspecM b () Source #
Asserts that the response is not a redirect.
should300To :: Text -> TestResponse -> SnapHspecM b () Source #
Asserts that the response is a redirect, and thet the url it redirects to starts with the given path.
shouldNot300To :: Text -> TestResponse -> SnapHspecM b () Source #
Asserts that the response is not a redirect to a given path. Note that it can still be a redirect for this assertion to succeed, the path it redirects to just can't start with the given path.
shouldHaveSelector :: Text -> TestResponse -> SnapHspecM b () Source #
Assert that a response (which should be Html) has a given selector.
shouldNotHaveSelector :: Text -> TestResponse -> SnapHspecM b () Source #
Assert that a response (which should be Html) doesn't have a given selector.
shouldHaveText :: Text -> TestResponse -> SnapHspecM b () Source #
Asserts that the response (which should be Html) contains the given text.
shouldNotHaveText :: Text -> TestResponse -> SnapHspecM b () Source #
Asserts that the response (which should be Html) does not contain the given text.
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) |
Predicate (a -> Bool) | |
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 |
-> SnapHspecM b () |
Tests against digestive-functors forms.
Internal types and helpers
data SnapHspecState b Source #
Internal state used to share site initialization across tests, and to propogate failures. Understanding it is completely unnecessary to use the library.
The fields it contains, in order, are:
Result Main handler Startup state Startup state Session state Before handler (runs before each eval) After handler (runs after each eval).
SnapHspecState ResultStatus (Handler b b ()) (Snaplet b) (InitializerState b) (MVar [(Text, Text)]) (Handler b b ()) (Handler b b ()) |
Instances
Example (SnapHspecM b ()) Source # | |
Defined in Test.Hspec.Snap type Arg (SnapHspecM b ()) :: Type # evaluateExample :: SnapHspecM b () -> Params -> (ActionWith (Arg (SnapHspecM b ())) -> IO ()) -> ProgressCallback -> IO Result # | |
type Arg (SnapHspecM b ()) Source # | |
Defined in Test.Hspec.Snap |
setResult :: ResultStatus -> SnapHspecM b () Source #
Records a test Success or Fail. Only the first Fail will be recorded (and will cause the whole block to Fail).
runRequest :: RequestBuilder IO () -> SnapHspecM b TestResponse Source #
Runs a request (built with helpers from Snap.Test), resulting in a response.
runHandlerSafe :: RequestBuilder IO () -> Handler b b v -> Snaplet b -> InitializerState b -> IO (Either Text Response) Source #
Runs a request against a given handler (often the whole site), with the given state. Returns any triggered exception, or the response.
evalHandlerSafe :: Handler b b v -> Snaplet b -> InitializerState b -> IO (Either Text v) Source #
Evaluates a given handler with the given state. Returns any triggered exception, or the value produced.