Copyright | 2015 Alp Mestanogullari |
---|---|
License | BSD3 |
Maintainer | Alp Mestanogullari <alpmestan@gmail.com> |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
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)
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.
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
actually "means" 2 request handlers, of the following types:Server
API
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 Raw context Source # | |
HasMock EmptyAPI context Source # | |
(HasMock a context, HasMock b context) => HasMock (a :<|> b :: Type) context Source # | |
(HasContextEntry context (NamedContext name subContext), HasMock rest subContext) => HasMock (WithNamedContext name subContext rest :: Type) context Source # | |
Defined in Servant.Mock mock :: Proxy (WithNamedContext name subContext rest) -> Proxy context -> Server (WithNamedContext name subContext rest) Source # | |
HasMock rest context => HasMock (HttpVersion :> rest :: Type) context Source # | |
Defined in Servant.Mock mock :: Proxy (HttpVersion :> rest) -> Proxy context -> Server (HttpVersion :> rest) Source # | |
(MimeUnrender ctype chunk, FramingUnrender fr, FromSourceIO chunk a, HasMock rest context) => HasMock (StreamBody' mods fr ctype a :> rest :: Type) context Source # | Since: 0.8.5 |
Defined in Servant.Mock mock :: Proxy (StreamBody' mods fr ctype a :> rest) -> Proxy context -> Server (StreamBody' mods fr ctype a :> rest) Source # | |
(AllCTUnrender ctypes a, HasMock rest context, SBoolI (FoldLenient mods)) => HasMock (ReqBody' mods ctypes a :> rest :: Type) context Source # | |
HasMock rest context => HasMock (RemoteHost :> rest :: Type) context Source # | |
Defined in Servant.Mock mock :: Proxy (RemoteHost :> rest) -> Proxy context -> Server (RemoteHost :> rest) Source # | |
(KnownSymbol s, FromHttpApiData a, HasMock rest context, SBoolI (FoldRequired mods), SBoolI (FoldLenient mods)) => HasMock (QueryParam' mods s a :> rest :: Type) context Source # | |
Defined in Servant.Mock mock :: Proxy (QueryParam' mods s a :> rest) -> Proxy context -> Server (QueryParam' mods s a :> rest) Source # | |
(KnownSymbol s, FromHttpApiData a, HasMock rest context) => HasMock (QueryParams s a :> rest :: Type) context Source # | |
Defined in Servant.Mock mock :: Proxy (QueryParams s a :> rest) -> Proxy context -> Server (QueryParams s a :> rest) Source # | |
(KnownSymbol s, HasMock rest context) => HasMock (QueryFlag s :> rest :: Type) context Source # | |
(KnownSymbol h, FromHttpApiData a, HasMock rest context, SBoolI (FoldRequired mods), SBoolI (FoldLenient mods)) => HasMock (Header' mods h a :> rest :: Type) context Source # | |
HasMock rest context => HasMock (IsSecure :> rest :: Type) context Source # | |
HasMock api context => HasMock (Summary d :> api :: Type) context Source # | |
HasMock api context => HasMock (Description d :> api :: Type) context Source # | |
Defined in Servant.Mock mock :: Proxy (Description d :> api) -> Proxy context -> Server (Description d :> api) Source # | |
(KnownSymbol s, FromHttpApiData a, HasMock rest context) => HasMock (Capture' mods s a :> rest :: Type) context Source # | |
(KnownSymbol s, FromHttpApiData a, HasMock rest context) => HasMock (CaptureAll s a :> rest :: Type) context Source # | |
Defined in Servant.Mock mock :: Proxy (CaptureAll s a :> rest) -> Proxy context -> Server (CaptureAll s a :> rest) Source # | |
HasMock rest context => HasMock (Vault :> rest :: Type) context Source # | |
(KnownSymbol path, HasMock rest context) => HasMock (path :> rest :: Type) context Source # | |
(GetHeaders (Headers headerTypes a), Arbitrary (HList headerTypes), Arbitrary a, KnownNat status, ReflectMethod method, AllCTRender ctypes a) => HasMock (Verb method status ctypes (Headers headerTypes a) :: Type) context Source # | |
(Arbitrary a, KnownNat status, ReflectMethod method, AllCTRender ctypes a) => HasMock (Verb method status ctypes a :: Type) context Source # | |
(Arbitrary a, KnownNat status, ReflectMethod method, MimeRender ctype chunk, FramingRender fr, ToSourceIO chunk a) => HasMock (Stream method status fr ctype a :: Type) context Source # | |