| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Test.Syd.Yesod.Def
Synopsis
- yesodSpec :: YesodDispatch site => site -> YesodSpec site -> Spec
- yesodSpecWithSiteGenerator :: YesodDispatch site => IO site -> YesodSpec site -> Spec
- yesodSpecWithSiteGeneratorAndArgument :: YesodDispatch site => (a -> IO site) -> YesodSpec site -> SpecWith a
- yesodSpecWithSiteSupplier :: YesodDispatch site => (forall r. (site -> IO r) -> IO r) -> YesodSpec site -> Spec
- yesodSpecWithSiteSupplierWith :: YesodDispatch site => (forall r. (site -> IO r) -> inner -> IO r) -> YesodSpec site -> SpecWith inner
- yesodSpecWithSiteSetupFunc :: YesodDispatch site => (Manager -> SetupFunc site) -> TestDef (Manager ': outers) (YesodClient site) -> TestDef (Manager ': outers) ()
- yesodSpecWithSiteSetupFunc' :: YesodDispatch site => (Manager -> inner -> SetupFunc site) -> TestDef (Manager ': outers) (YesodClient site) -> TestDef (Manager ': outers) inner
- yesodClientSetupFunc :: YesodDispatch site => Manager -> site -> SetupFunc (YesodClient site)
- type YesodSpec site = TestDef '[Manager] (YesodClient site)
- yit :: forall site. HasCallStack => String -> YesodClientM site () -> YesodSpec site
- ydescribe :: String -> YesodSpec site -> YesodSpec site
Documentation
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 200This 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 200This 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 200yesodSpecWithSiteSupplierWith :: YesodDispatch site => (forall r. (site -> IO r) -> inner -> IO r) -> YesodSpec site -> SpecWith inner Source #
Using a function that supplies a site, based on an inner resource, run a test suite.
yesodSpecWithSiteSetupFunc :: YesodDispatch site => (Manager -> SetupFunc site) -> TestDef (Manager ': outers) (YesodClient site) -> TestDef (Manager ': outers) () Source #
Using a function that supplies a site, using a SetupFunc
This function assumed that you've already set up the Manager beforehand using something like managerSpec.
yesodSpecWithSiteSetupFunc' :: YesodDispatch site => (Manager -> inner -> SetupFunc site) -> TestDef (Manager ': outers) (YesodClient site) -> TestDef (Manager ': outers) inner Source #
Using a function that supplies a site, using a SetupFunc.
This function assumed that you've already set up the Manager beforehand using something like managerSpec.
yesodClientSetupFunc :: YesodDispatch site => Manager -> site -> SetupFunc (YesodClient site) Source #
type YesodSpec site = TestDef '[Manager] (YesodClient site) Source #
For backward compatibility with yesod-test
yit :: forall site. HasCallStack => String -> YesodClientM site () -> YesodSpec site Source #