servant-quickcheck-0.0.4.1: QuickCheck entire APIs

Safe HaskellNone
LanguageHaskell2010

Servant.QuickCheck.Internal.HasGenRequest

Synopsis

Documentation

runGenRequest :: HasGenRequest a => Proxy a -> Gen (BaseUrl -> Request) Source #

This function returns a QuickCheck `Gen a` when passed a servant API value, typically a `Proxy API`. The generator returned is a function that accepts a BaseUrl and returns a Request, which can then be used to issue network requests. This Gen type makes it easier to compare distinct APIs across different BaseUrls.

class HasGenRequest a where Source #

This is the core Servant-Quickcheck generator, which, when given a `Proxy API` will return a pair of Int and `Gen a`, where a is a function from BaseUrl to a Request. The Int is a weight for the QuickCheck frequency function which ensures a random distribution across all endpoints in an API.

Minimal complete definition

genRequest

Methods

genRequest :: Proxy a -> (Int, Gen (BaseUrl -> Request)) Source #

Instances

HasGenRequest * EmptyAPI Source # 
(HasGenRequest * a, HasGenRequest * b) => HasGenRequest * ((:<|>) a b) Source # 

Methods

genRequest :: Proxy (a :<|> b) a -> (Int, Gen (BaseUrl -> Request)) Source #

HasGenRequest * a => HasGenRequest * (WithNamedContext x y a) Source # 

Methods

genRequest :: Proxy (WithNamedContext x y a) a -> (Int, Gen (BaseUrl -> Request)) Source #

HasGenRequest k1 a => HasGenRequest * ((:>) * k1 (BasicAuth x y) a) Source # 

Methods

genRequest :: Proxy ((* :> k1) (BasicAuth x y) a) a -> (Int, Gen (BaseUrl -> Request)) Source #

HasGenRequest k1 a => HasGenRequest * ((:>) * k1 Vault a) Source # 

Methods

genRequest :: Proxy ((* :> k1) Vault a) a -> (Int, Gen (BaseUrl -> Request)) Source #

HasGenRequest k1 a => HasGenRequest * ((:>) * k1 HttpVersion a) Source # 

Methods

genRequest :: Proxy ((* :> k1) HttpVersion a) a -> (Int, Gen (BaseUrl -> Request)) Source #

HasGenRequest k1 a => HasGenRequest * ((:>) * k1 IsSecure a) Source # 

Methods

genRequest :: Proxy ((* :> k1) IsSecure a) a -> (Int, Gen (BaseUrl -> Request)) Source #

HasGenRequest k1 a => HasGenRequest * ((:>) * k1 RemoteHost a) Source # 

Methods

genRequest :: Proxy ((* :> k1) RemoteHost a) a -> (Int, Gen (BaseUrl -> Request)) Source #

(KnownSymbol x, HasGenRequest k1 b) => HasGenRequest * ((:>) * k1 (QueryFlag x) b) Source # 

Methods

genRequest :: Proxy ((* :> k1) (QueryFlag x) b) a -> (Int, Gen (BaseUrl -> Request)) Source #

(KnownSymbol x, Arbitrary c, ToHttpApiData c, HasGenRequest k1 b) => HasGenRequest * ((:>) * k1 (QueryParams * x c) b) Source # 

Methods

genRequest :: Proxy ((* :> k1) (QueryParams * x c) b) a -> (Int, Gen (BaseUrl -> Request)) Source #

(KnownSymbol x, Arbitrary c, ToHttpApiData c, HasGenRequest k1 b) => HasGenRequest * ((:>) * k1 (QueryParam * x c) b) Source # 

Methods

genRequest :: Proxy ((* :> k1) (QueryParam * x c) b) a -> (Int, Gen (BaseUrl -> Request)) Source #

(AllMimeRender x c, Arbitrary c, HasGenRequest k1 b) => HasGenRequest * ((:>) * k1 (ReqBody * x c) b) Source # 

Methods

genRequest :: Proxy ((* :> k1) (ReqBody * x c) b) a -> (Int, Gen (BaseUrl -> Request)) Source #

(Arbitrary c, KnownSymbol h, HasGenRequest k1 b, ToHttpApiData c) => HasGenRequest * ((:>) * k1 (Header h c) b) Source # 

Methods

genRequest :: Proxy ((* :> k1) (Header h c) b) a -> (Int, Gen (BaseUrl -> Request)) Source #

(Arbitrary c, HasGenRequest k1 b, ToHttpApiData c) => HasGenRequest * ((:>) * k1 (CaptureAll * x c) b) Source # 

Methods

genRequest :: Proxy ((* :> k1) (CaptureAll * x c) b) a -> (Int, Gen (BaseUrl -> Request)) Source #

(Arbitrary c, HasGenRequest k1 b, ToHttpApiData c) => HasGenRequest * ((:>) * k1 (Capture * x c) b) Source # 

Methods

genRequest :: Proxy ((* :> k1) (Capture * x c) b) a -> (Int, Gen (BaseUrl -> Request)) Source #

HasGenRequest k1 api => HasGenRequest * ((:>) * k1 (Description d) api) Source # 

Methods

genRequest :: Proxy ((* :> k1) (Description d) api) a -> (Int, Gen (BaseUrl -> Request)) Source #

HasGenRequest k1 api => HasGenRequest * ((:>) * k1 (Summary d) api) Source # 

Methods

genRequest :: Proxy ((* :> k1) (Summary d) api) a -> (Int, Gen (BaseUrl -> Request)) Source #

(KnownSymbol path, HasGenRequest k1 b) => HasGenRequest * ((:>) Symbol k1 path b) Source # 

Methods

genRequest :: Proxy ((Symbol :> k1) path b) a -> (Int, Gen (BaseUrl -> Request)) Source #

ReflectMethod k2 method => HasGenRequest * (Verb k2 k1 method status cts a) Source # 

Methods

genRequest :: Proxy (Verb k2 k1 method status cts a) a -> (Int, Gen (BaseUrl -> Request)) Source #