Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Yesod.Test
Description
Yesod.Test is a pragmatic framework for testing web applications built using wai.
By pragmatic I may also mean dirty
. Its main goal is to encourage integration
and system testing of web applications by making everything easy to test.
Your tests are like browser sessions that keep track of cookies and the last visited page. You can perform assertions on the content of HTML responses, using CSS selectors to explore the document more easily.
You can also easily build requests using forms present in the current page. This is very useful for testing web applications built in yesod, for example, where your forms may have field names generated by the framework or a randomly generated CSRF token input.
Example project
The best way to see an example project using yesod-test is to create a scaffolded Yesod project:
stack new projectname yesod-sqlite
(See https://github.com/commercialhaskell/stack-templates/wiki#yesod for the full list of Yesod templates)
The scaffolded project makes your database directly available in tests, so you can use runDB
to set up
backend pre-conditions, or to assert that your session is having the desired effect.
It also handles wiping your database between each test.
Example code
The code below should give you a high-level idea of yesod-test's capabilities.
Note that it uses helper functions like withApp
and runDB
from the scaffolded project; these aren't provided by yesod-test.
spec :: Spec spec = withApp $ do describe "Homepage" $ do it "loads the homepage with a valid status code" $ doget
HomeRstatusIs
200 describe "Login Form" $ do it "Only allows dashboard access after logging in" $ doget
DashboardRstatusIs
401get
HomeR -- Assert a <p> tag exists on the pagehtmlAnyContain
"p" "Login" -- yesod-test provides aRequestBuilder
monad for building up HTTP requestsrequest
$ do -- Lookup the HTML <label> with the text Username, and set a POST parameter for that field with the value FelipebyLabelExact
"Username" "Felipe"byLabelExact
"Password" "pass"setMethod
"POST"setUrl
SignupRstatusIs
200 -- The previous request will have stored a session cookie, so we can access the dashboard nowget
DashboardRstatusIs
200 -- Assert a user with the name Felipe was added to the database [Entity userId user] <- runDB $ selectList [] []assertEq
"A single user named Felipe is created" (userUsername user) "Felipe" describe "JSON" $ do it "Can make requests using JSON, and parse JSON responses" $ do -- Precondition: Create a user with the name "George" runDB $ insert_ $ User "George" "pass"request
$ do -- Use the Aeson library to send JSON to the serversetRequestBody
(encode
$ LoginRequest "George" "pass")addRequestHeader
("Accept", "application/json")addRequestHeader
("Content-Type", "application/json")setUrl
LoginRstatusIs
200 -- Parse the request's response as JSON (signupResponse :: SignupResponse) <-requireJSONResponse
HUnit / HSpec integration
yesod-test is built on top of hspec, which is itself built on top of HUnit.
You can use existing assertion functions from those libraries, but you'll need to use liftIO
with them:
liftIO $ actualTimesCalled `shouldBe
` expectedTimesCalled -- hspec assertion
liftIO $ assertBool
"a is greater than b" (a > b) -- HUnit assertion
yesod-test provides a handful of assertion functions that are already lifted, such as assertEq
, as well.
Synopsis
- yesodSpec :: YesodDispatch site => site -> YesodSpec site -> Spec
- type YesodSpec site = Writer [YesodSpecTree site] ()
- yesodSpecWithSiteGenerator :: YesodDispatch site => IO site -> YesodSpec site -> Spec
- yesodSpecWithSiteGeneratorAndArgument :: YesodDispatch site => (a -> IO site) -> YesodSpec site -> SpecWith a
- yesodSpecApp :: YesodDispatch site => site -> IO Application -> YesodSpec site -> Spec
- type YesodExample site = SIO (YesodExampleData site)
- data YesodExampleData site = YesodExampleData {
- yedApp :: !Application
- yedSite :: !site
- yedCookies :: !Cookies
- yedResponse :: !(Maybe SResponse)
- type TestApp site = (site, Middleware)
- type YSpec site = SpecWith (TestApp site)
- testApp :: site -> Middleware -> TestApp site
- data YesodSpecTree site
- = YesodSpecGroup String [YesodSpecTree site]
- | YesodSpecItem String (YesodExample site ())
- ydescribe :: String -> YesodSpec site -> YesodSpec site
- yit :: String -> YesodExample site () -> YesodSpec site
- testModifySite :: YesodDispatch site => (site -> IO (site, Middleware)) -> YesodExample site ()
- testSetCookie :: SetCookie -> YesodExample site ()
- testDeleteCookie :: ByteString -> YesodExample site ()
- testModifyCookies :: (Cookies -> Cookies) -> YesodExample site ()
- testClearCookies :: YesodExample site ()
- get :: (Yesod site, RedirectUrl site url) => url -> YesodExample site ()
- post :: (Yesod site, RedirectUrl site url) => url -> YesodExample site ()
- postBody :: (Yesod site, RedirectUrl site url) => url -> ByteString -> YesodExample site ()
- performMethod :: (Yesod site, RedirectUrl site url) => ByteString -> url -> YesodExample site ()
- followRedirect :: Yesod site => YesodExample site (Either Text Text)
- getLocation :: ParseRoute site => YesodExample site (Either Text (Route site))
- request :: RequestBuilder site () -> YesodExample site ()
- addRequestHeader :: Header -> RequestBuilder site ()
- addBasicAuthHeader :: CI ByteString -> CI ByteString -> RequestBuilder site ()
- setMethod :: Method -> RequestBuilder site ()
- addPostParam :: Text -> Text -> RequestBuilder site ()
- addGetParam :: Text -> Text -> RequestBuilder site ()
- addBareGetParam :: Text -> RequestBuilder site ()
- addFile :: Text -> FilePath -> Text -> RequestBuilder site ()
- setRequestBody :: ByteString -> RequestBuilder site ()
- type RequestBuilder site = SIO (RequestBuilderData site)
- data SIO s a
- setUrl :: (Yesod site, RedirectUrl site url) => url -> RequestBuilder site ()
- clickOn :: (HasCallStack, Yesod site) => Query -> YesodExample site ()
- byLabel :: Text -> Text -> RequestBuilder site ()
- byLabelExact :: Text -> Text -> RequestBuilder site ()
- byLabelContain :: Text -> Text -> RequestBuilder site ()
- byLabelPrefix :: Text -> Text -> RequestBuilder site ()
- byLabelSuffix :: Text -> Text -> RequestBuilder site ()
- bySelectorLabelContain :: Text -> Text -> Text -> RequestBuilder site ()
- fileByLabel :: Text -> FilePath -> Text -> RequestBuilder site ()
- fileByLabelExact :: Text -> FilePath -> Text -> RequestBuilder site ()
- fileByLabelContain :: Text -> FilePath -> Text -> RequestBuilder site ()
- fileByLabelPrefix :: Text -> FilePath -> Text -> RequestBuilder site ()
- fileByLabelSuffix :: Text -> FilePath -> Text -> RequestBuilder site ()
- addToken :: HasCallStack => RequestBuilder site ()
- addToken_ :: HasCallStack => Query -> RequestBuilder site ()
- addTokenFromCookie :: HasCallStack => RequestBuilder site ()
- addTokenFromCookieNamedToHeaderNamed :: HasCallStack => ByteString -> CI ByteString -> RequestBuilder site ()
- assertEqual :: (HasCallStack, Eq a) => String -> a -> a -> YesodExample site ()
- assertNotEq :: (HasCallStack, Eq a, Show a) => String -> a -> a -> YesodExample site ()
- assertEqualNoShow :: (HasCallStack, Eq a) => String -> a -> a -> YesodExample site ()
- assertEq :: (HasCallStack, Eq a, Show a) => String -> a -> a -> YesodExample site ()
- assertHeader :: HasCallStack => CI ByteString -> ByteString -> YesodExample site ()
- assertNoHeader :: HasCallStack => CI ByteString -> YesodExample site ()
- statusIs :: HasCallStack => Int -> YesodExample site ()
- bodyEquals :: HasCallStack => String -> YesodExample site ()
- bodyContains :: HasCallStack => String -> YesodExample site ()
- bodyNotContains :: HasCallStack => String -> YesodExample site ()
- htmlAllContain :: HasCallStack => Query -> String -> YesodExample site ()
- htmlAnyContain :: HasCallStack => Query -> String -> YesodExample site ()
- htmlNoneContain :: HasCallStack => Query -> String -> YesodExample site ()
- htmlCount :: HasCallStack => Query -> Int -> YesodExample site ()
- requireJSONResponse :: (HasCallStack, FromJSON a) => YesodExample site a
- getTestYesod :: YesodExample site site
- getResponse :: YesodExample site (Maybe SResponse)
- getRequestCookies :: HasCallStack => RequestBuilder site Cookies
- printBody :: YesodExample site ()
- printMatches :: HasCallStack => Query -> YesodExample site ()
- htmlQuery :: HasCallStack => Query -> YesodExample site [HtmlLBS]
- parseHTML :: HtmlLBS -> Cursor
- withResponse :: HasCallStack => (SResponse -> YesodExample site a) -> YesodExample site a
Declaring and running your test suite
type YesodSpec site = Writer [YesodSpecTree site] () Source #
Corresponds to hspec's Spec
.
Since 1.2.0
yesodSpecWithSiteGenerator :: YesodDispatch site => IO site -> YesodSpec site -> Spec Source #
Same as yesodSpec, but instead of taking already built site it takes an action which produces site for each test.
yesodSpecWithSiteGeneratorAndArgument :: YesodDispatch site => (a -> IO site) -> YesodSpec site -> SpecWith a Source #
Same as yesodSpecWithSiteGenerator, but also takes an argument to build the site and makes that argument available to the tests.
Since: 1.6.4
yesodSpecApp :: YesodDispatch site => site -> IO Application -> YesodSpec site -> Spec Source #
Same as yesodSpec, but instead of taking a site it
takes an action which produces the Application
for each test.
This lets you use your middleware from makeApplication
type YesodExample site = SIO (YesodExampleData site) Source #
A single test case, to be run with yit
.
Since 1.2.0
data YesodExampleData site Source #
The state used in a single test case defined using yit
Since 1.2.4
Constructors
YesodExampleData | |
Fields
|
Instances
YesodDispatch site => Example (SIO (YesodExampleData site) a) Source # | |
Defined in Yesod.Test Associated Types type Arg (SIO (YesodExampleData site) a) # Methods evaluateExample :: SIO (YesodExampleData site) a -> Params -> (ActionWith (Arg (SIO (YesodExampleData site) a)) -> IO ()) -> ProgressCallback -> IO Result # | |
type Arg (SIO (YesodExampleData site) a) Source # | |
Defined in Yesod.Test |
type TestApp site = (site, Middleware) Source #
testApp :: site -> Middleware -> TestApp site Source #
data YesodSpecTree site Source #
Internal data structure, corresponding to hspec's SpecTree.
Since 1.2.0
Constructors
YesodSpecGroup String [YesodSpecTree site] | |
YesodSpecItem String (YesodExample site ()) |
ydescribe :: String -> YesodSpec site -> YesodSpec site Source #
Start describing a Tests suite keeping cookies and a reference to the tested Application
and ConnectionPool
yit :: String -> YesodExample site () -> YesodSpec site Source #
Describe a single test that keeps cookies, and a reference to the last response.
Modify test site
Arguments
:: YesodDispatch site | |
=> (site -> IO (site, Middleware)) | A function from the existing site, to a new site and middleware for a WAI app. |
-> YesodExample site () |
Modifies the site (yedSite
) of the test, and creates a new WAI app (yedApp
) for it.
yesod-test allows sending requests to your application to test that it handles them correctly. In rare cases, you may wish to modify that application in the middle of a test. This may be useful if you wish to, for example, test your application under a certain configuration, then change that configuration to see if your app responds differently.
Examples
post SendEmailR -- Assert email not created in database testModifySite (\site -> pure (site { siteSettingsStoreEmail = True }, id)) post SendEmailR -- Assert email created in database
testModifySite (\site -> do middleware <- makeLogware site pure (site { appRedisConnection = Nothing }, middleware) )
Since: 1.6.8
Modify test state
testSetCookie :: SetCookie -> YesodExample site () Source #
Sets a cookie
Examples
import qualified Web.Cookie as Cookie :set -XOverloadedStrings testSetCookie Cookie.defaultSetCookie { Cookie.setCookieName = "name" }
Since: 1.6.6
testDeleteCookie :: ByteString -> YesodExample site () Source #
Deletes the cookie of the given name
Examples
:set -XOverloadedStrings testDeleteCookie "name"
Since: 1.6.6
testModifyCookies :: (Cookies -> Cookies) -> YesodExample site () Source #
Modify the current cookies with the given mapping function
Since: 1.6.6
testClearCookies :: YesodExample site () Source #
Clears the current cookies
Since: 1.6.6
Making requests
You can construct requests with the RequestBuilder
monad, which lets you
set the URL and add parameters, headers, and files. Helper functions are provided to
lookup fields by label and to add the current CSRF token from your forms.
Once built, the request can be executed with the request
method.
Convenience functions like get
and post
build and execute common requests.
get :: (Yesod site, RedirectUrl site url) => url -> YesodExample site () Source #
Perform a GET request to url
.
Examples
get HomeR
get ("http://google.com" :: Text)
post :: (Yesod site, RedirectUrl site url) => url -> YesodExample site () Source #
Perform a POST request to url
.
Examples
post HomeR
postBody :: (Yesod site, RedirectUrl site url) => url -> ByteString -> YesodExample site () Source #
Perform a POST request to url
with the given body.
Examples
postBody HomeR "foobar"
import Data.Aeson postBody HomeR (encode $ object ["age" .= (1 :: Integer)])
performMethod :: (Yesod site, RedirectUrl site url) => ByteString -> url -> YesodExample site () Source #
Perform a request using a given method to url
.
Examples
performMethod "DELETE" HomeR
Since: 1.6.3
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.)
Examples
get HomeR followRedirect
getLocation :: ParseRoute site => YesodExample site (Either Text (Route site)) Source #
Parse the Location header of the last response.
Examples
post ResourcesR (Right (ResourceR resourceId)) <- getLocation
Since: 1.5.4
request :: RequestBuilder site () -> YesodExample site () Source #
The general interface for performing requests. request
takes a RequestBuilder
,
constructs a request, and executes it.
The RequestBuilder
allows you to build up attributes of the request, like the
headers, parameters, and URL of the request.
Examples
request $ do addToken byLabel "First Name" "Felipe" setMethod "PUT" setUrl NameR
addRequestHeader :: Header -> RequestBuilder site () Source #
Adds the given header to the request; see Network.HTTP.Types.Header for creating Header
s.
Examples
import Network.HTTP.Types.Header request $ do addRequestHeader (hUserAgent, "Chrome/41.0.2228.0")
Arguments
:: CI ByteString | Username |
-> CI ByteString | Password |
-> RequestBuilder site () |
Adds a header for HTTP Basic Authentication to the request
Examples
request $ do addBasicAuthHeader "Aladdin" "OpenSesame"
Since: 1.6.7
setMethod :: Method -> RequestBuilder site () Source #
Sets the HTTP method used by the request.
Examples
request $ do setMethod "POST"
import Network.HTTP.Types.Method request $ do setMethod methodPut
addPostParam :: Text -> Text -> RequestBuilder site () Source #
Add a parameter with the given name and value to the request body.
This function can be called multiple times to add multiple parameters, and be mixed with calls to addFile
.
"Post parameter" is an informal description of what is submitted by making an HTTP POST with an HTML <form>
.
Like HTML <form>
s, yesod-test will default to a Content-Type
of application/x-www-form-urlencoded
if no files are added,
and switch to multipart/form-data
if files are added.
Calling this function after using setRequestBody
will raise an error.
Examples
{-# LANGUAGE OverloadedStrings #-} post $ do addPostParam "key" "value"
addGetParam :: Text -> Text -> RequestBuilder site () Source #
Add a parameter with the given name and value to the query string.
Examples
{-# LANGUAGE OverloadedStrings #-} request $ do addGetParam "key" "value" -- Adds ?key=value to the URL
addBareGetParam :: Text -> RequestBuilder site () Source #
Add a bare parameter with the given name and no value to the query
string. The parameter is added without an =
sign.
You can specify the entire query string literally by adding a single bare parameter and no other parameters.
Examples
{-# LANGUAGE OverloadedStrings #-} request $ do addBareGetParam "key" -- Adds ?key to the URL
Since: 1.6.16
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 () |
Add a file to be posted with the current request.
Adding a file will automatically change your request content-type to be multipart/form-data.
Examples
request $ do addFile "profile_picture" "static/img/picture.png" "img/png"
setRequestBody :: ByteString -> RequestBuilder site () Source #
Simple way to set HTTP request body
Examples
request $ do setRequestBody "foobar"
import Data.Aeson request $ do setRequestBody $ encode $ object ["age" .= (1 :: Integer)]
type RequestBuilder site = SIO (RequestBuilderData site) Source #
The RequestBuilder
state monad constructs a URL encoded string of arguments
to send with your requests. Some of the functions that run on it use the current
response to analyze the forms that the server is expecting to receive.
State + IO
Since: 1.6.0
Instances
MonadState s (SIO s) Source # | |
MonadIO (SIO s) Source # | |
Defined in Yesod.Test.Internal.SIO | |
Applicative (SIO s) Source # | |
Functor (SIO s) Source # | |
Monad (SIO s) Source # | |
MonadThrow (SIO s) Source # | |
Defined in Yesod.Test.Internal.SIO | |
MonadUnliftIO (SIO s) Source # | |
Defined in Yesod.Test.Internal.SIO | |
YesodDispatch site => Example (SIO (YesodExampleData site) a) Source # | |
Defined in Yesod.Test Associated Types type Arg (SIO (YesodExampleData site) a) # Methods evaluateExample :: SIO (YesodExampleData site) a -> Params -> (ActionWith (Arg (SIO (YesodExampleData site) a)) -> IO ()) -> ProgressCallback -> IO Result # | |
type Arg (SIO (YesodExampleData site) a) Source # | |
Defined in Yesod.Test |
setUrl :: (Yesod site, RedirectUrl site url) => url -> RequestBuilder site () Source #
Sets the URL used by the request.
Examples
request $ do setUrl HomeR
request $ do setUrl ("http://google.com/" :: Text)
clickOn :: (HasCallStack, Yesod site) => Query -> YesodExample site () Source #
Click on a link defined by a CSS query
Examples
get "/foobar" clickOn "a#idofthelink"
Since: 1.5.7
Adding fields by label
Yesod can auto generate field names, so you are never sure what the argument name should be for each one of your inputs when constructing your requests. What you do know is the label of the field. These functions let you add parameters to your request based on currently displayed label names.
Arguments
:: Text | The text contained in the |
-> Text | The value to set the parameter to. |
-> RequestBuilder site () |
Deprecated: This function seems to have multiple bugs (ref: https://github.com/yesodweb/yesod/pull/1459). Use byLabelExact, byLabelContain, byLabelPrefix or byLabelSuffix instead
Finds the <label>
with the given value, finds its corresponding <input>
, then adds a parameter
for that input to the request body.
Examples
Given this HTML, we want to submit f1=Michael
to the server:
<form method="POST"> <label for="user">Username</label> <input id="user" name="f1" /> </form>
You can set this parameter like so:
request $ do byLabel "Username" "Michael"
This function also supports the implicit label syntax, in which
the <input>
is nested inside the <label>
rather than specified with for
:
<form method="POST"> <label>Username <input name="f1"> </label> </form>
Warning: This function looks for any label that contains the provided text. If multiple labels contain that text, this function will throw an error, as in the example below:
<form method="POST"> <label for="nickname">Nickname</label> <input id="nickname" name="f1" />
<label for="nickname2">Nickname2</label> <input id="nickname2" name="f2" /> </form>
request $ do byLabel "Nickname" "Snoyberger"
Then, it throws "More than one label contained" error.
Therefore, this function is deprecated. Please consider using byLabelExact
,
which performs the exact match over the provided text.
Arguments
:: Text | The text in the |
-> Text | The value to set the parameter to. |
-> RequestBuilder site () |
Finds the <label>
with the given value, finds its corresponding <input>
, then adds a parameter
for that input to the request body.
Examples
Given this HTML, we want to submit f1=Michael
to the server:
<form method="POST"> <label for="user">Username</label> <input id="user" name="f1" /> </form>
You can set this parameter like so:
request $ do byLabel "Username" "Michael"
This function also supports the implicit label syntax, in which
the <input>
is nested inside the <label>
rather than specified with for
:
<form method="POST"> <label>Username <input name="f1"> </label> </form>
Since: 1.5.9
Arguments
:: Text | The text in the |
-> Text | The value to set the parameter to. |
-> RequestBuilder site () |
Contain version of byLabelExact
Note: Just like byLabel
, this function throws an error if it finds multiple labels
Since: 1.6.2
Arguments
:: Text | The text in the |
-> Text | The value to set the parameter to. |
-> RequestBuilder site () |
Prefix version of byLabelExact
Note: Just like byLabel
, this function throws an error if it finds multiple labels
Since: 1.6.2
Arguments
:: Text | The text in the |
-> Text | The value to set the parameter to. |
-> RequestBuilder site () |
Suffix version of byLabelExact
Note: Just like byLabel
, this function throws an error if it finds multiple labels
Since: 1.6.2
bySelectorLabelContain Source #
Arguments
:: Text | The CSS selector. |
-> Text | The text in the |
-> Text | The value to set the parameter to. |
-> RequestBuilder site () |
Note: This function throws an error if it finds multiple labels or if the CSS selector fails to parse, doesn't match any fragment, or matches multiple fragments.
Since: 1.6.15
Arguments
:: Text | The text contained in the |
-> FilePath | The path to the file. |
-> Text | The MIME type of the file, e.g. "image/png". |
-> RequestBuilder site () |
Deprecated: This function seems to have multiple bugs (ref: https://github.com/yesodweb/yesod/pull/1459). Use fileByLabelExact, fileByLabelContain, fileByLabelPrefix or fileByLabelSuffix instead
Finds the <label>
with the given value, finds its corresponding <input>
, then adds a file for that input to the request body.
Examples
Given this HTML, we want to submit a file with the parameter name f1
to the server:
<form method="POST"> <label for="imageInput">Please submit an image</label> <input id="imageInput" type="file" name="f1" accept="image/*"> </form>
You can set this parameter like so:
request $ do fileByLabel "Please submit an image" "static/img/picture.png" "img/png"
This function also supports the implicit label syntax, in which
the <input>
is nested inside the <label>
rather than specified with for
:
<form method="POST"> <label>Please submit an image <input type="file" name="f1"> </label> </form>
Warning: This function has the same issue as byLabel
. Please use fileByLabelExact
instead.
Arguments
:: Text | The text contained in the |
-> FilePath | The path to the file. |
-> Text | The MIME type of the file, e.g. "image/png". |
-> RequestBuilder site () |
Finds the <label>
with the given value, finds its corresponding <input>
, then adds a file for that input to the request body.
Examples
Given this HTML, we want to submit a file with the parameter name f1
to the server:
<form method="POST"> <label for="imageInput">Please submit an image</label> <input id="imageInput" type="file" name="f1" accept="image/*"> </form>
You can set this parameter like so:
request $ do fileByLabel "Please submit an image" "static/img/picture.png" "img/png"
This function also supports the implicit label syntax, in which
the <input>
is nested inside the <label>
rather than specified with for
:
<form method="POST"> <label>Please submit an image <input type="file" name="f1"> </label> </form>
Since: 1.5.9
Arguments
:: Text | The text contained in the |
-> FilePath | The path to the file. |
-> Text | The MIME type of the file, e.g. "image/png". |
-> RequestBuilder site () |
Contain version of fileByLabelExact
Note: Just like fileByLabel
, this function throws an error if it finds multiple labels
Since: 1.6.2
Arguments
:: Text | The text contained in the |
-> FilePath | The path to the file. |
-> Text | The MIME type of the file, e.g. "image/png". |
-> RequestBuilder site () |
Prefix version of fileByLabelExact
Note: Just like fileByLabel
, this function throws an error if it finds multiple labels
Since: 1.6.2
Arguments
:: Text | The text contained in the |
-> FilePath | The path to the file. |
-> Text | The MIME type of the file, e.g. "image/png". |
-> RequestBuilder site () |
Suffix version of fileByLabelExact
Note: Just like fileByLabel
, this function throws an error if it finds multiple labels
Since: 1.6.2
CSRF Tokens
In order to prevent CSRF exploits, yesod-form adds a hidden input to your forms with the name "_token". This token is a randomly generated, per-session value.
In order to prevent your forms from being rejected in tests, use one of these functions to add the token to your request.
addToken :: HasCallStack => RequestBuilder site () Source #
For responses that display a single form, just lookup the only CSRF token available.
Examples
request $ do addToken
addToken_ :: HasCallStack => Query -> RequestBuilder site () Source #
Lookups the hidden input named "_token" and adds its value to the params. Receives a CSS selector that should resolve to the form element containing the token.
Examples
request $ do addToken_ "#formID"
addTokenFromCookie :: HasCallStack => RequestBuilder site () Source #
Calls addTokenFromCookieNamedToHeaderNamed
with the defaultCsrfCookieName
and defaultCsrfHeaderName
.
Use this function if you're using the CSRF middleware from Yesod.Core and haven't customized the cookie or header name.
Examples
request $ do addTokenFromCookie
Since 1.4.3.2
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 request headers. An error is thrown if the cookie can't be found.
Use this function if you're using the CSRF middleware from Yesod.Core and have customized the cookie or header name.
See Yesod.Core.Handler for details on this approach to CSRF protection.
Examples
import Data.CaseInsensitive (CI) request $ do addTokenFromCookieNamedToHeaderNamed "cookieName" (CI "headerName")
Since 1.4.3.2
Assertions
assertEqual :: (HasCallStack, Eq a) => String -> a -> a -> YesodExample site () Source #
Deprecated: Use assertEq instead
assertNotEq :: (HasCallStack, Eq a, Show a) => String -> a -> a -> YesodExample site () Source #
Asserts that the two given values are not equal.
In case they are equal, the error message includes the values.
Since: 1.5.6
assertEqualNoShow :: (HasCallStack, Eq a) => String -> a -> a -> YesodExample site () Source #
Asserts that the two given values are equal.
Since: 1.5.2
assertEq :: (HasCallStack, Eq a, Show a) => String -> a -> a -> YesodExample site () Source #
Asserts that the two given values are equal.
In case they are not equal, the error message includes the two values.
Since: 1.5.2
assertHeader :: HasCallStack => CI ByteString -> ByteString -> YesodExample site () Source #
Assert the given header key/value pair was returned.
Examples
{-# LANGUAGE OverloadedStrings #-} get HomeR assertHeader "key" "value"
import qualified Data.CaseInsensitive as CI import qualified Data.ByteString.Char8 as BS8 getHomeR assertHeader (CI.mk (BS8.pack "key")) (BS8.pack "value")
assertNoHeader :: HasCallStack => CI ByteString -> YesodExample site () Source #
Assert the given header was not included in the response.
Examples
{-# LANGUAGE OverloadedStrings #-} get HomeR assertNoHeader "key"
import qualified Data.CaseInsensitive as CI import qualified Data.ByteString.Char8 as BS8 getHomeR assertNoHeader (CI.mk (BS8.pack "key"))
statusIs :: HasCallStack => Int -> YesodExample site () Source #
Assert the last response status is as expected. If the status code doesn't match, a portion of the body is also printed to aid in debugging.
Examples
get HomeR statusIs 200
bodyEquals :: HasCallStack => String -> YesodExample site () Source #
Assert the last response is exactly equal to the given text. This is useful for testing API responses.
Examples
get HomeR bodyEquals "<html><body><h1>Hello, World</h1></body></html>"
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.
Examples
get HomeR bodyContains "<h1>Foo</h1>"
bodyNotContains :: HasCallStack => String -> YesodExample site () Source #
Assert the last response doesn't have the given text. The check is performed using the response body in full text form.
Examples
get HomeR bodyNotContains "<h1>Foo</h1>
Since: 1.5.3
htmlAllContain :: HasCallStack => Query -> String -> YesodExample site () Source #
Queries the HTML using a CSS selector, and all matched elements must contain the given string.
Examples
{-# LANGUAGE OverloadedStrings #-} get HomeR htmlAllContain "p" "Hello" -- Every <p> tag contains the string "Hello"
import qualified Data.Text as T get HomeR htmlAllContain (T.pack "h1#mainTitle") "Sign Up Now!" -- All <h1> tags with the ID mainTitle contain the string "Sign Up Now!"
htmlAnyContain :: HasCallStack => Query -> String -> YesodExample site () Source #
Queries the HTML using a CSS selector, and passes if any matched element contains the given string.
Examples
{-# LANGUAGE OverloadedStrings #-} get HomeR htmlAnyContain "p" "Hello" -- At least one <p> tag contains the string "Hello"
Since 0.3.5
htmlNoneContain :: HasCallStack => Query -> String -> YesodExample site () Source #
Queries the HTML using a CSS selector, and fails if any matched element contains the given string (in other words, it is the logical inverse of htmlAnyContain).
Examples
{-# LANGUAGE OverloadedStrings #-} get HomeR htmlNoneContain ".my-class" "Hello" -- No tags with the class "my-class" contain the string "Hello"
Since 1.2.2
htmlCount :: HasCallStack => Query -> Int -> YesodExample site () Source #
Performs a CSS query on the last response and asserts the matched elements are as many as expected.
Examples
{-# LANGUAGE OverloadedStrings #-} get HomeR htmlCount "p" 3 -- There are exactly 3 <p> tags in the response
requireJSONResponse :: (HasCallStack, FromJSON a) => YesodExample site a Source #
Parses the response body from JSON into a Haskell value, throwing an error if parsing fails.
This function also checks that the Content-Type
of the response is application/json
.
Examples
get CommentR (comment :: Comment) <- requireJSONResponse
post UserR (json :: Value) <- requireJSONResponse
Since: 1.6.9
Grab information
getTestYesod :: YesodExample site site Source #
Get the foundation value used for the current test.
Since 1.2.0
getResponse :: YesodExample site (Maybe SResponse) Source #
Get the most recently provided response value, if available.
Since 1.2.0
getRequestCookies :: HasCallStack => RequestBuilder site Cookies Source #
Returns the Cookies
from the most recent request. If a request hasn't been made, an error is raised.
Examples
request $ do cookies <- getRequestCookies liftIO $ putStrLn $ "Cookies are: " ++ show cookies
Since 1.4.3.2
Debug output
printBody :: YesodExample site () Source #
Outputs the last response body to stderr (So it doesn't get captured by HSpec). Useful for debugging.
Examples
get HomeR printBody
printMatches :: HasCallStack => Query -> YesodExample site () Source #
Performs a CSS query and print the matches to stderr.
Examples
{-# LANGUAGE OverloadedStrings #-} get HomeR printMatches "h1" -- Prints all h1 tags
Utils for building your own assertions
Please consider generalizing and contributing the assertions you write.
htmlQuery :: HasCallStack => Query -> YesodExample site [HtmlLBS] Source #
Query the last response using CSS selectors, returns a list of matched fragments
parseHTML :: HtmlLBS -> Cursor Source #
Use HXT to parse a value from an HTML tag. Check for usage examples in this module's source.
withResponse :: HasCallStack => (SResponse -> YesodExample site a) -> YesodExample site a Source #
Performs a given action using the last response. Use this to create response-level assertions