Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- data ApiDecl
- data API
- data Operation
- data Parameter
- data ParamType
- data Response
- data Model
- data Property
- data DataType
- data Primitive a
- data Items a
- int32 :: (Primitive Int32 -> Primitive Int32) -> DataType
- int32' :: DataType
- int64 :: (Primitive Int64 -> Primitive Int64) -> DataType
- int64' :: DataType
- float :: (Primitive Float -> Primitive Float) -> DataType
- float' :: DataType
- bool :: (Primitive Bool -> Primitive Bool) -> DataType
- bool' :: DataType
- double :: (Primitive Double -> Primitive Double) -> DataType
- double' :: DataType
- string :: (Primitive String -> Primitive String) -> DataType
- string' :: DataType
- bytes :: (Primitive String -> Primitive String) -> DataType
- bytes' :: DataType
- date :: (Primitive UTCTime -> Primitive UTCTime) -> DataType
- date' :: DataType
- dateTime :: (Primitive UTCTime -> Primitive UTCTime) -> DataType
- dateTime' :: DataType
- def :: a -> Primitive a -> Primitive a
- enum :: [a] -> Primitive a -> Primitive a
- min :: a -> Primitive a -> Primitive a
- max :: a -> Primitive a -> Primitive a
- ref :: Model -> DataType
- array :: DataType -> DataType
- unique :: DataType -> DataType
- type ApiDeclSt = Common `["produces", "consumes", "models", "authorisations"]` ApiDecl
- type ApiDeclBuilder = State ApiDeclSt ()
- type ApiSt = Common `["description"]` API
- type ApiBuilder = State ApiSt ()
- type OperationSt = Common `["produces", "consumes", "authorisations"]` Operation
- type OperationBuilder = State OperationSt ()
- type ParameterSt = Common `["description", "required"]` Parameter
- type ParameterBuilder = State ParameterSt ()
- type ResponseSt = Common `["models"]` Response
- type ResponseBuilder = State ResponseSt ()
- type ModelSt = Common `["description"]` Model
- type ModelBuilder = State ModelSt ()
- type PropertySt = Common `["description", "required"]` Property
- type PropertyBuilder = State PropertySt ()
- declare :: Text -> Text -> ApiDeclBuilder -> ApiDecl
- apiVersion :: Text -> ApiDeclBuilder
- resourcePath :: Text -> ApiDeclBuilder
- api :: Text -> ApiBuilder -> ApiDeclBuilder
- model :: Elem "models" f => Model -> State (Common f a) ()
- operation :: Text -> Text -> OperationBuilder -> ApiBuilder
- returns :: DataType -> OperationBuilder
- parameter :: ParamType -> Text -> DataType -> ParameterBuilder -> OperationBuilder
- file :: Text -> ParameterBuilder -> OperationBuilder
- body :: DataType -> ParameterBuilder -> OperationBuilder
- summary :: Text -> OperationBuilder
- notes :: Text -> OperationBuilder
- response :: Int -> Text -> ResponseBuilder -> OperationBuilder
- produces :: Elem "produces" f => Text -> State (Common f a) ()
- authorisation :: Elem "authorisations" f => Auth -> State (Common f a) ()
- data Auth
- multiple :: ParameterBuilder
- defineModel :: ModelId -> ModelBuilder -> Model
- property :: PropertyName -> DataType -> PropertyBuilder -> ModelBuilder
- children :: PropertyName -> [Model] -> ModelBuilder
- description :: Elem "description" f => Text -> State (Common f a) ()
- optional :: Elem "required" f => State (Common f a) ()
- consumes :: Elem "consumes" f => Text -> State (Common f a) ()
- deprecated :: OperationBuilder
- end :: Monad m => m ()
data types
Re-exports
primitive construction
primitive modifiers
data-type constructors
builder types
type ApiDeclBuilder = State ApiDeclSt () Source
type ApiBuilder = State ApiSt () Source
type OperationSt = Common `["produces", "consumes", "authorisations"]` Operation Source
type OperationBuilder = State OperationSt () Source
type ParameterSt = Common `["description", "required"]` Parameter Source
type ParameterBuilder = State ParameterSt () Source
type ResponseSt = Common `["models"]` Response Source
type ResponseBuilder = State ResponseSt () Source
type ModelBuilder = State ModelSt () Source
type PropertySt = Common `["description", "required"]` Property Source
type PropertyBuilder = State PropertySt () 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.
apiVersion :: Text -> ApiDeclBuilder Source
resourcePath :: Text -> ApiDeclBuilder Source
api :: Text -> ApiBuilder -> ApiDeclBuilder Source
Add one API object to an API declaration given some path and other API object values.
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
summary :: Text -> OperationBuilder Source
notes :: Text -> OperationBuilder Source
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.
authorisation :: Elem "authorisations" f => Auth -> State (Common f a) () Source
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