hspec-snap-1.0.2.0: A library for testing with Hspec and the Snap Web Framework

Safe HaskellNone
LanguageHaskell98

Test.Hspec.Snap

Contents

Synopsis

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

Defined in Test.Hspec.Snap

Show TestResponse Source # 
Instance details

Defined in Test.Hspec.Snap

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

Minimal complete definition

fields, save

Methods

fields :: d Source #

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

params Source #

Arguments

:: [(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)

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.

Constructors

Value a

The value the form should take (and should be valid)

Predicate (a -> Bool) 
ErrorPaths [Text]

The error paths that should be populated

form Source #

Arguments

:: (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).

Constructors

SnapHspecState ResultStatus (Handler b b ()) (Snaplet b) (InitializerState b) (MVar [(Text, Text)]) (Handler b b ()) (Handler b b ()) 
Instances
Example (SnapHspecM b ()) Source # 
Instance details

Defined in Test.Hspec.Snap

Associated Types

type Arg (SnapHspecM b ()) :: Type #

Methods

evaluateExample :: SnapHspecM b () -> Params -> (ActionWith (Arg (SnapHspecM b ())) -> IO ()) -> ProgressCallback -> IO Result #

type Arg (SnapHspecM b ()) Source # 
Instance details

Defined in Test.Hspec.Snap

type Arg (SnapHspecM b ()) = SnapHspecState b

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.