sydtest-wai-0.2.0.1: A wai companion library for sydtest
Safe HaskellSafe-Inferred
LanguageHaskell2010

Test.Syd.Wai

Description

Test a Application

Example usage:

exampleApplication :: Wai.Application
exampleApplication req sendResp = do
  lb <- strictRequestBody req
  sendResp $ responseLBS HTTP.ok200 (requestHeaders req) lb

spec :: Spec
spec =
  waiClientSpec exampleApplication $
    describe "get" $
      it "can GET the root and get a 200" $ do
        resp <- get "/"
        liftIO $ responseStatus resp `shouldBe` ok200
Synopsis

Functions to run a test suite

A test suite that uses a running wai applications

waiSpec :: Application -> TestDef outers PortNumber -> TestDef outers () Source #

Run a given Application around every test.

This provides the port on which the application is running.

waiSpecWith :: (forall r. (Application -> IO r) -> IO r) -> TestDef outers PortNumber -> TestDef outers () Source #

Run a Application around every test by setting it up with the given setup function.

This provides the port on which the application is running.

waiSpecWith' :: (forall r. (Application -> IO r) -> inner -> IO r) -> TestDef outers PortNumber -> TestDef outers inner Source #

Run a Application around every test by setting it up with the given setup function that can take an argument. a This provides the port on which the application is running.

waiSpecWithSetupFunc :: SetupFunc Application -> TestDef outers PortNumber -> TestDef outers () Source #

Run a Application around every test by setting it up with the given SetupFunc. a This provides the port on which the application is running.

A test suite that uses a running wai application and calls it using the functions provided in this package

waiClientSpec :: Application -> TestDefM (Manager ': outers) (WaiClient ()) result -> TestDefM outers oldInner result Source #

Run a given Application around every test.

This provides a 'WaiClient ()' which contains the port of the running application.

waiClientSpecWith :: IO Application -> TestDefM (Manager ': outers) (WaiClient ()) result -> TestDefM outers oldInner result Source #

Run a given Application, as built by the given action, around every test.

waiClientSpecWithSetupFunc :: (Manager -> oldInner -> SetupFunc (Application, env)) -> TestDefM (Manager ': outers) (WaiClient env) result -> TestDefM outers oldInner result Source #

Run a given Application, as built by the given SetupFunc, around every test.

waiClientSpecWithSetupFunc' :: (Manager -> oldInner -> SetupFunc (Application, env)) -> TestDefM (Manager ': outers) (WaiClient env) result -> TestDefM (Manager ': outers) oldInner result Source #

Run a given Application, as built by the given SetupFunc, around every test.

This function doesn't set up the Manager like waiClientSpecWithSetupFunc does.

A test suite that uses a single HTTP manager accross tests

managerSpec :: TestDefM (Manager ': outers) inner result -> TestDefM outers inner result Source #

Create a Manager before all tests in the given group.

Setup functions

waiClientSetupFunc :: Manager -> Application -> env -> SetupFunc (WaiClient env) Source #

A SetupFunc for a WaiClient, given an Application and user-defined env.

applicationSetupFunc :: Application -> SetupFunc PortNumber Source #

A SetupFunc to run an application and provide its port.

Core

data WaiClient env Source #

A client environment for a Application with a user-defined environment as well

Constructors

WaiClient 

Fields

Instances

Instances details
Generic (WaiClient env) Source # 
Instance details

Defined in Test.Syd.Wai.Client

Associated Types

type Rep (WaiClient env) :: Type -> Type #

Methods

from :: WaiClient env -> Rep (WaiClient env) x #

to :: Rep (WaiClient env) x -> WaiClient env #

MonadReader (WaiClient env) (WaiClientM env) Source # 
Instance details

Defined in Test.Syd.Wai.Client

Methods

ask :: WaiClientM env (WaiClient env) #

local :: (WaiClient env -> WaiClient env) -> WaiClientM env a -> WaiClientM env a #

reader :: (WaiClient env -> a) -> WaiClientM env a #

type Rep (WaiClient env) Source # 
Instance details

Defined in Test.Syd.Wai.Client

type Rep (WaiClient env) = D1 ('MetaData "WaiClient" "Test.Syd.Wai.Client" "sydtest-wai-0.2.0.1-JOOxDw3gaCGJOcTMzLiL4T" 'False) (C1 ('MetaCons "WaiClient" 'PrefixI 'True) (S1 ('MetaSel ('Just "waiClientManager") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Manager) :*: (S1 ('MetaSel ('Just "waiClientEnv") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 env) :*: S1 ('MetaSel ('Just "waiClientPort") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PortNumber))))

data WaiClientState Source #

Constructors

WaiClientState 

Fields

Instances

Instances details
Generic WaiClientState Source # 
Instance details

Defined in Test.Syd.Wai.Client

Associated Types

type Rep WaiClientState :: Type -> Type #

MonadState WaiClientState (WaiClientM env) Source # 
Instance details

Defined in Test.Syd.Wai.Client

type Rep WaiClientState Source # 
Instance details

Defined in Test.Syd.Wai.Client

type Rep WaiClientState = D1 ('MetaData "WaiClientState" "Test.Syd.Wai.Client" "sydtest-wai-0.2.0.1-JOOxDw3gaCGJOcTMzLiL4T" 'False) (C1 ('MetaCons "WaiClientState" 'PrefixI 'True) (S1 ('MetaSel ('Just "waiClientStateLast") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (Request, Response ByteString))) :*: S1 ('MetaSel ('Just "waiClientStateCookies") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CookieJar)))

newtype WaiClientM env a Source #

A Wai testing monad that carries client state, information about how to call the application, a user-defined environment, and everything necessary to show nice error messages.

Constructors

WaiClientM 

Instances

Instances details
MonadState WaiClientState (WaiClientM env) Source # 
Instance details

Defined in Test.Syd.Wai.Client

MonadFail (WaiClientM env) Source # 
Instance details

Defined in Test.Syd.Wai.Client

Methods

fail :: String -> WaiClientM env a #

MonadIO (WaiClientM env) Source # 
Instance details

Defined in Test.Syd.Wai.Client

Methods

liftIO :: IO a -> WaiClientM env a #

Applicative (WaiClientM env) Source # 
Instance details

Defined in Test.Syd.Wai.Client

Methods

pure :: a -> WaiClientM env a #

(<*>) :: WaiClientM env (a -> b) -> WaiClientM env a -> WaiClientM env b #

liftA2 :: (a -> b -> c) -> WaiClientM env a -> WaiClientM env b -> WaiClientM env c #

(*>) :: WaiClientM env a -> WaiClientM env b -> WaiClientM env b #

(<*) :: WaiClientM env a -> WaiClientM env b -> WaiClientM env a #

Functor (WaiClientM env) Source # 
Instance details

Defined in Test.Syd.Wai.Client

Methods

fmap :: (a -> b) -> WaiClientM env a -> WaiClientM env b #

(<$) :: a -> WaiClientM env b -> WaiClientM env a #

Monad (WaiClientM env) Source # 
Instance details

Defined in Test.Syd.Wai.Client

Methods

(>>=) :: WaiClientM env a -> (a -> WaiClientM env b) -> WaiClientM env b #

(>>) :: WaiClientM env a -> WaiClientM env b -> WaiClientM env b #

return :: a -> WaiClientM env a #

MonadReader (WaiClient env) (WaiClientM env) Source # 
Instance details

Defined in Test.Syd.Wai.Client

Methods

ask :: WaiClientM env (WaiClient env) #

local :: (WaiClient env -> WaiClient env) -> WaiClientM env a -> WaiClientM env a #

reader :: (WaiClient env -> a) -> WaiClientM env a #

IsTest (WaiClientM env ()) Source # 
Instance details

Defined in Test.Syd.Wai.Client

Associated Types

type Arg1 (WaiClientM env ()) #

type Arg2 (WaiClientM env ()) #

Methods

runTest :: WaiClientM env () -> TestRunSettings -> ProgressReporter -> ((Arg1 (WaiClientM env ()) -> Arg2 (WaiClientM env ()) -> IO ()) -> IO ()) -> IO TestRunResult #

IsTest (outerArgs -> WaiClientM env ()) Source # 
Instance details

Defined in Test.Syd.Wai.Client

Associated Types

type Arg1 (outerArgs -> WaiClientM env ()) #

type Arg2 (outerArgs -> WaiClientM env ()) #

Methods

runTest :: (outerArgs -> WaiClientM env ()) -> TestRunSettings -> ProgressReporter -> ((Arg1 (outerArgs -> WaiClientM env ()) -> Arg2 (outerArgs -> WaiClientM env ()) -> IO ()) -> IO ()) -> IO TestRunResult #

type Arg1 (WaiClientM env ()) Source # 
Instance details

Defined in Test.Syd.Wai.Client

type Arg1 (WaiClientM env ()) = ()
type Arg1 (outerArgs -> WaiClientM env ()) Source # 
Instance details

Defined in Test.Syd.Wai.Client

type Arg1 (outerArgs -> WaiClientM env ()) = outerArgs
type Arg2 (WaiClientM env ()) Source # 
Instance details

Defined in Test.Syd.Wai.Client

type Arg2 (WaiClientM env ()) = WaiClient env
type Arg2 (outerArgs -> WaiClientM env ()) Source # 
Instance details

Defined in Test.Syd.Wai.Client

type Arg2 (outerArgs -> WaiClientM env ()) = WaiClient env

runWaiClientM :: WaiClient env -> WaiClientM env a -> IO a Source #

Run a WaiClientM env using a WaiClient env

Making requests

get :: ByteString -> WaiSession st (Response ByteString) Source #

Perform a GET request to the application under test.

post :: ByteString -> ByteString -> WaiSession st (Response ByteString) Source #

Perform a POST request to the application under test.

put :: ByteString -> ByteString -> WaiSession st (Response ByteString) Source #

Perform a PUT request to the application under test.

patch :: ByteString -> ByteString -> WaiSession st (Response ByteString) Source #

Perform a PATCH request to the application under test.

options :: ByteString -> WaiSession st (Response ByteString) Source #

Perform an OPTIONS request to the application under test.

delete :: ByteString -> WaiSession st (Response ByteString) Source #

Perform a DELETE request to the application under test.

request :: Method -> ByteString -> [Header] -> ByteString -> WaiSession st (Response ByteString) Source #

Perform a request to the application under test, with specified HTTP method, request path, headers and body.

performRequest :: Request -> WaiSession st (Response ByteString) Source #

Perform a bare Request.

You can use this to make a request to an application other than the one under test. This function does not set the host and port of the request like request does, but it does share a CookieJar.

Assertions

data MatchHeader Source #

Constructors

MatchHeader ([Header] -> Body -> Maybe String) 

data MatchBody Source #

Constructors

MatchBody ([Header] -> Body -> Maybe String) 

Instances

Instances details
IsString MatchBody Source # 
Instance details

Defined in Test.Syd.Wai.Matcher

shouldRespondWith :: HasCallStack => WaiSession st (Response ByteString) -> ResponseMatcher -> WaiExpectation st Source #

Make a test assertion using a ResponseMatcher on the Response produced by the given action

This function is provided for backward compatibility with wai-test but this approach has been made obsolete by the way sydtest does things. You should use shouldBe based on the responses that you get from functions like get and post instead.

Just to make sure we didn't forget any exports

Reexports