sydtest-yesod-0.1.0.0: A yesod companion library for sydtest
Safe HaskellNone
LanguageHaskell2010

Test.Syd.Yesod.Request

Synopsis

Documentation

get :: (Yesod site, RedirectUrl site url) => url -> YesodClientM site () Source #

Make a GET request for the given route

yit "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

yit "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 #

Assert the status of the most recently received response.

yit "returns 200 on the home route" $ do
  get HomeR
  statusIs 200

locationShouldBe :: (ParseRoute site, Show (Route site)) => Route site -> YesodClientM site () Source #

Assert the redirect location of the most recently received response.

yit "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 

Instances

Instances details
Monad (RequestBuilder site) Source # 
Instance details

Defined in Test.Syd.Yesod.Request

Methods

(>>=) :: RequestBuilder site a -> (a -> RequestBuilder site b) -> RequestBuilder site b #

(>>) :: RequestBuilder site a -> RequestBuilder site b -> RequestBuilder site b #

return :: a -> RequestBuilder site a #

Functor (RequestBuilder site) Source # 
Instance details

Defined in Test.Syd.Yesod.Request

Methods

fmap :: (a -> b) -> RequestBuilder site a -> RequestBuilder site b #

(<$) :: a -> RequestBuilder site b -> RequestBuilder site a #

MonadFail (RequestBuilder site) Source # 
Instance details

Defined in Test.Syd.Yesod.Request

Methods

fail :: String -> RequestBuilder site a #

Applicative (RequestBuilder site) Source # 
Instance details

Defined in Test.Syd.Yesod.Request

Methods

pure :: a -> RequestBuilder site a #

(<*>) :: RequestBuilder site (a -> b) -> RequestBuilder site a -> RequestBuilder site b #

liftA2 :: (a -> b -> c) -> RequestBuilder site a -> RequestBuilder site b -> RequestBuilder site c #

(*>) :: RequestBuilder site a -> RequestBuilder site b -> RequestBuilder site b #

(<*) :: RequestBuilder site a -> RequestBuilder site b -> RequestBuilder site a #

MonadIO (RequestBuilder site) Source # 
Instance details

Defined in Test.Syd.Yesod.Request

Methods

liftIO :: IO a -> RequestBuilder site a #

MonadThrow (RequestBuilder site) Source # 
Instance details

Defined in Test.Syd.Yesod.Request

Methods

throwM :: Exception e => e -> RequestBuilder site a #

MonadState (RequestBuilderData site) (RequestBuilder site) Source # 
Instance details

Defined in Test.Syd.Yesod.Request

MonadReader (YesodClient site) (RequestBuilder site) Source # 
Instance details

Defined in Test.Syd.Yesod.Request

Methods

ask :: RequestBuilder site (YesodClient site) #

local :: (YesodClient site -> YesodClient site) -> RequestBuilder site a -> RequestBuilder site a #

reader :: (YesodClient site -> a) -> RequestBuilder site a #

liftClient :: YesodClientM site a -> RequestBuilder site a Source #

Run a YesodClientM function as part of a RequestBuilder.

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.

yit "returns 200 on this post request" $ do
  request $ do
    setUrl StartProcessingR
    setMethod "POST"
    addPostParam "key" "value"
  statusIs 200

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

addFile Source #

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

addFileWith Source #

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://google.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

followRedirect Source #

Arguments

:: Yesod site 
=> YesodExample site (Either Text Text)

Left with an error message if not a redirect, Right with the redirected URL if it was

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