swagger-0.3.0: Implementation of swagger data model

Safe HaskellNone
LanguageHaskell2010

Data.Swagger.Build.Api

Contents

Description

Construction of Data.Swagger.Model.Api values. For example:

declare "http://petstore.swagger.wordnik.com/api" "1.2" $ do
   apiVersion "1.0.0"
   resourcePath "/store"
   model foo
   model bar
   produces "application/json"
   produces "text/html"
   produces "text/plain"
   api "/store/order/{orderId}" $ do
       operation "GET" "foo" $ do
           summary "give me some foo"
           notes   "but only the good one"
           returns (ref foo)
           parameter Header "type" (string $ enum ["bar", "baz"]) $ do
               description "specifies the type of foo"
               optional
           parameter Query "format" (string $ enum ["plain", "html"]) $
               description "output format"
           parameter Query "size" (int32 $ min 1 . max 100 . def 10) $
               description "amount of foo"
           produces "application/json"
           produces "text/html"
           response 200 "OK" (model foo)
           response 400 "Bad Request" end
       operation "POST" "foo" $ do
           summary "something else"
           deprecated

Synopsis

data types

Re-exports

data Primitive a Source #

Instances

data Items a Source #

Instances

Show a => Show (Items a) Source # 

Methods

showsPrec :: Int -> Items a -> ShowS #

show :: Items a -> String #

showList :: [Items a] -> ShowS #

primitive construction

primitive modifiers

def :: a -> Primitive a -> Primitive a Source #

Default value of some primitive type.

enum :: [a] -> Primitive a -> Primitive a Source #

Enumerate valid values of some primitive type.

min :: a -> Primitive a -> Primitive a Source #

Minimum value of some primitive type.

max :: a -> Primitive a -> Primitive a Source #

Maximum value of some primitive type.

data-type constructors

unique :: DataType -> DataType Source #

Specify that array elements are unique.

builder types

type ApiDeclSt = Common '["produces", "consumes", "models", "authorisations"] ApiDecl Source #

type ApiSt = Common '["description"] API Source #

type OperationSt = Common '["produces", "consumes", "authorisations"] Operation Source #

type ParameterSt = Common '["description", "required"] Parameter Source #

type ResponseSt = Common '["models"] Response Source #

type ModelSt = Common '["description"] Model Source #

type PropertySt = Common '["description", "required"] Property Source #

API declaration

declare :: Text -> Text -> ApiDeclBuilder -> ApiDecl Source #

Create an API declaration given a base URL, a swagger version, and other API declaration values.

api :: Text -> ApiBuilder -> ApiDeclBuilder Source #

Add one API object to an API declaration given some path and other API object values.

model :: Elem "models" f => Model -> State (Common f a) () Source #

operation

operation :: Text -> Text -> OperationBuilder -> ApiBuilder Source #

Add one operation object to an API object given an HTTP method, a nickname and other operation specific values.

parameter :: ParamType -> Text -> DataType -> ParameterBuilder -> OperationBuilder Source #

Add one parameter object to an operation object given the ParamType, the parameter name and the actual data-type plus some other parameter values.

file :: Text -> ParameterBuilder -> OperationBuilder Source #

Like parameter but specific for file uploads.

body :: DataType -> ParameterBuilder -> OperationBuilder Source #

Like parameter but specific for request body parameters. Sets ParamType to Body and uses as name "body" which is the only valid name for request bodies.

response :: Int -> Text -> ResponseBuilder -> OperationBuilder Source #

Add one response message object to an operation given a status code and some message plus response message specific values.

produces :: Elem "produces" f => Text -> State (Common f a) () Source #

authorisation :: Elem "authorisations" f => Auth -> State (Common f a) () Source #

data Auth Source #

Constructors

Basic 
ApiKey 
OAuth2 Scope 
None 

parameter

model

defineModel :: ModelId -> ModelBuilder -> Model Source #

Construct a complex data-type (aka "Model") given some identifier and model-specific values.

property :: PropertyName -> DataType -> PropertyBuilder -> ModelBuilder Source #

Add a property to a model given a name, type and other propertu values.

children :: PropertyName -> [Model] -> ModelBuilder Source #

Specify a sub-typing relationship for a model by given a "discriminator" property name and all sub-types.

various

description :: Elem "description" f => Text -> State (Common f a) () Source #

optional :: Elem "required" f => State (Common f a) () Source #

consumes :: Elem "consumes" f => Text -> State (Common f a) () Source #

end :: Monad m => m () Source #

If cases where no build steps are provided but a builder is required end can be used, e.g. defineModel "Foo" end