Copyright | (c) 2015 GetShopTV |
---|---|
License | BSD3 |
Maintainer | Nickolay Kudasov <nickolay@getshoptv.com> |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Types and functions for working with Swagger schema.
- class ToSchema a where
- declareNamedSchema :: proxy a -> Declare Definitions NamedSchema
- type Definitions = HashMap Text Schema
- type NamedSchema = (Maybe Text, Schema)
- declareSchema :: ToSchema a => proxy a -> Declare Definitions Schema
- declareSchemaRef :: ToSchema a => proxy a -> Declare Definitions (Referenced Schema)
- toSchema :: ToSchema a => proxy a -> Schema
- toSchemaRef :: ToSchema a => proxy a -> Referenced Schema
- schemaName :: ToSchema a => proxy a -> Maybe Text
- toInlinedSchema :: ToSchema a => proxy a -> Schema
- genericDeclareNamedSchema :: forall a proxy. (Generic a, GToSchema (Rep a)) => SchemaOptions -> proxy a -> Declare Definitions NamedSchema
- genericDeclareSchema :: (Generic a, GToSchema (Rep a)) => SchemaOptions -> proxy a -> Declare Definitions Schema
- genericToNamedSchemaBoundedIntegral :: forall a d f proxy. (Bounded a, Integral a, Generic a, Rep a ~ D1 d f, Datatype d) => SchemaOptions -> proxy a -> NamedSchema
- toSchemaBoundedIntegral :: forall a proxy. (Bounded a, Integral a) => proxy a -> Schema
- paramSchemaToNamedSchema :: forall a d f proxy. (ToParamSchema a, Generic a, Rep a ~ D1 d f, Datatype d) => SchemaOptions -> proxy a -> NamedSchema
- paramSchemaToSchema :: forall a proxy. ToParamSchema a => proxy a -> Schema
- inlineNonRecursiveSchemas :: Data s => Definitions -> s -> s
- inlineAllSchemas :: Data s => Definitions -> s -> s
- inlineSchemas :: Data s => [Text] -> Definitions -> s -> s
- inlineSchemasWhen :: Data s => (Text -> Bool) -> Definitions -> s -> s
- data SchemaOptions = SchemaOptions {}
- defaultSchemaOptions :: SchemaOptions
Encoding
Convert a type into
.Schema
An example type and instance:
{-# LANGUAGE OverloadedStrings #-} -- allows to writeText
literals {-# LANGUAGE OverloadedLists #-} -- allows to writeMap
andHashMap
as lists import Control.Lens data Coord = Coord { x :: Double, y :: Double } instance ToSchema Coord where declareNamedSchema = pure (Just "Coord", schema) where schema = mempty & schemaType .~ SwaggerObject & schemaProperties .~ [ ("x", toSchemaRef (Proxy :: Proxy Double)) , ("y", toSchemaRef (Proxy :: Proxy Double)) ] & schemaRequired .~ [ "x", "y" ]
Instead of manually writing your
instance you can
use a default generic implementation of ToSchema
.declareNamedSchema
To do that, simply add deriving
clause to your datatype
and declare a Generic
instance for your datatype without
giving definition for ToSchema
.declareNamedSchema
For instance, the previous example can be simplified into this:
{-# LANGUAGE DeriveGeneric #-} import GHC.Generics (Generic) data Coord = Coord { x :: Double, y :: Double } deriving Generic instance ToSchema Coord
Nothing
declareNamedSchema :: proxy a -> Declare Definitions NamedSchema Source
Convert a type into an optionally named schema together with all used definitions. Note that the schema itself is included in definitions only if it is recursive (and thus needs its definition in scope).
type Definitions = HashMap Text Schema Source
Schema definitions, a mapping from schema name to
.Schema
type NamedSchema = (Maybe Text, Schema) Source
A
with an optional name.
This name can be used in references.Schema
declareSchema :: ToSchema a => proxy a -> Declare Definitions Schema Source
Convert a type into a schema and declare all used schema definitions.
declareSchemaRef :: ToSchema a => proxy a -> Declare Definitions (Referenced Schema) Source
Convert a type into a referenced schema if possible and declare all used schema definitions. Only named schemas can be referenced, nameless schemas are inlined.
Schema definitions are typically declared for every referenced schema.
If
returns a reference, a corresponding schema
will be declared (regardless of whether it is recusive or not).declareSchemaRef
toSchema :: ToSchema a => proxy a -> Schema Source
Convert a type into a schema.
>>>
encode $ toSchema (Proxy :: Proxy Int8)
"{\"maximum\":127,\"minimum\":-128,\"type\":\"integer\"}"
>>>
encode $ toSchema (Proxy :: Proxy [Day])
"{\"items\":{\"$ref\":\"#/definitions/Day\"},\"type\":\"array\"}"
toSchemaRef :: ToSchema a => proxy a -> Referenced Schema Source
Convert a type into a referenced schema if possible. Only named schemas can be referenced, nameless schemas are inlined.
>>>
encode $ toSchemaRef (Proxy :: Proxy Integer)
"{\"type\":\"integer\"}"
>>>
encode $ toSchemaRef (Proxy :: Proxy Day)
"{\"$ref\":\"#/definitions/Day\"}"
schemaName :: ToSchema a => proxy a -> Maybe Text Source
Get type's schema name according to its
instance.ToSchema
>>>
schemaName (Proxy :: Proxy Int)
Nothing
>>>
schemaName (Proxy :: Proxy UTCTime)
Just "UTCTime"
toInlinedSchema :: ToSchema a => proxy a -> Schema Source
Convert a type into a schema without references.
>>>
encode $ toInlinedSchema (Proxy :: Proxy [Day])
"{\"items\":{\"format\":\"date\",\"type\":\"string\"},\"type\":\"array\"}"
WARNING:
will produce infinite schema
when inlining recursive schemas.toInlinedSchema
Generic schema encoding
genericDeclareNamedSchema :: forall a proxy. (Generic a, GToSchema (Rep a)) => SchemaOptions -> proxy a -> Declare Definitions NamedSchema Source
A configurable generic
creator.
This function applied to NamedSchema
is used as the default for defaultSchemaOptions
when the type is an instance of declareNamedSchema
.Generic
genericDeclareSchema :: (Generic a, GToSchema (Rep a)) => SchemaOptions -> proxy a -> Declare Definitions Schema Source
A configurable generic
creator.Schema
genericToNamedSchemaBoundedIntegral :: forall a d f proxy. (Bounded a, Integral a, Generic a, Rep a ~ D1 d f, Datatype d) => SchemaOptions -> proxy a -> NamedSchema Source
toSchemaBoundedIntegral :: forall a proxy. (Bounded a, Integral a) => proxy a -> Schema Source
paramSchemaToNamedSchema :: forall a d f proxy. (ToParamSchema a, Generic a, Rep a ~ D1 d f, Datatype d) => SchemaOptions -> proxy a -> NamedSchema Source
Lift a plain
into a model ParamSchema
.NamedSchema
paramSchemaToSchema :: forall a proxy. ToParamSchema a => proxy a -> Schema Source
Lift a plain
into a model ParamSchema
.Schema
Inlining Schema
s
Schema
inlineNonRecursiveSchemas :: Data s => Definitions -> s -> s Source
Inline all non-recursive schemas for which the definition
can be found in
.Definitions
inlineAllSchemas :: Data s => Definitions -> s -> s Source
Inline all schema references for which the definition
can be found in
.Definitions
WARNING:
will produce infinite schemas
when inlining recursive schemas.inlineAllSchemas
inlineSchemas :: Data s => [Text] -> Definitions -> s -> s Source
Inline any referenced schema if its name is in the given list.
NOTE: if a referenced schema is not found in definitions it stays referenced even if it appears in the list of names.
WARNING:
will produce infinite schemas
when inlining recursive schemas.inlineSchemas
inlineSchemasWhen :: Data s => (Text -> Bool) -> Definitions -> s -> s Source
Inline any referenced schema if its name satisfies given predicate.
NOTE: if a referenced schema is not found in definitions the predicate is ignored and schema stays referenced.
WARNING:
will produce infinite schemas
when inlining recursive schemas.inlineSchemasWhen
Generic encoding configuration
data SchemaOptions Source
Options that specify how to encode your type to Swagger schema.
SchemaOptions | |
|
defaultSchemaOptions :: SchemaOptions Source
Default encoding
.SchemaOptions
SchemaOptions
{fieldLabelModifier
= id ,constructorTagModifier
= id ,datatypeNameModifier
= id ,allNullaryToStringTag
= True ,unwrapUnaryRecords
= False }