Safe Haskell | None |
---|
The Snap.Test module contains primitives and combinators for testing Snap applications.
- data RequestBuilder m a
- type MultipartParams = [(ByteString, MultipartParam)]
- data MultipartParam
- = FormData [ByteString]
- | Files [FileData]
- data FileData = FileData {}
- data RequestType
- buildRequest :: MonadIO m => RequestBuilder m () -> m Request
- runHandler :: MonadIO m => RequestBuilder m () -> Snap a -> m Response
- runHandlerM :: (MonadIO m, MonadSnap n) => (forall a. Request -> n a -> m Response) -> RequestBuilder m () -> n b -> m Response
- evalHandler :: MonadIO m => RequestBuilder m () -> Snap a -> m a
- evalHandlerM :: (MonadIO m, MonadSnap n) => (forall a. Request -> n a -> m a) -> RequestBuilder m () -> n b -> m b
- get :: MonadIO m => ByteString -> Params -> RequestBuilder m ()
- postUrlEncoded :: MonadIO m => ByteString -> Params -> RequestBuilder m ()
- postMultipart :: MonadIO m => ByteString -> MultipartParams -> RequestBuilder m ()
- put :: MonadIO m => ByteString -> ByteString -> ByteString -> RequestBuilder m ()
- postRaw :: MonadIO m => ByteString -> ByteString -> ByteString -> RequestBuilder m ()
- delete :: MonadIO m => ByteString -> Params -> RequestBuilder m ()
- addHeader :: Monad m => CI ByteString -> ByteString -> RequestBuilder m ()
- setContentType :: Monad m => ByteString -> RequestBuilder m ()
- setHeader :: Monad m => CI ByteString -> ByteString -> RequestBuilder m ()
- setHttpVersion :: Monad m => (Int, Int) -> RequestBuilder m ()
- setQueryString :: Monad m => Params -> RequestBuilder m ()
- setQueryStringRaw :: Monad m => ByteString -> RequestBuilder m ()
- setRequestPath :: Monad m => ByteString -> RequestBuilder m ()
- setRequestType :: MonadIO m => RequestType -> RequestBuilder m ()
- setSecure :: Monad m => Bool -> RequestBuilder m ()
- assertSuccess :: Response -> Assertion
- assert404 :: Response -> Assertion
- assertRedirectTo :: ByteString -> Response -> Assertion
- assertRedirect :: Response -> Assertion
- assertBodyContains :: ByteString -> Response -> Assertion
- getResponseBody :: Response -> IO ByteString
- dumpResponse :: Response -> IO ()
- responseToString :: Response -> IO ByteString
Combinators and types for testing Snap handlers.
Types
data RequestBuilder m a Source
RequestBuilder is a monad transformer that allows you to conveniently
build a snap Request
for testing.
MonadTrans RequestBuilder | |
Monad m => MonadState Request (RequestBuilder m) | |
Monad m => Monad (RequestBuilder m) | |
Functor m => Functor (RequestBuilder m) | |
(Monad m, Functor m) => Applicative (RequestBuilder m) | |
MonadIO m => MonadIO (RequestBuilder m) |
type MultipartParams = [(ByteString, MultipartParam)]Source
A request body of type "multipart/form-data
" consists of a set of
named form parameters, each of which can by either a list of regular form
values or a set of file uploads.
data MultipartParam Source
FormData [ByteString] | a form variable consisting of the given |
Files [FileData] | a file upload consisting of the given |
FileData | |
|
data RequestType Source
The RequestType
datatype enumerates the different kinds of HTTP
requests you can generate using the testing interface. Most users will
prefer to use the get
, postUrlEncoded
, postMultipart
, put
, and
delete
convenience functions.
Building Requests and testing handlers
buildRequest :: MonadIO m => RequestBuilder m () -> m RequestSource
Runs a RequestBuilder
, producing the desired Request
.
N.B. please don't use the request you get here in a real Snap application; things will probably break. Don't say you weren't warned :-)
:: MonadIO m | |
=> RequestBuilder m () | a request builder |
-> Snap a | a web handler |
-> m Response |
Given a web handler in the Snap
monad, and a RequestBuilder
defining
a test request, runs the handler, producing an HTTP Response
.
This function will produce almost exactly the same output as running the handler in a real server, except that chunked transfer encoding is not applied, and the "Transfer-Encoding" header is not set (this makes it easier to test response output).
:: (MonadIO m, MonadSnap n) | |
=> (forall a. Request -> n a -> m Response) | a function defining how the |
-> RequestBuilder m () | a request builder |
-> n b | a web handler |
-> m Response |
Given a web handler in some arbitrary MonadSnap
monad, a function
specifying how to evaluate it within the context of the test monad, and a
RequestBuilder
defining a test request, runs the handler, producing an
HTTP Response
.
evalHandler :: MonadIO m => RequestBuilder m () -> Snap a -> m aSource
Given a web handler in the Snap
monad, and a RequestBuilder
defining a
test request, runs the handler and returns the monadic value it produces.
Throws an exception if the Snap
handler early-terminates with finishWith
or mzero
.
:: (MonadIO m, MonadSnap n) | |
=> (forall a. Request -> n a -> m a) | a function defining
how the |
-> RequestBuilder m () | a request builder |
-> n b | a web handler |
-> m b |
Given a web handler in some arbitrary MonadSnap
monad, a function
specifying how to evaluate it within the context of the test monad, and a
RequestBuilder
defining a test request, runs the handler, returning the
monadic value it produces.
Throws an exception if the Snap
handler early-terminates with finishWith
or mzero
.
Convenience functions for generating common types of HTTP requests
:: MonadIO m | |
=> ByteString | request path |
-> Params | request's form parameters |
-> RequestBuilder m () |
Builds an HTTP "GET" request with the given query parameters.
:: MonadIO m | |
=> ByteString | request path |
-> Params | request's form parameters |
-> RequestBuilder m () |
Builds an HTTP "POST" request with the given form parameters, using the "application/x-www-form-urlencoded" MIME type.
:: MonadIO m | |
=> ByteString | request path |
-> MultipartParams | multipart form parameters |
-> RequestBuilder m () |
Builds an HTTP "POST" request with the given form parameters, using the "form-data/multipart" MIME type.
:: MonadIO m | |
=> ByteString | request path |
-> ByteString | request body MIME content-type |
-> ByteString | request body contents |
-> RequestBuilder m () |
Builds an HTTP "PUT" request.
:: MonadIO m | |
=> ByteString | request path |
-> ByteString | request body MIME content-type |
-> ByteString | request body contents |
-> RequestBuilder m () |
Builds a "raw" HTTP "POST" request, with the given MIME type and body contents.
:: MonadIO m | |
=> ByteString | request path |
-> Params | request's form parameters |
-> RequestBuilder m () |
Builds an HTTP "DELETE" request with the given query parameters.
Precise control over building Requests
addHeader :: Monad m => CI ByteString -> ByteString -> RequestBuilder m ()Source
Adds the given header to the request being built.
setContentType :: Monad m => ByteString -> RequestBuilder m ()Source
Sets the request's content-type
to the given MIME type.
setHeader :: Monad m => CI ByteString -> ByteString -> RequestBuilder m ()Source
Sets the given header in the request being built, overwriting any header with the same name already present.
setHttpVersion :: Monad m => (Int, Int) -> RequestBuilder m ()Source
Sets the test request's http version
setQueryString :: Monad m => Params -> RequestBuilder m ()Source
Escapes the given parameter mapping and sets it as the request's query string.
setQueryStringRaw :: Monad m => ByteString -> RequestBuilder m ()Source
Sets the request's query string to be the raw bytestring provided,
without any escaping or other interpretation. Most users should instead
choose the setQueryString
function, which takes a parameter mapping.
setRequestPath :: Monad m => ByteString -> RequestBuilder m ()Source
Sets the request's path. The path provided must begin with a "/
" and
must not contain a query string; if you want to provide a query string
in your test request, you must use setQueryString
or setQueryStringRaw
.
Note that rqContextPath
is never set by any RequestBuilder
function.
setRequestType :: MonadIO m => RequestType -> RequestBuilder m ()Source
Sets the type of the Request
being built.
setSecure :: Monad m => Bool -> RequestBuilder m ()Source
Controls whether the test request being generated appears to be an https request or not.
HUnit Assertions
assertSuccess :: Response -> AssertionSource
Given a Response, asserts that its HTTP status code is 200 (success).
assert404 :: Response -> AssertionSource
Given a Response, asserts that its HTTP status code is 404 (Not Found).
:: ByteString | The Response should redirect to this URI |
-> Response | |
-> Assertion |
Given a Response, asserts that its HTTP status code is between 300 and 399 (a redirect), and that the Location header of the Response points to the specified URI.
assertRedirect :: Response -> AssertionSource
Given a Response, asserts that its HTTP status code is between 300 and 399 (a redirect).
:: ByteString | Regexp that will match the body content |
-> Response | |
-> Assertion |
Given a Response, asserts that its body matches the given regular expression.
Getting response bodies
Dumping HTTP Responses
dumpResponse :: Response -> IO ()Source
Dumps the given response to stdout.
responseToString :: Response -> IO ByteStringSource
Converts the given response to a bytestring.