Safe Haskell | None |
---|---|
Language | Haskell2010 |
Servant.Swagger
Contents
- class HasSwagger h where
- toSwaggerDocs :: Proxy h -> SwaggerRoute -> SwagResult
- class ToSwaggerDescription a where
- toSwaggerDescription :: Proxy a -> Text
- class ToHeader a where
- toHeader :: Proxy a -> SwaggerHeader
- class ToSwaggerParamType a where
- toSwaggerParamType :: Proxy a -> SwaggerParamType
- data SwaggerParamType
- class ToSwaggerModel a where
- toSwagModel :: Proxy a -> SwaggerModel
- toSwagModelName :: Proxy a -> ModelName
- class ToHeaderDescription a where
- toHeaderDescription :: Proxy a -> Text
- class ToModelExample model where
- newtype APIDescription = APIDescription {
- _unApiDesc :: Text
- data Contact = Contact {}
- newtype ContactName = ContactName Text
- newtype ContactURL = ContactURL Text
- newtype ContactEmail = ContactEmail Text
- newtype TermsOfService = TermsOfService Text
- data SwaggerAPI = SwaggerAPI {
- _swaggerInfo :: Info
- _swaggerPaths :: HashMap PathName SwaggerOperation
- _swaggerSchemes :: Maybe [Scheme]
- _swaggerDefinitions :: HashMap ModelName SwaggerModel
- _swaggerTags :: Maybe [Tag]
- _swaggerBasePath :: Maybe BasePath
- _swaggerHostName :: Maybe HostName
- _swaggerSecurityDefintions :: Maybe [SecurityDefinition]
- _swaggerExternalDocs :: Maybe ExternalDocs
- data SwaggerOperation = SwaggerOperation {}
- newtype SwaggerRouteInfo a = SwaggerRouteInfo SwagResult
- data Operation = Operation {
- _summary :: PathSummary
- _params :: [Param]
- _responses :: HashMap Code Response
- _produces :: [ContentType]
- _consumes :: [ContentType]
- _tags :: [Tag]
- _operationId :: Maybe OperationId
- _description :: PathDescription
- _deprecated :: Maybe Deprecated
- newtype Code = Code Int
- data Verb
- newtype PathSummary = PathSummary Text
- data SwaggerType
- data SwaggerModel = SwaggerModel {}
- data Info = Info {}
- newtype ModelName = ModelName {
- unModelName :: Text
- data ContentType
- = JSON
- | HTML
- | XML
- | FormUrlEncoded
- | PlainText
- | OctetStream
- newtype APIVersion = APIVersion Text
- newtype APITitle = APITitle Text
- data APILicense = APILicense {
- _licenseName :: Text
- _licenseUrl :: Maybe Text
- data Scheme
- newtype Description = Description {}
- newtype BasePath = BasePath Text
- data Response = Response {}
- data ModelSwag = ModelSwag {}
- data SwaggerHeader = SwaggerHeader {}
- responseDescription :: Lens' Response Text
- responseModelName :: Lens' Response ModelName
- responseHeaders :: Lens' Response (HashMap Text SwaggerHeader)
- responseIsArray :: Lens' Response Bool
- responseCode :: Lens' Response Code
- defResponse :: Response
- data Tag = Tag {}
- newtype TagName = TagName Text
- newtype TagDescription = TagDescription Text
- tagName :: Lens' Tag TagName
- tagDescription :: Lens' Tag TagDescription
- swagger :: HasSwagger swagger => Proxy swagger -> SwaggerRouteInfo swagger -> BasePath -> Info -> [Scheme] -> Maybe HostName -> [SecurityDefinition] -> SwaggerAPI
- emptyModel :: SwaggerModel
- swaggerPathInfo :: (IsElem endpoint layout, HasLink endpoint, HasSwagger endpoint, HasSwagger layout) => Proxy endpoint -> Proxy layout -> SwaggerRouteDescription -> SwaggerRouteInfo layout
- emptyRouteDescription :: SwaggerRouteDescription
- swagModelName :: Lens' SwaggerModel ModelName
- swagModelExample :: Lens' SwaggerModel (Maybe Value)
- swagProperties :: Lens' SwaggerModel [(Text, SwaggerType)]
- swagModelRequired :: Lens' SwaggerModel [Text]
- swagDescription :: Lens' SwaggerModel (Maybe Description)
- swagRouteTags :: Lens' SwaggerRouteDescription [Tag]
- swagRouteSummary :: Lens' SwaggerRouteDescription PathSummary
- swagRouteResponses :: Lens' SwaggerRouteDescription (HashMap Code Response)
- swagRouteModels :: Lens' SwaggerRouteDescription (HashMap ModelName SwaggerModel)
- newtype PathDescription = PathDescription Text
- swagRouteDescription :: Lens' SwaggerRouteDescription PathDescription
- newtype OperationId = OperationId Text
- swagRouteOperationId :: Lens' SwaggerRouteDescription (Maybe OperationId)
- defSwaggerInfo :: Info
- createSwaggerJson :: SwaggerAPI -> IO ()
- swaggerInfoTitle :: Lens' Info APITitle
- swaggerVersion :: Lens' Info APIVersion
- swaggerAPIDescription :: Lens' Info APIDescription
- license :: Lens' Info (Maybe APILicense)
- contact :: Lens' Info (Maybe Contact)
- termsOfService :: Lens' Info (Maybe TermsOfService)
Classes
class HasSwagger h where Source
Swaggin'
Methods
toSwaggerDocs :: Proxy h -> SwaggerRoute -> SwagResult Source
Instances
HasSwagger * Raw Source | Raw holds no verb / body information |
(HasSwagger * left, HasSwagger * right) => HasSwagger * ((:<|>) left right) Source | |
(ToSwaggerModel returnType, ToVerb ([*] -> * -> k) verb, SwaggerAcceptTypes xs, ToResponseHeaders [*] ls) => HasSwagger k (verb xs (Headers ls returnType)) Source | |
(ToSwaggerModel returnType, ToVerb ([*] -> * -> k) verb, SwaggerAcceptTypes xs, ToResponseHeaders [*] ls) => HasSwagger k (verb xs (Headers ls [returnType])) Source | |
(ToSwaggerModel returnType, ToVerb ([*] -> * -> k) verb, SwaggerAcceptTypes xs) => HasSwagger k (verb xs [returnType]) Source | |
(ToSwaggerModel returnType, ToVerb ([*] -> * -> k) verb, SwaggerAcceptTypes xs) => HasSwagger k (verb xs returnType) Source | |
HasSwagger k rest => HasSwagger * ((:>) (k -> *) k (MatrixParam k typ) rest) Source | Swagger doesn't support Raw, bypass |
(SwaggerAcceptTypes ctypes, ToSwaggerModel model, HasSwagger k rest) => HasSwagger * ((:>) * k (ReqBody * ctypes [model]) rest) Source | ReqBody Array |
(SwaggerAcceptTypes ctypes, ToSwaggerModel model, HasSwagger k rest) => HasSwagger * ((:>) * k (ReqBody * ctypes model) rest) Source | ReqBody Object |
(KnownSymbol sym, ToSwaggerDescription * typ, ToSwaggerParamType * typ, HasSwagger k rest) => HasSwagger * ((:>) * k (Header sym typ) rest) Source | Swagger Header |
(ToSwaggerDescription Symbol typ, ToSwaggerParamType Symbol typ, HasSwagger k rest) => HasSwagger * ((:>) * k (MatrixFlag typ) rest) Source | Swagger doesn't support matrix flags, bypass |
(ToSwaggerDescription Symbol sym, KnownSymbol sym, HasSwagger k rest) => HasSwagger * ((:>) * k (QueryFlag sym) rest) Source | Query Flag |
(ToSwaggerDescription k1 typ, ToSwaggerParamType k1 typ, KnownSymbol sym, HasSwagger k rest) => HasSwagger * ((:>) * k (QueryParams k sym typ) rest) Source | |
(ToSwaggerDescription k1 typ, ToSwaggerParamType k1 typ, KnownSymbol sym, HasSwagger k rest) => HasSwagger * ((:>) * k (QueryParam k sym typ) rest) Source | |
(ToSwaggerDescription k1 typ, ToSwaggerParamType k1 typ, KnownSymbol sym, HasSwagger k rest) => HasSwagger * ((:>) * k (Capture k sym typ) rest) Source | |
(HasSwagger k rest, KnownSymbol sym) => HasSwagger * ((:>) Symbol k sym rest) Source |
class ToSwaggerDescription a where Source
Methods
toSwaggerDescription :: Proxy a -> Text Source
Methods
toHeader :: Proxy a -> SwaggerHeader Source
Instances
(ToSwaggerParamType * headerType, KnownSymbol headerName, ToHeaderDescription Symbol headerName) => ToHeader * (Header headerName headerType) Source |
class ToSwaggerParamType a where Source
Methods
Instances
data SwaggerParamType Source
class ToHeaderDescription a where Source
Methods
toHeaderDescription :: Proxy a -> Text Source
Types
Contact Object
Constructors
Contact | |
Fields |
data SwaggerAPI Source
This is the root document object for the API specification.
Constructors
SwaggerAPI | |
Fields
|
data SwaggerOperation Source
Constructors
SwaggerOperation | |
newtype SwaggerRouteInfo a Source
Constructors
SwaggerRouteInfo SwagResult |
Instances
Monoid (SwaggerRouteInfo k a) Source |
Constructors
Operation | |
Fields
|
newtype PathSummary Source
Constructors
PathSummary Text |
data SwaggerType Source
Constructors
IntegerSwag | |
LongSwag | |
FloatSwag | |
DoubleSwag | |
StringSwag | |
ByteSwag | |
BinarySwag | |
BooleanSwag | |
DateSwag | |
DateTimeSwag | |
PasswordSwag | |
Model ModelSwag |
Instances
data SwaggerModel Source
Constructors
SwaggerModel | |
Fields
|
Instances
Info Objet
Constructors
Info | |
Fields
|
Constructors
ModelName | |
Fields
|
newtype APIVersion Source
Constructors
APIVersion Text |
data APILicense Source
Constructors
APILicense | |
Fields
|
newtype Description Source
Constructors
Description | |
Fields |
BasePath
A container for the expected responses of an operation.
Constructors
Response | |
Fields
|
Constructors
ModelSwag | |
Fields |
data SwaggerHeader Source
A Swagger metadata for a Servant header
Constructors
SwaggerHeader | |
Fields
|
defResponse :: Response Source
Default Response for a Path
Allows adding meta data to a single tag that is used by the Operation Object
Constructors
Tag | |
Fields
|
Name of Tag
, that can be applied to an operation
Swaggadelic
swagger :: HasSwagger swagger => Proxy swagger -> SwaggerRouteInfo swagger -> BasePath -> Info -> [Scheme] -> Maybe HostName -> [SecurityDefinition] -> SwaggerAPI Source
swaggerPathInfo :: (IsElem endpoint layout, HasLink endpoint, HasSwagger endpoint, HasSwagger layout) => Proxy endpoint -> Proxy layout -> SwaggerRouteDescription -> SwaggerRouteInfo layout Source
emptyRouteDescription :: SwaggerRouteDescription Source
Lenses
swagProperties :: Lens' SwaggerModel [(Text, SwaggerType)] Source
swagRouteTags :: Lens' SwaggerRouteDescription [Tag] Source
swagRouteSummary :: Lens' SwaggerRouteDescription PathSummary Source
swagRouteModels :: Lens' SwaggerRouteDescription (HashMap ModelName SwaggerModel) Source
newtype PathDescription Source
Constructors
PathDescription Text |
swagRouteDescription :: Lens' SwaggerRouteDescription PathDescription Source
newtype OperationId Source
Constructors
OperationId Text |
swagRouteOperationId :: Lens' SwaggerRouteDescription (Maybe OperationId) Source
Default contact
createSwaggerJson :: SwaggerAPI -> IO () Source
Helper to generate swagger.json file