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

Test.Syd.Yesod

Description

Testing a yesod site.

For a fully-worked example, see sydtest-yesod/blog-example.

Synopsis

Functions to run a test suite

yesodSpec :: YesodDispatch site => site -> YesodSpec site -> Spec Source #

Run a test suite using the given site.

If your site contains any resources that need to be set up, you probably want to be using one of the following functions instead.

Example usage with a minimal yesod App:

{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings     #-}
{-# LANGUAGE QuasiQuotes           #-}
{-# LANGUAGE TemplateHaskell       #-}
{-# LANGUAGE TypeFamilies          #-}

module Minimal where

import Yesod
import Test.Syd

data App = App -- | Empty App type

mkYesod "App" [parseRoutes|
    / HomeR GET
|]

instance Yesod App

getHomeR :: Handler Html
getHomeR = "Hello, world!"

main :: IO ()
main = Yesod.warp 3000 App

testMain :: IO ()
testMain = sydTest spec

spec :: Spec
spec = yesodSpec App $ do
  it "returns 200 on the homepage" $ do
    get HomeR
    statusIs 200

This function exists for backward compatibility with yesod-test.

yesodSpecWithSiteGenerator :: YesodDispatch site => IO site -> YesodSpec site -> Spec Source #

Run a test suite using the given site generator.

If your site contains any resources that you will want to have set up beforhand, you will probably want to use yesodSpecWithSiteGeneratorAndArgument or yesodSpecWithSiteSupplierWith instead.

Example usage with a yesod App that contains a secret key that is generated at startup but not used during tests:

data Key = Key -- The implementation of the actual key is omitted here for brevity.
genKey :: IO Key
genKey = pure Key

data App = App { appSecretKey :: Key }

genApp :: IO App
genApp = App <$> genKey

main :: IO ()
main = sydTest spec

spec :: Spec
spec = yesodSpecWithSiteGenerator genApp $ do
  it "returns 200 on the homepage" $ do
    get HomeR
    statusIs 200

This function exists for backward compatibility with yesod-test.

yesodSpecWithSiteGeneratorAndArgument :: YesodDispatch site => (a -> IO site) -> YesodSpec site -> SpecWith a Source #

Run a test suite using the given site generator which uses an inner resource.

If your site contains any resources that you need to set up using a withX function, you will want to use yesodSpecWithSiteSupplier instead.

This function exists for backward compatibility with yesod-test.

yesodSpecWithSiteSupplier :: YesodDispatch site => (forall r. (site -> IO r) -> IO r) -> YesodSpec site -> Spec Source #

Using a function that supplies a site, run a test suite.

Example usage with a yesod App that contains an sqlite database connection. See 'sydtest-persistent-sqlite'.

import Test.Syd.Persistent.Sqlite

data App = App { appConnectionPool :: ConnectionPool }

main :: IO ()
main = sydTest spec

appSupplier :: (App -> IO r) -> IO r
appSupplier func =
  withConnectionPool myMigration $ \pool ->
    func $ App { appConnectionPool = pool}

spec :: Spec
spec = yesodSpecWithSiteSupplier appSupplier $ do
  it "returns 200 on the homepage" $ do
    get HomeR
    statusIs 200

yesodSpecWithSiteSupplierWith :: YesodDispatch site => (forall r. (site -> IO r) -> a -> IO r) -> YesodSpec site -> SpecWith a Source #

Using a function that supplies a site, based on an inner resource, run a test suite.

yesodSpecWithSiteSetupFunc :: YesodDispatch site => (Manager -> SetupFunc a site) -> TestDef (Manager ': l) (YesodClient site) -> TestDef l a Source #

Using a function that supplies a site, using a SetupFunc

yesodSpecWithSiteSetupFunc' :: YesodDispatch site => (Manager -> SetupFunc a site) -> TestDef (Manager ': l) (YesodClient site) -> TestDef (Manager ': l) a Source #

Using a function that supplies a site, using a SetupFunc but without setting up the Manager beforehand.

This function assumed that you've already set up the Manager beforehand using something like managerSpec.

Setup functions

Core

type YesodSpec site = TestDef '[Manager] (YesodClient site) Source #

For backward compatibility with yesod-test

data YesodClient site Source #

A client environment to call a Yesod app.

Constructors

YesodClient 

Fields

Instances

Instances details
MonadReader (YesodClient site) (YesodClientM site) Source # 
Instance details

Defined in Test.Syd.Yesod.Client

Methods

ask :: YesodClientM site (YesodClient site) #

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

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

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 #

newtype YesodClientM site a Source #

A monad to call a Yesod app.

This has access to a 'YesodClient site'.

Constructors

YesodClientM 

Instances

Instances details
Monad (YesodClientM site) Source # 
Instance details

Defined in Test.Syd.Yesod.Client

Methods

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

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

return :: a -> YesodClientM site a #

Functor (YesodClientM site) Source # 
Instance details

Defined in Test.Syd.Yesod.Client

Methods

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

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

MonadFail (YesodClientM site) Source # 
Instance details

Defined in Test.Syd.Yesod.Client

Methods

fail :: String -> YesodClientM site a #

Applicative (YesodClientM site) Source # 
Instance details

Defined in Test.Syd.Yesod.Client

Methods

pure :: a -> YesodClientM site a #

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

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

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

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

MonadIO (YesodClientM site) Source # 
Instance details

Defined in Test.Syd.Yesod.Client

Methods

liftIO :: IO a -> YesodClientM site a #

MonadThrow (YesodClientM site) Source # 
Instance details

Defined in Test.Syd.Yesod.Client

Methods

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

MonadState (YesodClientState site) (YesodClientM site) Source # 
Instance details

Defined in Test.Syd.Yesod.Client

Methods

get :: YesodClientM site (YesodClientState site) #

put :: YesodClientState site -> YesodClientM site () #

state :: (YesodClientState site -> (a, YesodClientState site)) -> YesodClientM site a #

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

Defined in Test.Syd.Yesod.Client

Methods

ask :: YesodClientM site (YesodClient site) #

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

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

runYesodClientM :: YesodClient site -> YesodClientM site a -> IO a Source #

Run a YesodClientM site using a YesodClient site

type YesodExample site a = YesodClientM site a Source #

For backward compatibility

Helper functions to define tests

yit :: forall site e. (HasCallStack, IsTest (YesodClient site -> IO e), Arg1 (YesodClient site -> IO e) ~ (), Arg2 (YesodClient site -> IO e) ~ YesodClient site) => String -> YesodClientM site e -> YesodSpec site Source #

Define a test in the 'YesodClientM site' monad instead of IO.

ydescribe :: String -> YesodSpec site -> YesodSpec site Source #

For backward compatibility

ydescribe = describe

Making requests

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

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

Using the request builder

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.

Helpers

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

Perform a request using an arbitrary method for the given route.

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.

Types

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 #

runRequestBuilder :: RequestBuilder site a -> YesodClientM site Request Source #

Run a RequestBuilder to make the Request that it defines.

Token

addToken :: HasCallStack => RequestBuilder site () Source #

Look up the CSRF token from the only form data and add it to the request header

addToken_ :: HasCallStack => Text -> RequestBuilder site () Source #

Look up the CSRF token from the given 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.

Queries

getRequest :: YesodClientM site (Maybe Request) Source #

Get the most recently sent request.

getResponse :: YesodClientM site (Maybe (Response ByteString)) Source #

Get the most recently received response.

getLocation :: ParseRoute site => YesodClientM site (Either Text (Route site)) Source #

Get the Location header of most recently received response.

getLast :: YesodClientM site (Maybe (Request, Response ByteString)) Source #

Get the most recently sent request and the response to it.

Declaring assertions

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.

Reexports