servant-mock-0.8.2: Derive a mock server for free from your servant API types

Copyright2015 Alp Mestanogullari
LicenseBSD3
MaintainerAlp Mestanogullari <alpmestan@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Servant.Mock

Contents

Description

Automatically derive a mock webserver that implements some API type, just from the said API type's definition.

Using this module couldn't be simpler. Given some API type, like:

type API = "user" :> Get '[JSON] User

that describes your web application, all you have to do is define a Proxy to it:

myAPI :: Proxy API
myAPI = Proxy

and call mock, which has the following type:

mock :: HasMock api context => Proxy api -> Proxy context -> Server api

What this says is, given some API type api that it knows it can "mock", mock hands you an implementation of the API type. It does so by having each request handler generate a random value of the appropriate type (User in our case). All you need for this to work is to provide Arbitrary instances for the data types returned as response bodies, hence appearing next to Delete, Get, Patch, Post and Put.

To put this all to work and run the mock server, just call serve on the result of mock to get an Application that you can then run with warp.

main :: IO ()
main = Network.Wai.Handler.Warp.run 8080 $
  serve myAPI (mock myAPI Proxy)

Synopsis

Documentation

class HasServer api context => HasMock api context where Source #

HasMock defines an interpretation of API types than turns them into random-response-generating request handlers, hence providing an instance for all the combinators of the core servant library.

Minimal complete definition

mock

Methods

mock :: Proxy api -> Proxy context -> Server api Source #

Calling this method creates request handlers of the right type to implement the API described by api that just generate random response values of the right type. E.g:

  type API = "user" :> Get '[JSON] User
        :| "book" :> Get '[JSON] Book

  api :: Proxy API
  api = Proxy

  -- let's say we will start with the frontend,
  -- and hence need a placeholder server
  server :: Server API
  server = mock api Proxy
  

What happens here is that Server API actually "means" 2 request handlers, of the following types:

  getUser :: Handler User
  getBook :: Handler Book
  

So under the hood, mock uses the IO bit to generate random values of type User and Book every time these endpoints are requested.

Instances

HasMock * EmptyAPI context Source # 

Methods

mock :: Proxy EmptyAPI context -> Proxy [*] context -> Server EmptyAPI context Source #

HasMock * Raw context Source # 

Methods

mock :: Proxy Raw context -> Proxy [*] context -> Server Raw context Source #

(HasMock * a context, HasMock * b context) => HasMock * ((:<|>) a b) context Source # 

Methods

mock :: Proxy (a :<|> b) context -> Proxy [*] context -> Server (a :<|> b) context Source #

(HasContextEntry context (NamedContext name subContext), HasMock * rest subContext) => HasMock * (WithNamedContext name subContext rest) context Source # 

Methods

mock :: Proxy (WithNamedContext name subContext rest) context -> Proxy [*] context -> Server (WithNamedContext name subContext rest) context Source #

(KnownSymbol h, FromHttpApiData a, HasMock k rest context) => HasMock * ((:>) k * (Header h a) rest) context Source # 

Methods

mock :: Proxy ((k :> *) (Header h a) rest) context -> Proxy [*] context -> Server ((k :> *) (Header h a) rest) context Source #

(KnownSymbol s, HasMock k rest context) => HasMock * ((:>) k * (QueryFlag s) rest) context Source # 

Methods

mock :: Proxy ((k :> *) (QueryFlag s) rest) context -> Proxy [*] context -> Server ((k :> *) (QueryFlag s) rest) context Source #

(KnownSymbol s, FromHttpApiData a, HasMock k rest context) => HasMock * ((:>) k * (QueryParams * s a) rest) context Source # 

Methods

mock :: Proxy ((k :> *) (QueryParams * s a) rest) context -> Proxy [*] context -> Server ((k :> *) (QueryParams * s a) rest) context Source #

(KnownSymbol s, FromHttpApiData a, HasMock k rest context) => HasMock * ((:>) k * (QueryParam * s a) rest) context Source # 

Methods

mock :: Proxy ((k :> *) (QueryParam * s a) rest) context -> Proxy [*] context -> Server ((k :> *) (QueryParam * s a) rest) context Source #

HasMock k rest context => HasMock * ((:>) k * HttpVersion rest) context Source # 

Methods

mock :: Proxy ((k :> *) HttpVersion rest) context -> Proxy [*] context -> Server ((k :> *) HttpVersion rest) context Source #

HasMock k rest context => HasMock * ((:>) k * Vault rest) context Source # 

Methods

mock :: Proxy ((k :> *) Vault rest) context -> Proxy [*] context -> Server ((k :> *) Vault rest) context Source #

HasMock k rest context => HasMock * ((:>) k * IsSecure rest) context Source # 

Methods

mock :: Proxy ((k :> *) IsSecure rest) context -> Proxy [*] context -> Server ((k :> *) IsSecure rest) context Source #

HasMock k rest context => HasMock * ((:>) k * RemoteHost rest) context Source # 

Methods

mock :: Proxy ((k :> *) RemoteHost rest) context -> Proxy [*] context -> Server ((k :> *) RemoteHost rest) context Source #

(AllCTUnrender ctypes a, HasMock k rest context) => HasMock * ((:>) k * (ReqBody * ctypes a) rest) context Source # 

Methods

mock :: Proxy ((k :> *) (ReqBody * ctypes a) rest) context -> Proxy [*] context -> Server ((k :> *) (ReqBody * ctypes a) rest) context Source #

(KnownSymbol s, FromHttpApiData a, HasMock k rest context) => HasMock * ((:>) k * (CaptureAll * s a) rest) context Source # 

Methods

mock :: Proxy ((k :> *) (CaptureAll * s a) rest) context -> Proxy [*] context -> Server ((k :> *) (CaptureAll * s a) rest) context Source #

(KnownSymbol s, FromHttpApiData a, HasMock k rest context) => HasMock * ((:>) k * (Capture * s a) rest) context Source # 

Methods

mock :: Proxy ((k :> *) (Capture * s a) rest) context -> Proxy [*] context -> Server ((k :> *) (Capture * s a) rest) context Source #

(KnownSymbol path, HasMock k rest context) => HasMock * ((:>) k Symbol path rest) context Source # 

Methods

mock :: Proxy ((k :> Symbol) path rest) context -> Proxy [*] context -> Server ((k :> Symbol) path rest) context Source #

(GetHeaders (Headers headerTypes a), Arbitrary (HList headerTypes), Arbitrary a, KnownNat status, ReflectMethod k1 method, AllCTRender ctypes a) => HasMock * (Verb * k1 method status ctypes (Headers headerTypes a)) context Source # 

Methods

mock :: Proxy (Verb * k1 method status ctypes (Headers headerTypes a)) context -> Proxy [*] context -> Server (Verb * k1 method status ctypes (Headers headerTypes a)) context Source #

(Arbitrary a, KnownNat status, ReflectMethod k1 method, AllCTRender ctypes a) => HasMock * (Verb * k1 method status ctypes a) context Source # 

Methods

mock :: Proxy (Verb * k1 method status ctypes a) context -> Proxy [*] context -> Server (Verb * k1 method status ctypes a) context Source #

Orphan instances

Arbitrary NoContent Source # 
(Arbitrary a, Arbitrary (HList hs)) => Arbitrary (HList ((:) * (Header h a) hs)) Source # 

Methods

arbitrary :: Gen (HList ((* ': Header h a) hs)) #

shrink :: HList ((* ': Header h a) hs) -> [HList ((* ': Header h a) hs)] #

Arbitrary (HList ([] *)) Source # 

Methods

arbitrary :: Gen (HList [*]) #

shrink :: HList [*] -> [HList [*]] #

(Arbitrary (HList ls), Arbitrary a) => Arbitrary (Headers ls a) Source # 

Methods

arbitrary :: Gen (Headers ls a) #

shrink :: Headers ls a -> [Headers ls a] #