| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Snap.Test
Contents
Description
The Snap.Test module contains primitives and combinators for testing Snap applications.
Synopsis
- 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 ()
- addCookies :: Monad m => [Cookie] -> 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
- requestToString :: Request -> IO ByteString
- 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.
Instances
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 #
A single "multipart/form-data" form parameter: either a list of regular
 form values or a set of file uploads.
Constructors
| FormData [ByteString] | a form variable consisting of the given  | 
| Files [FileData] | a file upload consisting of the given  | 
Instances
| Show MultipartParam Source # | |
| Defined in Snap.Internal.Test.RequestBuilder Methods showsPrec :: Int -> MultipartParam -> ShowS # show :: MultipartParam -> String # showList :: [MultipartParam] -> ShowS # | |
Represents a single file upload for the MultipartParam.
Constructors
| FileData | |
| Fields 
 | |
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.
Constructors
| GetRequest | |
| RequestWithRawBody Method ByteString | |
| MultipartPostRequest MultipartParams | |
| UrlEncodedPostRequest Params | |
| DeleteRequest | 
Instances
| Show RequestType Source # | |
| Defined in Snap.Internal.Test.RequestBuilder Methods showsPrec :: Int -> RequestType -> ShowS # show :: RequestType -> String # showList :: [RequestType] -> ShowS # | |
Building Requests and testing handlers
buildRequest :: MonadIO m => RequestBuilder m () -> m Request Source #
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 :-)
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci>buildRequest$get"/foo/bar" M.empty GET /foo/bar HTTP/1.1 host: localhost sn="localhost" c=127.0.0.1:60000 s=127.0.0.1:8080 ctx=/ clen=n/a
Arguments
| :: 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).
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci> import Snap.Core ghci>runHandler(get"foo/bar" M.empty) (writeBS"Hello, world!") HTTP/1.1 200 OK server: Snap/test date: Thu, 17 Jul 2014 21:03:23 GMT Hello, world!
Arguments
| :: (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 a Source #
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.
Example:
ghci> :set -XOverloadedStrings ghci> import Control.Monad ghci> import qualified Data.Map as M ghci> import Snap.Core ghci>evalHandler(get"foo/bar" M.empty) (writeBS"Hello, world!" >> return 42) 42 ghci>evalHandler(get"foo/bar" M.empty)mzero*** Exception: No handler for request: failure was pass
Arguments
| :: (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
Arguments
| :: MonadIO m | |
| => ByteString | request path | 
| -> Params | request's form parameters | 
| -> RequestBuilder m () | 
Builds an HTTP "GET" request with the given query parameters.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci>buildRequest$get"/foo/bar" (M.fromList [("param0", ["baz", "quux"])]) GET /foo/bar?param0=baz¶m0=quux HTTP/1.1 host: localhost sn="localhost" c=127.0.0.1:60000 s=127.0.0.1:8080 ctx=/ clen=n/a params: param0: ["baz","quux"]
Arguments
| :: 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.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci>buildRequest$postUrlEncoded"/foo/bar" (M.fromList [("param0", ["baz", "quux"])]) POST /foo/bar HTTP/1.1 content-type: application/x-www-form-urlencoded content-length: 22 host: localhost sn="localhost" c=127.0.0.1:60000 s=127.0.0.1:8080 ctx=/ clen=22 params: param0: ["baz","quux"]
Arguments
| :: 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.
Example:
ghci> :set -XOverloadedStrings ghci>buildRequest$postMultipart"/foo/bar" [("param0", FormData ["baz", "quux"])] POST /foo/bar HTTP/1.1 content-type: multipart/form-data; boundary=snap-boundary-572334111ec0c05ad4812481e8585dfa content-length: 406 host: localhost sn="localhost" c=127.0.0.1:60000 s=127.0.0.1:8080 ctx=/ clen=406
Arguments
| :: MonadIO m | |
| => ByteString | request path | 
| -> ByteString | request body MIME content-type | 
| -> ByteString | request body contents | 
| -> RequestBuilder m () | 
Builds an HTTP "PUT" request.
Example:
ghci> :set -XOverloadedStrings ghci>buildRequest$put"/foo/bar" "text/plain" "some text" PUT /foo/bar HTTP/1.1 content-type: text/plain content-length: 9 host: localhost sn="localhost" c=127.0.0.1:60000 s=127.0.0.1:8080 ctx=/ clen=9
Arguments
| :: 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.
Example:
ghci> :set -XOverloadedStrings ghci>buildRequest$postRaw"/foo/bar" "text/plain" "some text" POST /foo/bar HTTP/1.1 content-type: text/plain content-length: 9 host: localhost sn="localhost" c=127.0.0.1:60000 s=127.0.0.1:8080 ctx=/ clen=9
Arguments
| :: MonadIO m | |
| => ByteString | request path | 
| -> Params | request's form parameters | 
| -> RequestBuilder m () | 
Builds an HTTP "DELETE" request with the given query parameters.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci>buildRequest$delete"/foo/bar" M.empty DELETE /foo/bar HTTP/1.1 host: localhost sn="localhost" c=127.0.0.1:60000 s=127.0.0.1:8080 ctx=/ clen=n/a
Precise control over building Requests
addHeader :: Monad m => CI ByteString -> ByteString -> RequestBuilder m () Source #
Adds the given header to the request being built.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci> :{ ghci|buildRequest$ doget"/foo/bar" M.empty ghci|addHeader"Accept" "text/html" ghci|addHeader"Accept" "text/plain" ghci| :} GET /foo/bar HTTP/1.1 accept: text/html,text/plain host: localhost sn="localhost" c=127.0.0.1:60000 s=127.0.0.1:8080 ctx=/ clen=n/a
setContentType :: Monad m => ByteString -> RequestBuilder m () Source #
Sets the request's content-type to the given MIME type.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci>buildRequest$put"/foo/bar" "text/html" "some text" >>setContentType"text/plain" PUT /foo/bar HTTP/1.1 content-type: text/plain content-length: 9 host: localhost sn="localhost" c=127.0.0.1:60000 s=127.0.0.1:8080 ctx=/ clen=9
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.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci> :{ ghci|buildRequest$ do get "/foo/bar" M.empty ghci|setHeader"Accept" "text/html" ghci|setHeader"Accept" "text/plain" ghci| :} GET /foo/bar HTTP/1.1 accept: text/plain host: localhost sn="localhost" c=127.0.0.1:60000 s=127.0.0.1:8080 ctx=/ clen=n/a
addCookies :: Monad m => [Cookie] -> RequestBuilder m () Source #
Adds the given cookies to the request being built.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci> import Snap.Core ghci> let cookie =Cookie"name" "value" Nothing Nothing Nothing False False ghci>buildRequest$get"/foo/bar" M.empty >>addCookies[cookie] GET /foo/bar HTTP/1.1 cookie: name=value host: localhost sn="localhost" c=127.0.0.1:60000 s=127.0.0.1:8080 ctx=/ clen=n/a cookies: Cookie {cookieName = "name", cookieValue = "value", ...}
setHttpVersion :: Monad m => (Int, Int) -> RequestBuilder m () Source #
Sets the test request's http version
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci>buildRequest$delete"/foo/bar" M.empty >>setHttpVersion(1,0) DELETE /foo/bar HTTP/1.0 host: localhost sn="localhost" c=127.0.0.1:60000 s=127.0.0.1:8080 ctx=/ clen=n/a
setQueryString :: Monad m => Params -> RequestBuilder m () Source #
Escapes the given parameter mapping and sets it as the request's query string.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci>buildRequest$get"/foo/bar" M.empty >>setQueryString(M.fromList [("param0", ["baz"]), ("param1", ["qux"])]) GET /foo/bar?param0=baz¶m1=qux HTTP/1.1 host: localhost sn="localhost" c=127.0.0.1:60000 s=127.0.0.1:8080 ctx=/ clen=n/a params: param0: ["baz"], param1: ["qux"]
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.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci>buildRequest$get"/foo/bar" M.empty >>setQueryStringRaw"param0=baz¶m1=qux" GET /foo/bar?param0=baz¶m1=qux HTTP/1.1 host: localhost sn="localhost" c=127.0.0.1:60000 s=127.0.0.1:8080 ctx=/ clen=n/a params: param0: ["baz"], param1: ["qux"]
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.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci>buildRequest$get"/foo/bar" M.empty >>setRequestPath"/bar/foo" GET /bar/foo HTTP/1.1 host: localhost sn="localhost" c=127.0.0.1:60000 s=127.0.0.1:8080 ctx=/ clen=n/a
setRequestType :: MonadIO m => RequestType -> RequestBuilder m () Source #
Sets the type of the Request being built.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci>buildRequest$delete"/foo/bar" M.empty >>setRequestTypeGetRequest GET /foo/bar HTTP/1.1 host: localhost sn="localhost" c=127.0.0.1:60000 s=127.0.0.1:8080 ctx=/ clen=n/a
setSecure :: Monad m => Bool -> RequestBuilder m () Source #
Controls whether the test request being generated appears to be an https request or not.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci>buildRequest$delete"/foo/bar" M.empty >>setSecureTrue DELETE /foo/bar HTTP/1.1 host: localhost sn="localhost" c=127.0.0.1:60000 s=127.0.0.1:8080 ctx=/ clen=n/a secure
HUnit Assertions
assertSuccess :: Response -> Assertion Source #
Given a Response, assert that its HTTP status code is 200 (success).
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Test.HUnit as T ghci> let test = T.runTestTT . T.TestCase ghci> test $assertSuccessemptyResponseCases: 1 Tried: 1 Errors: 0 Failures: 0 Counts {cases = 1, tried = 1, errors = 0, failures = 0} ghci> test $assertSuccess(setResponseStatus500 "Internal Server Error"emptyResponse) ### Failure: Expected success (200) but got (500) expected: 200 but got: 500 Cases: 1 Tried: 1 Errors: 0 Failures: 1 Counts {cases = 1, tried = 1, errors = 0, failures = 1}
assert404 :: Response -> Assertion Source #
Given a Response, assert that its HTTP status code is 404 (Not Found).
Example:
ghci> :set -XOverloadedStrings ghci>assert404$setResponseStatus404 "Not Found"emptyResponseghci>assert404emptyResponse*** Exception: HUnitFailure "Expected Not Found (404) but got (200)\nexpected: 404\n but got: 200"
Arguments
| :: ByteString | The Response should redirect to this URI | 
| -> Response | |
| -> Assertion | 
Given a Response, assert 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.
Example:
ghci> :set -XOverloadedStrings ghci> let r' =setResponseStatus301 "Moved Permanently"emptyResponseghci> let r =setHeader"Location" "www.example.com" r' ghci>assertRedirectTo"www.example.com" r ghci>assertRedirectTo"www.example.com"emptyResponse*** Exception: HUnitFailure "Expected redirect but got status code (200)"
assertRedirect :: Response -> Assertion Source #
Given a Response, assert that its HTTP status code is between 300 and 399
 (a redirect).
Example:
ghci> :set -XOverloadedStrings ghci>assertRedirect$setResponseStatus301 "Moved Permanently"emptyResponseghci>assertRedirectemptyResponse*** Exception: HUnitFailure "Expected redirect but got status code (200)"
Arguments
| :: ByteString | Regexp that will match the body content | 
| -> Response | |
| -> Assertion | 
Given a Response, assert that its body matches the given regular
 expression.
Example:
ghci> :set -XOverloadedStrings ghci> import qualified System.IO.Streams as Streams ghci> import qualified Data.ByteString.Builder as Builder ghci> :{ ghci| let r =setResponseBodyghci| (out -> do ghci| Streams.write (Just $ Builder.byteString "Hello, world!") out ghci| return out) ghci|emptyResponseghci| :} ghci>assertBodyContains"^Hello" r ghci>assertBodyContains"Bye" r *** Exception: HUnitFailure "Expected body to match regexp \"\"Bye\"\", but didn't"
Getting response bodies
getResponseBody :: Response -> IO ByteString Source #
Dumping HTTP Messages
requestToString :: Request -> IO ByteString Source #
Converts the given Request to a bytestring.
Since: 1.0.0.0
Example:
ghci> :set -XOverloadedStrings ghci> import qualified Data.Map as M ghci> r <-buildRequest$ get "/foo/bar" M.empty ghci>requestToStringr "GET /foo/bar HTTP/1.1\r\nhost: localhost\r\n\r\n"
responseToString :: Response -> IO ByteString Source #
Converts the given Response to a bytestring.
Example:
ghci> import Snap.Core ghci>responseToStringemptyResponse"HTTP/1.1 200 OK\r\n\r\n"