| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Test.Syd.Yesod.Request
Synopsis
- get :: (Yesod site, RedirectUrl site url) => url -> YesodClientM site ()
- post :: (Yesod site, RedirectUrl site url) => url -> YesodClientM site ()
- performMethod :: (Yesod site, RedirectUrl site url) => Method -> url -> YesodClientM site ()
- statusIs :: HasCallStack => Int -> YesodClientM site ()
- statusShouldBe :: HasCallStack => Int -> YesodClientM site ()
- locationShouldBe :: (ParseRoute site, Show (Route site)) => Route site -> YesodClientM localSite ()
- bodyContains :: HasCallStack => String -> YesodExample site ()
- newtype RequestBuilder site a = RequestBuilder {
- unRequestBuilder :: StateT (RequestBuilderData site) (YesodClientM site) a
- liftClient :: YesodClientM site a -> RequestBuilder site a
- data RequestBuilderData site = RequestBuilderData {}
- data PostData
- data RequestPart
- initialRequestBuilderData :: RequestBuilderData site
- isFile :: RequestPart -> Bool
- runRequestBuilder :: RequestBuilder site a -> YesodClientM site Request
- request :: RequestBuilder site a -> YesodClientM site ()
- setUrl :: (Yesod site, RedirectUrl site url) => url -> RequestBuilder site ()
- setMethod :: Method -> RequestBuilder site ()
- addRequestHeader :: Header -> RequestBuilder site ()
- addGetParam :: Text -> Text -> RequestBuilder site ()
- addPostParam :: Text -> Text -> RequestBuilder site ()
- addFile :: Text -> FilePath -> Text -> RequestBuilder site ()
- addFileWith :: Text -> FilePath -> ByteString -> Maybe Text -> RequestBuilder site ()
- setRequestBody :: ByteString -> RequestBuilder site ()
- addToken_ :: HasCallStack => Text -> RequestBuilder site ()
- addToken :: HasCallStack => RequestBuilder site ()
- addTokenFromCookie :: HasCallStack => RequestBuilder site ()
- addTokenFromCookieNamedToHeaderNamed :: HasCallStack => ByteString -> CI ByteString -> RequestBuilder site ()
- performRequest :: Request -> YesodClientM site ()
- getRequestCookies :: RequestBuilder site (Map ByteString SetCookie)
- htmlQuery :: HasCallStack => Query -> YesodExample site [HtmlLBS]
- followRedirect :: Yesod site => YesodExample site (Either Text Text)
- followRedirect_ :: Yesod site => YesodExample site ()
Documentation
get :: (Yesod site, RedirectUrl site url) => url -> YesodClientM site () Source #
Make a GET request for the given route
it "returns 200 on the home route" $ do get HomeR statusIs 200
post :: (Yesod site, RedirectUrl site url) => url -> YesodClientM site () Source #
Make a POST request for the given route
it "returns 200 on the start processing route" $ do post StartProcessingR statusIs 200
performMethod :: (Yesod site, RedirectUrl site url) => Method -> url -> YesodClientM site () Source #
Perform a request using an arbitrary method for the given route.
statusIs :: HasCallStack => Int -> YesodClientM site () Source #
Synonym of statusShouldBe for compatibility with yesod-test
statusShouldBe :: HasCallStack => Int -> YesodClientM site () Source #
Assert the status of the most recently received response.
it "returns 200 on the home route" $ do get HomeR statusShouldBe 200
locationShouldBe :: (ParseRoute site, Show (Route site)) => Route site -> YesodClientM localSite () Source #
Assert the redirect location of the most recently received response.
it "redirects to the overview on the home route" $ do get HomeR statusIs 301 locationShouldBe OverviewR
bodyContains :: HasCallStack => String -> YesodExample site () Source #
Assert the last response has the given text.
The check is performed using the response body in full text form without any html parsing.
newtype RequestBuilder site a Source #
A request builder monad that allows you to monadically build a request using runRequestBuilder.
This request builder has access to the entire YesodClientM underneath.
This includes the Site under test, as well as cookies etc.
See YesodClientM for more details.
Constructors
| RequestBuilder | |
Fields
| |
Instances
liftClient :: YesodClientM site a -> RequestBuilder site a Source #
Run a YesodClientM function as part of a RequestBuilder.
data RequestBuilderData site Source #
Constructors
| RequestBuilderData | |
Instances
| MonadState (RequestBuilderData site) (RequestBuilder site) Source # | |
Defined in Test.Syd.Yesod.Request Methods get :: RequestBuilder site (RequestBuilderData site) # put :: RequestBuilderData site -> RequestBuilder site () # state :: (RequestBuilderData site -> (a, RequestBuilderData site)) -> RequestBuilder site a # | |
Constructors
| MultipleItemsPostData [RequestPart] | |
| BinaryPostData ByteString |
data RequestPart Source #
Constructors
| ReqKvPart Text Text | |
| ReqFilePart Text FilePath ByteString (Maybe Text) |
isFile :: RequestPart -> Bool Source #
runRequestBuilder :: RequestBuilder site a -> YesodClientM site Request Source #
Run a RequestBuilder to make the Request that it defines.
request :: RequestBuilder site a -> YesodClientM site () Source #
Perform the request that is built by the given RequestBuilder.
it "returns 200 on this post request" $ do
request $ do
setUrl StartProcessingR
setMethod "POST"
addPostParam "key" "value"
statusIs 200setUrl :: (Yesod site, RedirectUrl site url) => url -> RequestBuilder site () Source #
Set the url of the RequestBuilder to the given route.
setMethod :: Method -> RequestBuilder site () Source #
Set the method of the RequestBuilder.
addRequestHeader :: Header -> RequestBuilder site () Source #
Add the given request header to the RequestBuilder.
addGetParam :: Text -> Text -> RequestBuilder site () Source #
Add the given GET parameter to the RequestBuilder.
addPostParam :: Text -> Text -> RequestBuilder site () Source #
Add the given POST parameter to the RequestBuilder.
Arguments
| :: Text | The parameter name for the file. |
| -> FilePath | The path to the file. |
| -> Text | The MIME type of the file, e.g. "image/png". |
| -> RequestBuilder site () |
Arguments
| :: Text | The parameter name for the file. |
| -> FilePath | The path to the file. |
| -> ByteString | The contents of the file. |
| -> Maybe Text | The MIME type of the file, e.g. "image/png". |
| -> RequestBuilder site () |
setRequestBody :: ByteString -> RequestBuilder site () Source #
Set the request body of the RequestBuilder.
Note that this invalidates any of the other post parameters that may have been set.
addToken_ :: HasCallStack => Text -> RequestBuilder site () Source #
Look up the CSRF token from the given form data and add it to the request header
addToken :: HasCallStack => RequestBuilder site () Source #
Look up the CSRF token from the only form data and add it to the request header
addTokenFromCookie :: HasCallStack => RequestBuilder site () Source #
Look up the CSRF token from the cookie with name defaultCsrfCookieName and add it to the request header with name defaultCsrfHeaderName.
addTokenFromCookieNamedToHeaderNamed Source #
Arguments
| :: HasCallStack | |
| => ByteString | The name of the cookie |
| -> CI ByteString | The name of the header |
| -> RequestBuilder site () |
Looks up the CSRF token stored in the cookie with the given name and adds it to the given request header.
performRequest :: Request -> YesodClientM site () Source #
Perform the given request as-is.
Note that this function does not check whether you are making a request to the site under test. You could make a request to https://example.com if you wanted.
getRequestCookies :: RequestBuilder site (Map ByteString SetCookie) Source #
For backward compatibiilty, you can use the MonadState constraint to get access to the CookieJar directly.
htmlQuery :: HasCallStack => Query -> YesodExample site [HtmlLBS] Source #
Query the last response using CSS selectors, returns a list of matched fragments
Arguments
| :: Yesod site | |
| => YesodExample site (Either Text Text) |
|
Follow a redirect, if the last response was a redirect.
(We consider a request a redirect if the status is 301, 302, 303, 307 or 308, and the Location header is set.)
it "redirects home" $ do get RedirectHomeR statusIs 303 locationShouldBe HomeR _ <- followRedirect statusIs 200
followRedirect_ :: Yesod site => YesodExample site () Source #