| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Test.Hspec.Wai
Description
Have a look at the README for an example of how to use this library.
Synopsis
- data WaiSession st a
- type WaiExpectation st = WaiSession st ()
- get :: ByteString -> WaiSession st SResponse
- post :: ByteString -> ByteString -> WaiSession st SResponse
- put :: ByteString -> ByteString -> WaiSession st SResponse
- patch :: ByteString -> ByteString -> WaiSession st SResponse
- options :: ByteString -> WaiSession st SResponse
- delete :: ByteString -> WaiSession st SResponse
- request :: Method -> ByteString -> [Header] -> ByteString -> WaiSession st SResponse
- postHtmlForm :: ByteString -> [(String, String)] -> WaiSession st SResponse
- shouldRespondWith :: HasCallStack => WaiSession st SResponse -> ResponseMatcher -> WaiExpectation st
- data ResponseMatcher = ResponseMatcher {- matchStatus :: Int
- matchHeaders :: [MatchHeader]
- matchBody :: MatchBody
 
- data MatchHeader = MatchHeader ([Header] -> Body -> Maybe String)
- data MatchBody = MatchBody ([Header] -> Body -> Maybe String)
- type Body = ByteString
- (<:>) :: HeaderName -> ByteString -> MatchHeader
- liftIO :: MonadIO m => IO a -> m a
- with :: IO Application -> SpecWith ((), Application) -> Spec
- withState :: IO (st, Application) -> SpecWith (st, Application) -> Spec
- getState :: WaiSession st st
- pending :: WaiSession st ()
- pendingWith :: String -> WaiSession st ()
Types
data WaiSession st a Source #
A WAI test
 session that carries the Application under test and some client state.
Instances
type WaiExpectation st = WaiSession st () Source #
An expectation in the WaiSession monad.  Failing expectations are
 communicated through exceptions (similar to Expectation and
 Assertion).
Performing requests
get :: ByteString -> WaiSession st SResponse Source #
Perform a GET request to the application under test.
post :: ByteString -> ByteString -> WaiSession st SResponse Source #
Perform a POST request to the application under test.
put :: ByteString -> ByteString -> WaiSession st SResponse Source #
Perform a PUT request to the application under test.
patch :: ByteString -> ByteString -> WaiSession st SResponse Source #
Perform a PATCH request to the application under test.
options :: ByteString -> WaiSession st SResponse Source #
Perform an OPTIONS request to the application under test.
delete :: ByteString -> WaiSession st SResponse Source #
Perform a DELETE request to the application under test.
request :: Method -> ByteString -> [Header] -> ByteString -> WaiSession st SResponse Source #
Perform a request to the application under test, with specified HTTP method, request path, headers and body.
Posting HTML forms
postHtmlForm :: ByteString -> [(String, String)] -> WaiSession st SResponse Source #
Perform a POST request to the application under test.
The specified list of key-value pairs is encoded as
 application/x-www-form-urlencoded and used as request body.
In addition the Content-Type is set to application/x-www-form-urlencoded.
Matching on the response
shouldRespondWith :: HasCallStack => WaiSession st SResponse -> ResponseMatcher -> WaiExpectation st Source #
Set the expectation that a response matches a specified ResponseMatcher.
A ResponseMatcher matches a response if:
- the specified status matches the HTTP response status code
- the specified body (if any) matches the response body
- the response has all of the specified Headerfields (the response may have arbitrary additionalHeaderfields)
You can use ResponseMatcher's (broken) Num instance to match for a HTTP
 status code:
get "/" `shouldRespondWith` 200 -- matches if status is 200
You can use ResponseMatcher's IsString instance to match for a HTTP
 status 200 and a body:
get "/" `shouldRespondWith` "foo" -- matches if body is "foo" and status is 200
If you want to match for a different HTTP status, you can use record update
 notation to specify matchStatus explicitly:
get "/" `shouldRespondWith` "foo" {matchStatus = 404}
-- matches if body is "foo" and status is 404If you want to require a specific header field you can specify
 matchHeaders:
get "/" `shouldRespondWith` "foo" {matchHeaders = ["Content-Type" <:> "text/plain"]}
-- matches if body is "foo", status is 200 and there is a header field "Content-Type: text/plain"data ResponseMatcher Source #
Constructors
| ResponseMatcher | |
| Fields 
 | |
Instances
| Num ResponseMatcher Source # | |
| Defined in Test.Hspec.Wai.Matcher Methods (+) :: ResponseMatcher -> ResponseMatcher -> ResponseMatcher # (-) :: ResponseMatcher -> ResponseMatcher -> ResponseMatcher # (*) :: ResponseMatcher -> ResponseMatcher -> ResponseMatcher # negate :: ResponseMatcher -> ResponseMatcher # abs :: ResponseMatcher -> ResponseMatcher # signum :: ResponseMatcher -> ResponseMatcher # fromInteger :: Integer -> ResponseMatcher # | |
| IsString ResponseMatcher Source # | |
| Defined in Test.Hspec.Wai.Matcher Methods fromString :: String -> ResponseMatcher # | |
data MatchHeader Source #
Constructors
| MatchHeader ([Header] -> Body -> Maybe String) | 
Instances
| IsString MatchBody Source # | |
| Defined in Test.Hspec.Wai.Matcher Methods fromString :: String -> MatchBody # | |
type Body = ByteString Source #
(<:>) :: HeaderName -> ByteString -> MatchHeader Source #
Helpers and re-exports
with :: IO Application -> SpecWith ((), Application) -> Spec Source #
withState :: IO (st, Application) -> SpecWith (st, Application) -> Spec Source #
getState :: WaiSession st st Source #
pending :: WaiSession st () Source #
A lifted version of pending.
pendingWith :: String -> WaiSession st () Source #
A lifted version of pendingWith.