servant-quickcheck-0.0.4: 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 k a => HasGenRequest * ((:>) k * (BasicAuth x y) a) Source # 

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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