yam-0.4.0: Yam Web

Safe HaskellNone
LanguageHaskell2010

Yam.Web.Swagger

Synopsis

Documentation

class HasSwagger (api :: k) #

Generate a Swagger specification for a servant API.

To generate Swagger specification, your data types need ToParamSchema and/or ToSchema instances.

ToParamSchema is used for Capture, QueryParam and Header. ToSchema is used for ReqBody and response data types.

You can easily derive those instances via Generic. For more information, refer to swagger2 documentation.

Example:

newtype Username = Username String deriving (Generic, ToText)

instance ToParamSchema Username

data User = User
  { username :: Username
  , fullname :: String
  } deriving (Generic)

instance ToJSON User
instance ToSchema User

type MyAPI = QueryParam "username" Username :> Get '[JSON] User

mySwagger :: Swagger
mySwagger = toSwagger (Proxy :: Proxy MyAPI)

Minimal complete definition

toSwagger

Instances
HasSwagger Raw 
Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy Raw -> Swagger #

HasSwagger EmptyAPI 
Instance details

Defined in Servant.Swagger.Internal

(HasSwagger a, HasSwagger b) => HasSwagger (a :<|> b :: Type) 
Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (a :<|> b) -> Swagger #

HasSwagger sub => HasSwagger (WithNamedContext x c sub :: Type)

WithNamedContext combinator does not change our specification at all.

Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (WithNamedContext x c sub) -> Swagger #

HasSwagger sub => HasSwagger (HttpVersion :> sub :: Type)

HttpVersion combinator does not change our specification at all.

Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (HttpVersion :> sub) -> Swagger #

(ToSchema a, Accept ct, HasSwagger sub, KnownSymbol (FoldDescription mods)) => HasSwagger (StreamBody' mods fr ct a :> sub :: Type)

This instance is an approximation.

Since: servant-swagger-1.1.7

Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (StreamBody' mods fr ct a :> sub) -> Swagger #

(ToSchema a, AllAccept cs, HasSwagger sub, KnownSymbol (FoldDescription mods)) => HasSwagger (ReqBody' mods cs a :> sub :: Type) 
Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (ReqBody' mods cs a :> sub) -> Swagger #

HasSwagger sub => HasSwagger (RemoteHost :> sub :: Type)

RemoteHost combinator does not change our specification at all.

Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (RemoteHost :> sub) -> Swagger #

(KnownSymbol sym, ToParamSchema a, HasSwagger sub, SBoolI (FoldRequired mods), KnownSymbol (FoldDescription mods)) => HasSwagger (QueryParam' mods sym a :> sub :: Type) 
Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (QueryParam' mods sym a :> sub) -> Swagger #

(KnownSymbol sym, ToParamSchema a, HasSwagger sub) => HasSwagger (QueryParams sym a :> sub :: Type) 
Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (QueryParams sym a :> sub) -> Swagger #

(KnownSymbol sym, HasSwagger sub) => HasSwagger (QueryFlag sym :> sub :: Type) 
Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (QueryFlag sym :> sub) -> Swagger #

(KnownSymbol sym, ToParamSchema a, HasSwagger sub, SBoolI (FoldRequired mods), KnownSymbol (FoldDescription mods)) => HasSwagger (Header' mods sym a :> sub :: Type) 
Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (Header' mods sym a :> sub) -> Swagger #

HasSwagger sub => HasSwagger (IsSecure :> sub :: Type)

IsSecure combinator does not change our specification at all.

Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (IsSecure :> sub) -> Swagger #

(KnownSymbol desc, HasSwagger api) => HasSwagger (Summary desc :> api :: Type) 
Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (Summary desc :> api) -> Swagger #

(KnownSymbol desc, HasSwagger api) => HasSwagger (Description desc :> api :: Type) 
Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (Description desc :> api) -> Swagger #

(KnownSymbol sym, ToParamSchema a, HasSwagger sub, KnownSymbol (FoldDescription mods)) => HasSwagger (Capture' mods sym a :> sub :: Type) 
Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (Capture' mods sym a :> sub) -> Swagger #

(KnownSymbol sym, ToParamSchema a, HasSwagger sub) => HasSwagger (CaptureAll sym a :> sub :: Type)

Swagger Spec doesn't have a notion of CaptureAll, this instance is the best effort.

Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (CaptureAll sym a :> sub) -> Swagger #

HasSwagger sub => HasSwagger (Vault :> sub :: Type)

Vault combinator does not change our specification at all.

Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (Vault :> sub) -> Swagger #

(KnownSymbol sym, HasSwagger sub) => HasSwagger (sym :> sub :: Type) 
Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (sym :> sub) -> Swagger #

(ToSchema a, AllAccept cs, AllToResponseHeader hs, KnownNat status, SwaggerMethod method) => HasSwagger (Verb method status cs (Headers hs a) :: Type) 
Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (Verb method status cs (Headers hs a)) -> Swagger #

(AllAccept cs, AllToResponseHeader hs, KnownNat status, SwaggerMethod method) => HasSwagger (Verb method status cs (Headers hs NoContent) :: Type) 
Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (Verb method status cs (Headers hs NoContent)) -> Swagger #

(ToSchema a, AllAccept cs, KnownNat status, SwaggerMethod method) => HasSwagger (Verb method status cs a :: Type) 
Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (Verb method status cs a) -> Swagger #

(AllAccept cs, KnownNat status, SwaggerMethod method) => HasSwagger (Verb method status cs NoContent :: Type) 
Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (Verb method status cs NoContent) -> Swagger #

(ToSchema a, Accept ct, KnownNat status, SwaggerMethod method) => HasSwagger (Stream method status fr ct a :: Type)

Since: servant-swagger-1.1.7

Instance details

Defined in Servant.Swagger.Internal

Methods

toSwagger :: Proxy (Stream method status fr ct a) -> Swagger #

module Servant