-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Generate a Swagger/OpenAPI/OAS 2.0 specification for your servant API. -- -- Swagger is a project used to describe and document RESTful APIs. The -- core of the project is the OpenAPI Specification (OAS). This -- library implements v2.0 of the spec. Unlike Servant it is -- language-agnostic and thus is quite popular among developers in -- different languages. It has also existed for a longer time and has -- more helpful tooling. -- -- This package provides means to generate a Swagger/OAS specification -- for a Servant API and also to partially test whether an API conforms -- with its specification. -- -- Generated Swagger specification then can be used for many things such -- as -- -- @package servant-swagger @version 1.2.1 module Servant.Swagger.Internal.Orphans instance Data.Swagger.Internal.Schema.ToSchema a => Data.Swagger.Internal.Schema.ToSchema (Servant.API.UVerb.WithStatus s a) instance Data.Swagger.Internal.Schema.ToSchema a => Data.Swagger.Internal.Schema.ToSchema (Servant.Types.SourceT.SourceT m a) module Servant.Swagger.Internal.TypeLevel.API -- | Build a list of endpoints from an API. type family EndpointsList api -- | Check whether sub is a sub API of api. type family IsSubAPI sub api :: Constraint -- | Check that every element of xs is an endpoint of -- api. type family AllIsElem xs api :: Constraint -- | Apply (e :>) to every API in xs. type family MapSub e xs -- | Append two type-level lists. type family AppendList xs ys type family Or (a :: Constraint) (b :: Constraint) :: Constraint type family IsIn sub api :: Constraint -- | Check whether a type is a member of a list of types. This is a -- type-level analogue of elem. type family Elem x xs -- | Remove duplicates from a type-level list. type family Nub xs -- | Remove element from a type-level list. type family Remove x xs -- | Extract a list of unique "body" types for a specific content-type from -- a servant API. type BodyTypes c api = Nub (BodyTypes' c api) -- | AddBodyType c cs a as adds type a to the list -- as only if c is in cs. type AddBodyType c cs a as = If (Elem c cs) (a ': as) as -- | Extract a list of "body" types for a specific content-type from a -- servant API. To extract unique types see BodyTypes. -- -- NoContent is removed from the list and not tested. -- (This allows for leaving the body completely empty on responses to -- requests that only accept 'application/json', while setting the -- content-type in the response accordingly.) type family BodyTypes' c api :: [Type] module Servant.Swagger.Internal -- | 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 ResponseHeader. -- 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)
--   
class HasSwagger api -- | Generate a Swagger specification for a servant API. toSwagger :: HasSwagger api => Proxy api -> Swagger -- | All operations of sub API. This is similar to -- operationsOf but ensures that operations indeed belong -- to the API at compile time. subOperations :: (IsSubAPI sub api, HasSwagger sub) => Proxy sub -> Proxy api -> Traversal' Swagger Operation -- | Make a singleton Swagger spec (with only one endpoint). For endpoints -- with no content see mkEndpointNoContent. mkEndpoint :: forall a cs hs proxy method status. (ToSchema a, AllAccept cs, AllToResponseHeader hs, SwaggerMethod method, KnownNat status) => FilePath -> proxy (Verb method status cs (Headers hs a)) -> Swagger -- | Make a singletone Swagger spec (with only one endpoint) and -- with no content schema. mkEndpointNoContent :: forall nocontent cs hs proxy method status. (AllAccept cs, AllToResponseHeader hs, SwaggerMethod method, KnownNat status) => FilePath -> proxy (Verb method status cs (Headers hs nocontent)) -> Swagger -- | Like mkEndpoint but with explicit schema reference. -- Unlike mkEndpoint this function does not update -- definitions. mkEndpointWithSchemaRef :: forall cs hs proxy method status a. (AllAccept cs, AllToResponseHeader hs, SwaggerMethod method, KnownNat status) => Maybe (Referenced Schema) -> FilePath -> proxy (Verb method status cs (Headers hs a)) -> Swagger mkEndpointNoContentVerb :: forall proxy method. SwaggerMethod method => FilePath -> proxy (NoContentVerb method) -> Swagger -- | Add parameter to every operation in the spec. addParam :: Param -> Swagger -> Swagger -- | Add a tag to every operation in the spec. addTag :: Text -> Swagger -> Swagger -- | Add accepted content types to every operation in the spec. addConsumes :: [MediaType] -> Swagger -> Swagger -- | Format given text as inline code in Markdown. markdownCode :: Text -> Text addDefaultResponse400 :: ParamName -> Swagger -> Swagger -- | Methods, available for Swagger. class SwaggerMethod method swaggerMethod :: SwaggerMethod method => proxy method -> Lens' PathItem (Maybe Operation) combinePathItem :: PathItem -> PathItem -> PathItem combineSwagger :: Swagger -> Swagger -> Swagger class AllAccept cs allContentType :: AllAccept cs => Proxy cs -> [MediaType] class ToResponseHeader h toResponseHeader :: ToResponseHeader h => Proxy h -> (HeaderName, Header) class AllToResponseHeader hs toAllResponseHeaders :: AllToResponseHeader hs => Proxy hs -> InsOrdHashMap HeaderName Header instance forall k1 a (cs :: [*]) (hs :: [*]) (status :: GHC.TypeNats.Nat) (method :: k1). (Data.Swagger.Internal.Schema.ToSchema a, Servant.Swagger.Internal.AllAccept cs, Servant.Swagger.Internal.AllToResponseHeader hs, GHC.TypeNats.KnownNat status, Servant.Swagger.Internal.SwaggerMethod method) => Servant.Swagger.Internal.HasSwagger (Servant.API.Verbs.Verb method status cs (Servant.API.ResponseHeaders.Headers hs a)) instance forall k1 (cs :: [*]) (hs :: [*]) (status :: GHC.TypeNats.Nat) (method :: k1). (Servant.Swagger.Internal.AllAccept cs, Servant.Swagger.Internal.AllToResponseHeader hs, GHC.TypeNats.KnownNat status, Servant.Swagger.Internal.SwaggerMethod method) => Servant.Swagger.Internal.HasSwagger (Servant.API.Verbs.Verb method status cs (Servant.API.ResponseHeaders.Headers hs Servant.API.ContentTypes.NoContent)) instance Servant.Swagger.Internal.AllToResponseHeader '[] instance forall a (h :: a) (hs :: [a]). (Servant.Swagger.Internal.ToResponseHeader h, Servant.Swagger.Internal.AllToResponseHeader hs) => Servant.Swagger.Internal.AllToResponseHeader (h : hs) instance Servant.Swagger.Internal.AllToResponseHeader hs => Servant.Swagger.Internal.AllToResponseHeader (Servant.API.ResponseHeaders.HList hs) instance (GHC.TypeLits.KnownSymbol sym, Data.Swagger.Internal.ParamSchema.ToParamSchema a, GHC.TypeLits.KnownSymbol (Servant.API.Description.FoldDescription mods)) => Servant.Swagger.Internal.ToResponseHeader (Servant.API.Header.Header' mods sym a) instance (Data.Swagger.Internal.Schema.ToSchema a, Servant.API.UVerb.HasStatus a, Servant.Swagger.Internal.AllAccept cs, Servant.Swagger.Internal.SwaggerMethod method, Servant.Swagger.Internal.HasSwagger (Servant.API.UVerb.UVerb method cs as)) => Servant.Swagger.Internal.HasSwagger (Servant.API.UVerb.UVerb method cs (a : as)) instance (GHC.TypeNats.KnownNat status, Servant.Swagger.Internal.AllAccept cs, Servant.Swagger.Internal.SwaggerMethod method, Servant.Swagger.Internal.HasSwagger (Servant.API.UVerb.UVerb method cs as)) => Servant.Swagger.Internal.HasSwagger (Servant.API.UVerb.UVerb method cs (Servant.API.UVerb.WithStatus status Servant.API.ContentTypes.NoContent : as)) instance forall k1 a (cs :: [*]) (status :: GHC.TypeNats.Nat) (method :: k1). (Data.Swagger.Internal.Schema.ToSchema a, Servant.Swagger.Internal.AllAccept cs, GHC.TypeNats.KnownNat status, Servant.Swagger.Internal.SwaggerMethod method) => Servant.Swagger.Internal.HasSwagger (Servant.API.Verbs.Verb method status cs a) instance forall k1 (cs :: [*]) (status :: GHC.TypeNats.Nat) (method :: k1). (Servant.Swagger.Internal.AllAccept cs, GHC.TypeNats.KnownNat status, Servant.Swagger.Internal.SwaggerMethod method) => Servant.Swagger.Internal.HasSwagger (Servant.API.Verbs.Verb method status cs Servant.API.ContentTypes.NoContent) instance (Data.Swagger.Internal.Schema.ToSchema a, Servant.Swagger.Internal.AllAccept cs, Servant.Swagger.Internal.HasSwagger sub, GHC.TypeLits.KnownSymbol (Servant.API.Description.FoldDescription mods)) => Servant.Swagger.Internal.HasSwagger (Servant.API.ReqBody.ReqBody' mods cs a Servant.API.Sub.:> sub) instance Servant.Swagger.Internal.AllAccept '[] instance forall a (c :: a) (cs :: [a]). (Servant.API.ContentTypes.Accept c, Servant.Swagger.Internal.AllAccept cs) => Servant.Swagger.Internal.AllAccept (c : cs) instance Servant.Swagger.Internal.SwaggerMethod 'Network.HTTP.Types.Method.GET instance Servant.Swagger.Internal.SwaggerMethod 'Network.HTTP.Types.Method.PUT instance Servant.Swagger.Internal.SwaggerMethod 'Network.HTTP.Types.Method.POST instance Servant.Swagger.Internal.SwaggerMethod 'Network.HTTP.Types.Method.DELETE instance Servant.Swagger.Internal.SwaggerMethod 'Network.HTTP.Types.Method.OPTIONS instance Servant.Swagger.Internal.SwaggerMethod 'Network.HTTP.Types.Method.HEAD instance Servant.Swagger.Internal.SwaggerMethod 'Network.HTTP.Types.Method.PATCH instance forall k1 a ct (status :: GHC.TypeNats.Nat) (method :: k1) fr. (Data.Swagger.Internal.Schema.ToSchema a, Servant.API.ContentTypes.Accept ct, GHC.TypeNats.KnownNat status, Servant.Swagger.Internal.SwaggerMethod method) => Servant.Swagger.Internal.HasSwagger (Servant.API.Stream.Stream method status fr ct a) instance forall k1 (method :: k1). Servant.Swagger.Internal.SwaggerMethod method => Servant.Swagger.Internal.HasSwagger (Servant.API.Verbs.NoContentVerb method) instance Servant.Swagger.Internal.HasSwagger Servant.API.Raw.Raw instance Servant.Swagger.Internal.HasSwagger Servant.API.Empty.EmptyAPI instance Servant.Swagger.Internal.HasSwagger (Servant.API.UVerb.UVerb method cs '[]) instance (Servant.Swagger.Internal.HasSwagger a, Servant.Swagger.Internal.HasSwagger b) => Servant.Swagger.Internal.HasSwagger (a Servant.API.Alternative.:<|> b) instance Servant.Swagger.Internal.HasSwagger sub => Servant.Swagger.Internal.HasSwagger (Data.Vault.Lazy.Vault Servant.API.Sub.:> sub) instance Servant.Swagger.Internal.HasSwagger sub => Servant.Swagger.Internal.HasSwagger (Servant.API.IsSecure.IsSecure Servant.API.Sub.:> sub) instance Servant.Swagger.Internal.HasSwagger sub => Servant.Swagger.Internal.HasSwagger (Servant.API.RemoteHost.RemoteHost Servant.API.Sub.:> sub) instance Servant.Swagger.Internal.HasSwagger sub => Servant.Swagger.Internal.HasSwagger (Servant.API.Fragment.Fragment a Servant.API.Sub.:> sub) instance Servant.Swagger.Internal.HasSwagger sub => Servant.Swagger.Internal.HasSwagger (Network.HTTP.Types.Version.HttpVersion Servant.API.Sub.:> sub) instance forall k (sub :: k) (x :: GHC.Types.Symbol) (c :: [*]). Servant.Swagger.Internal.HasSwagger sub => Servant.Swagger.Internal.HasSwagger (Servant.API.WithNamedContext.WithNamedContext x c sub) instance forall k sub (res :: k). Servant.Swagger.Internal.HasSwagger sub => Servant.Swagger.Internal.HasSwagger (Servant.API.WithResource.WithResource res Servant.API.Sub.:> sub) instance (GHC.TypeLits.KnownSymbol sym, Servant.Swagger.Internal.HasSwagger sub) => Servant.Swagger.Internal.HasSwagger (sym Servant.API.Sub.:> sub) instance (GHC.TypeLits.KnownSymbol sym, Data.Typeable.Internal.Typeable a, Data.Swagger.Internal.ParamSchema.ToParamSchema a, Servant.Swagger.Internal.HasSwagger sub, GHC.TypeLits.KnownSymbol (Servant.API.Description.FoldDescription mods)) => Servant.Swagger.Internal.HasSwagger (Servant.API.Capture.Capture' mods sym a Servant.API.Sub.:> sub) instance (GHC.TypeLits.KnownSymbol sym, Data.Typeable.Internal.Typeable a, Data.Swagger.Internal.ParamSchema.ToParamSchema a, Servant.Swagger.Internal.HasSwagger sub) => Servant.Swagger.Internal.HasSwagger (Servant.API.Capture.CaptureAll sym a Servant.API.Sub.:> sub) instance (GHC.TypeLits.KnownSymbol desc, Servant.Swagger.Internal.HasSwagger api) => Servant.Swagger.Internal.HasSwagger (Servant.API.Description.Description desc Servant.API.Sub.:> api) instance (GHC.TypeLits.KnownSymbol desc, Servant.Swagger.Internal.HasSwagger api) => Servant.Swagger.Internal.HasSwagger (Servant.API.Description.Summary desc Servant.API.Sub.:> api) instance (GHC.TypeLits.KnownSymbol sym, Data.Swagger.Internal.ParamSchema.ToParamSchema a, Servant.Swagger.Internal.HasSwagger sub, Data.Singletons.Bool.SBoolI (Servant.API.Modifiers.FoldRequired mods), GHC.TypeLits.KnownSymbol (Servant.API.Description.FoldDescription mods)) => Servant.Swagger.Internal.HasSwagger (Servant.API.QueryParam.QueryParam' mods sym a Servant.API.Sub.:> sub) instance (GHC.TypeLits.KnownSymbol sym, Data.Swagger.Internal.ParamSchema.ToParamSchema a, Servant.Swagger.Internal.HasSwagger sub) => Servant.Swagger.Internal.HasSwagger (Servant.API.QueryParam.QueryParams sym a Servant.API.Sub.:> sub) instance (GHC.TypeLits.KnownSymbol sym, Servant.Swagger.Internal.HasSwagger sub) => Servant.Swagger.Internal.HasSwagger (Servant.API.QueryParam.QueryFlag sym Servant.API.Sub.:> sub) instance (GHC.TypeLits.KnownSymbol sym, Data.Swagger.Internal.ParamSchema.ToParamSchema a, Servant.Swagger.Internal.HasSwagger sub, Data.Singletons.Bool.SBoolI (Servant.API.Modifiers.FoldRequired mods), GHC.TypeLits.KnownSymbol (Servant.API.Description.FoldDescription mods)) => Servant.Swagger.Internal.HasSwagger (Servant.API.Header.Header' mods sym a Servant.API.Sub.:> sub) instance (Data.Swagger.Internal.Schema.ToSchema a, Servant.API.ContentTypes.Accept ct, Servant.Swagger.Internal.HasSwagger sub, GHC.TypeLits.KnownSymbol (Servant.API.Description.FoldDescription mods)) => Servant.Swagger.Internal.HasSwagger (Servant.API.Stream.StreamBody' mods fr ct a Servant.API.Sub.:> sub) instance (Servant.Swagger.Internal.HasSwagger (Servant.API.Generic.ToServantApi routes), GHC.TypeLits.KnownSymbol datatypeName, GHC.Generics.Rep (routes Servant.API.Generic.AsApi) GHC.Types.~ GHC.Generics.D1 ('GHC.Generics.MetaData datatypeName moduleName packageName isNewtype) f) => Servant.Swagger.Internal.HasSwagger (Servant.API.NamedRoutes.NamedRoutes routes) module Servant.Swagger.Internal.TypeLevel.TMap -- | Map a list of constrained types to a list of values. -- --
--   >>> tmap (Proxy :: Proxy KnownSymbol) symbolVal (Proxy :: Proxy ["hello", "world"])
--   ["hello","world"]
--   
class TMap (q :: k -> Constraint) (xs :: [k]) tmap :: TMap q xs => p q -> (forall x p'. q x => p' x -> a) -> p'' xs -> [a] instance forall k (q :: k -> GHC.Types.Constraint). Servant.Swagger.Internal.TypeLevel.TMap.TMap q '[] instance forall a (q :: a -> GHC.Types.Constraint) (x :: a) (xs :: [a]). (q x, Servant.Swagger.Internal.TypeLevel.TMap.TMap q xs) => Servant.Swagger.Internal.TypeLevel.TMap.TMap q (x : xs) module Servant.Swagger.Internal.TypeLevel.Every -- | Apply multiple constraint constructors to a type. -- --
--   EveryTF '[Show, Read] a ~ (Show a, Read a)
--   
-- -- Note that since this is a type family, you have to alway fully apply -- EveryTF. -- -- For partial application of multiple constraint constructors see -- Every. type family EveryTF cs x :: Constraint -- | Apply multiple constraint constructors to a type as a class. -- -- This is different from EveryTF in that it allows -- partial application. class EveryTF cs x => Every (cs :: [Type -> Constraint]) (x :: Type) -- | Like tmap, but uses Every for multiple -- constraints. -- --
--   >>> let zero :: forall p a. (Show a, Num a) => p a -> String; zero _ = show (0 :: a)
--   
--   >>> tmapEvery (Proxy :: Proxy [Show, Num]) zero (Proxy :: Proxy [Int, Float]) :: [String]
--   ["0","0.0"]
--   
tmapEvery :: forall a cs p p'' xs. TMap (Every cs) xs => p cs -> (forall x p'. Every cs x => p' x -> a) -> p'' xs -> [a] instance Servant.Swagger.Internal.TypeLevel.Every.Every '[] x instance (c x, Servant.Swagger.Internal.TypeLevel.Every.Every cs x) => Servant.Swagger.Internal.TypeLevel.Every.Every (c : cs) x module Servant.Swagger.Internal.TypeLevel module Servant.Swagger.Internal.Test -- | Verify that every type used with JSON content type in -- a servant API has compatible ToJSON and -- ToSchema instances using -- validateToJSON. -- -- NOTE: validateEveryToJSON does not perform -- string pattern validation. See -- validateEveryToJSONWithPatternChecker. -- -- validateEveryToJSON will produce one -- prop specification for every type in the API. Each -- type only gets one test, even if it occurs multiple times in the API. -- --
--   >>> data User = User { name :: String, age :: Maybe Int } deriving (Show, Generic, Typeable)
--   
--   >>> newtype UserId = UserId String deriving (Show, Generic, Typeable, ToJSON, Arbitrary)
--   
--   >>> instance ToJSON User
--   
--   >>> instance ToSchema User
--   
--   >>> instance ToSchema UserId
--   
--   >>> instance Arbitrary User where arbitrary = User <$> arbitrary <*> arbitrary
--   
--   >>> type UserAPI = (Capture "user_id" UserId :> Get '[JSON] User) :<|> (ReqBody '[JSON] User :> Post '[JSON] UserId)
--   
-- --
--   >>> hspec $ context "ToJSON matches ToSchema" $ validateEveryToJSON (Proxy :: Proxy UserAPI)
--   
--   ToJSON matches ToSchema...
--     User...
--   ...
--     UserId...
--   ...
--   Finished in ... seconds
--   2 examples, 0 failures
--   
-- -- For the test to compile all body types should have the following -- instances: -- -- -- -- If any of the instances is missing, you'll get a descriptive type -- error: -- --
--   >>> data Contact = Contact { fullname :: String, phone :: Integer } deriving (Show, Generic)
--   
--   >>> instance ToJSON Contact
--   
--   >>> instance ToSchema Contact
--   
--   >>> type ContactAPI = Get '[JSON] Contact
--   
--   >>> hspec $ validateEveryToJSON (Proxy :: Proxy ContactAPI)
--   ...
--   ...No instance for ...Arbitrary Contact...
--   ...  arising from a use of ‘validateEveryToJSON’
--   ...
--   
validateEveryToJSON :: forall proxy api. TMap (Every [Typeable, Show, Arbitrary, ToJSON, ToSchema]) (BodyTypes JSON api) => proxy api -> Spec -- | Verify that every type used with JSON content type in -- a servant API has compatible ToJSON and -- ToSchema instances using -- validateToJSONWithPatternChecker. -- -- For validation without patterns see -- validateEveryToJSON. validateEveryToJSONWithPatternChecker :: forall proxy api. TMap (Every [Typeable, Show, Arbitrary, ToJSON, ToSchema]) (BodyTypes JSON api) => (Pattern -> Text -> Bool) -> proxy api -> Spec -- | Construct property tests for each type in a list. The name for each -- property is the name of the corresponding type. -- --
--   >>> :{
--    hspec $
--      context "read . show == id" $
--        props
--          (Proxy :: Proxy [Eq, Show, Read])
--          (\x -> read (show x) === x)
--          (Proxy :: Proxy [Bool, Int, String])
--   :}
--   
--   read . show == id
--     Bool...
--   ...
--     Int...
--   ...
--     [Char]...
--   ...
--   Finished in ... seconds
--   3 examples, 0 failures
--   
props :: forall p p'' cs xs. TMap (Every (Typeable ': (Show ': (Arbitrary ': cs)))) xs => p cs -> (forall x. EveryTF cs x => x -> Property) -> p'' xs -> Spec -- | Pretty print validation errors together with actual JSON and Swagger -- Schema (using encodePretty). -- --
--   >>> import Data.Aeson
--   
--   >>> import Data.Foldable (traverse_)
--   
--   >>> data Person = Person { name :: String, phone :: Integer } deriving (Generic)
--   
--   >>> instance ToJSON Person where toJSON p = object [ "name" .= name p ]
--   
--   >>> instance ToSchema Person
--   
--   >>> let person = Person { name = "John", phone = 123456 }
--   
--   >>> traverse_ putStrLn $ prettyValidateWith validateToJSON person
--   Validation against the schema fails:
--     * property "phone" is required, but not found in "{\"name\":\"John\"}"
--   
--   JSON value:
--   {
--       "name": "John"
--   }
--   
--   Swagger Schema:
--   {
--       "properties": {
--           "name": {
--               "type": "string"
--           },
--           "phone": {
--               "type": "integer"
--           }
--       },
--       "required": [
--           "name",
--           "phone"
--       ],
--       "type": "object"
--   }
--   
-- -- FIXME: this belongs in Data.Swagger.Schema.Validation (in -- swagger2). prettyValidateWith :: forall a. (ToJSON a, ToSchema a) => (a -> [ValidationError]) -> a -> Maybe String -- | Provide a counterexample if there is any. maybeCounterExample :: Maybe String -> Property -- | Automatic tests for servant API against Swagger spec. module Servant.Swagger.Test -- | Verify that every type used with JSON content type in -- a servant API has compatible ToJSON and -- ToSchema instances using -- validateToJSON. -- -- NOTE: validateEveryToJSON does not perform -- string pattern validation. See -- validateEveryToJSONWithPatternChecker. -- -- validateEveryToJSON will produce one -- prop specification for every type in the API. Each -- type only gets one test, even if it occurs multiple times in the API. -- --
--   >>> data User = User { name :: String, age :: Maybe Int } deriving (Show, Generic, Typeable)
--   
--   >>> newtype UserId = UserId String deriving (Show, Generic, Typeable, ToJSON, Arbitrary)
--   
--   >>> instance ToJSON User
--   
--   >>> instance ToSchema User
--   
--   >>> instance ToSchema UserId
--   
--   >>> instance Arbitrary User where arbitrary = User <$> arbitrary <*> arbitrary
--   
--   >>> type UserAPI = (Capture "user_id" UserId :> Get '[JSON] User) :<|> (ReqBody '[JSON] User :> Post '[JSON] UserId)
--   
-- --
--   >>> hspec $ context "ToJSON matches ToSchema" $ validateEveryToJSON (Proxy :: Proxy UserAPI)
--   
--   ToJSON matches ToSchema...
--     User...
--   ...
--     UserId...
--   ...
--   Finished in ... seconds
--   2 examples, 0 failures
--   
-- -- For the test to compile all body types should have the following -- instances: -- -- -- -- If any of the instances is missing, you'll get a descriptive type -- error: -- --
--   >>> data Contact = Contact { fullname :: String, phone :: Integer } deriving (Show, Generic)
--   
--   >>> instance ToJSON Contact
--   
--   >>> instance ToSchema Contact
--   
--   >>> type ContactAPI = Get '[JSON] Contact
--   
--   >>> hspec $ validateEveryToJSON (Proxy :: Proxy ContactAPI)
--   ...
--   ...No instance for ...Arbitrary Contact...
--   ...  arising from a use of ‘validateEveryToJSON’
--   ...
--   
validateEveryToJSON :: forall proxy api. TMap (Every [Typeable, Show, Arbitrary, ToJSON, ToSchema]) (BodyTypes JSON api) => proxy api -> Spec -- | Verify that every type used with JSON content type in -- a servant API has compatible ToJSON and -- ToSchema instances using -- validateToJSONWithPatternChecker. -- -- For validation without patterns see -- validateEveryToJSON. validateEveryToJSONWithPatternChecker :: forall proxy api. TMap (Every [Typeable, Show, Arbitrary, ToJSON, ToSchema]) (BodyTypes JSON api) => (Pattern -> Text -> Bool) -> proxy api -> Spec -- | This module provides means to generate and manipulate Swagger -- specification for servant APIs. -- -- Swagger is a project used to describe and document RESTful APIs. -- -- The Swagger specification defines a set of files required to describe -- such an API. These files can then be used by the Swagger-UI project to -- display the API and Swagger-Codegen to generate clients in various -- languages. Additional utilities can also take advantage of the -- resulting files, such as testing tools. -- -- For more information see Swagger documentation. module Servant.Swagger -- | 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 ResponseHeader. -- 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)
--   
class HasSwagger api -- | Generate a Swagger specification for a servant API. toSwagger :: HasSwagger api => Proxy api -> Swagger -- | All operations of sub API. This is similar to -- operationsOf but ensures that operations indeed belong -- to the API at compile time. subOperations :: (IsSubAPI sub api, HasSwagger sub) => Proxy sub -> Proxy api -> Traversal' Swagger Operation -- | Verify that every type used with JSON content type in -- a servant API has compatible ToJSON and -- ToSchema instances using -- validateToJSON. -- -- NOTE: validateEveryToJSON does not perform -- string pattern validation. See -- validateEveryToJSONWithPatternChecker. -- -- validateEveryToJSON will produce one -- prop specification for every type in the API. Each -- type only gets one test, even if it occurs multiple times in the API. -- --
--   >>> data User = User { name :: String, age :: Maybe Int } deriving (Show, Generic, Typeable)
--   
--   >>> newtype UserId = UserId String deriving (Show, Generic, Typeable, ToJSON, Arbitrary)
--   
--   >>> instance ToJSON User
--   
--   >>> instance ToSchema User
--   
--   >>> instance ToSchema UserId
--   
--   >>> instance Arbitrary User where arbitrary = User <$> arbitrary <*> arbitrary
--   
--   >>> type UserAPI = (Capture "user_id" UserId :> Get '[JSON] User) :<|> (ReqBody '[JSON] User :> Post '[JSON] UserId)
--   
-- --
--   >>> hspec $ context "ToJSON matches ToSchema" $ validateEveryToJSON (Proxy :: Proxy UserAPI)
--   
--   ToJSON matches ToSchema...
--     User...
--   ...
--     UserId...
--   ...
--   Finished in ... seconds
--   2 examples, 0 failures
--   
-- -- For the test to compile all body types should have the following -- instances: -- -- -- -- If any of the instances is missing, you'll get a descriptive type -- error: -- --
--   >>> data Contact = Contact { fullname :: String, phone :: Integer } deriving (Show, Generic)
--   
--   >>> instance ToJSON Contact
--   
--   >>> instance ToSchema Contact
--   
--   >>> type ContactAPI = Get '[JSON] Contact
--   
--   >>> hspec $ validateEveryToJSON (Proxy :: Proxy ContactAPI)
--   ...
--   ...No instance for ...Arbitrary Contact...
--   ...  arising from a use of ‘validateEveryToJSON’
--   ...
--   
validateEveryToJSON :: forall proxy api. TMap (Every [Typeable, Show, Arbitrary, ToJSON, ToSchema]) (BodyTypes JSON api) => proxy api -> Spec -- | Verify that every type used with JSON content type in -- a servant API has compatible ToJSON and -- ToSchema instances using -- validateToJSONWithPatternChecker. -- -- For validation without patterns see -- validateEveryToJSON. validateEveryToJSONWithPatternChecker :: forall proxy api. TMap (Every [Typeable, Show, Arbitrary, ToJSON, ToSchema]) (BodyTypes JSON api) => (Pattern -> Text -> Bool) -> proxy api -> Spec -- | Useful type families for servant APIs. module Servant.Swagger.TypeLevel -- | Check whether sub is a sub API of api. type family IsSubAPI sub api :: Constraint -- | Build a list of endpoints from an API. type family EndpointsList api -- | Extract a list of unique "body" types for a specific content-type from -- a servant API. type BodyTypes c api = Nub (BodyTypes' c api)