swagger2-2.3: Swagger 2.0 data model

MaintainerNickolay Kudasov <nickolay@getshoptv.com>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Data.Swagger.Schema

Contents

Description

Types and functions for working with Swagger schema.

Synopsis

Encoding

class ToSchema a where Source #

Convert a type into Schema.

An example type and instance:

{-# LANGUAGE OverloadedStrings #-}   -- allows to write Text literals
{-# LANGUAGE OverloadedLists #-}     -- allows to write Map and HashMap as lists

import Control.Lens
import Data.Proxy
import Data.Swagger

data Coord = Coord { x :: Double, y :: Double }

instance ToSchema Coord where
  declareNamedSchema _ = do
    doubleSchema <- declareSchemaRef (Proxy :: Proxy Double)
    return $ NamedSchema (Just "Coord") $ mempty
      & type_ .~ SwaggerObject
      & properties .~
          [ ("x", doubleSchema)
          , ("y", doubleSchema)
          ]
      & required .~ [ "x", "y" ]

Instead of manually writing your ToSchema instance you can use a default generic implementation of declareNamedSchema.

To do that, simply add deriving Generic clause to your datatype and declare a ToSchema instance for your datatype without giving definition for 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

Methods

declareNamedSchema :: proxy a -> Declare (Definitions Schema) 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).

declareNamedSchema :: (Generic a, GToSchema (Rep a), TypeHasSimpleShape a "genericDeclareNamedSchemaUnrestricted") => proxy a -> Declare (Definitions Schema) 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).

Instances
ToSchema Bool Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Char Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Double Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Float Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Int Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Int8 Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Int16 Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Int32 Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Int64 Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Integer Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Natural Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Word Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Word8 Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Word16 Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Word32 Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Word64 Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema () Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

(ToSchemaByteStringError ByteString :: Constraint) => ToSchema ByteString Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

(ToSchemaByteStringError ByteString :: Constraint) => ToSchema ByteString Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Scientific Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema String Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Text Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema UTCTime Source #
>>> toSchema (Proxy :: Proxy UTCTime) ^. format
Just "yyyy-mm-ddThh:MM:ssZ"
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Object Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Text Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Version Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema All Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Any Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema IntSet Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema ZonedTime Source #

Format "date" corresponds to yyyy-mm-ddThh:MM:ss(Z|+hh:MM) format.

Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema LocalTime Source #
>>> toSchema (Proxy :: Proxy LocalTime) ^. format
Just "yyyy-mm-ddThh:MM:ss"
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema NominalDiffTime Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema Day Source #

Format "date" corresponds to yyyy-mm-dd format.

Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema UUID Source #

For ToJSON instance, see uuid-aeson package.

Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema a => ToSchema [a] Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema a => ToSchema (Maybe a) Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

HasResolution a => ToSchema (Fixed a) Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema a => ToSchema (Identity a) Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema a => ToSchema (First a) Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema a => ToSchema (Last a) Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema a => ToSchema (Dual a) Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema a => ToSchema (Sum a) Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema a => ToSchema (Product a) Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema a => ToSchema (NonEmpty a) Source #

Since: swagger2-2.2.1

Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema a => ToSchema (IntMap a) Source #

NOTE: This schema does not account for the uniqueness of keys.

Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema a => ToSchema (Set a) Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema a => ToSchema (Vector a) Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema a => ToSchema (Vector a) Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema a => ToSchema (Vector a) Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema a => ToSchema (HashSet a) Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

ToSchema a => ToSchema (Vector a) Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

(ToSchema a, ToSchema b) => ToSchema (Either a b) Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

(ToSchema a, ToSchema b) => ToSchema (a, b) Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

(ToJSONKey k, ToSchema k, ToSchema v) => ToSchema (HashMap k v) Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

(ToJSONKey k, ToSchema k, ToSchema v) => ToSchema (Map k v) Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

(ToSchema a, ToSchema b, ToSchema c) => ToSchema (a, b, c) Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

(ToSchema a, ToSchema b, ToSchema c, ToSchema d) => ToSchema (a, b, c, d) Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

Methods

declareNamedSchema :: proxy (a, b, c, d) -> Declare (Definitions Schema) NamedSchema Source #

(ToSchema a, ToSchema b, ToSchema c, ToSchema d, ToSchema e) => ToSchema (a, b, c, d, e) Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

Methods

declareNamedSchema :: proxy (a, b, c, d, e) -> Declare (Definitions Schema) NamedSchema Source #

(ToSchema a, ToSchema b, ToSchema c, ToSchema d, ToSchema e, ToSchema f) => ToSchema (a, b, c, d, e, f) Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

Methods

declareNamedSchema :: proxy (a, b, c, d, e, f) -> Declare (Definitions Schema) NamedSchema Source #

(ToSchema a, ToSchema b, ToSchema c, ToSchema d, ToSchema e, ToSchema f, ToSchema g) => ToSchema (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Data.Swagger.Internal.Schema

Methods

declareNamedSchema :: proxy (a, b, c, d, e, f, g) -> Declare (Definitions Schema) NamedSchema Source #

declareSchema :: ToSchema a => proxy a -> Declare (Definitions Schema) Schema Source #

Convert a type into a schema and declare all used schema definitions.

declareSchemaRef :: ToSchema a => proxy a -> Declare (Definitions Schema) (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 declareSchemaRef returns a reference, a corresponding schema will be declared (regardless of whether it is recusive or not).

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 ToSchema instance.

>>> 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\":{\"example\":\"2016-07-22\",\"format\":\"date\",\"type\":\"string\"},\"type\":\"array\"}"

WARNING: toInlinedSchema will produce infinite schema when inlining recursive schemas.

Generic schema encoding

genericDeclareNamedSchema :: forall a proxy. (Generic a, GToSchema (Rep a), TypeHasSimpleShape a "genericDeclareNamedSchemaUnrestricted") => SchemaOptions -> proxy a -> Declare (Definitions Schema) NamedSchema Source #

A configurable generic NamedSchema creator. This function applied to defaultSchemaOptions is used as the default for declareNamedSchema when the type is an instance of Generic.

genericDeclareSchema :: (Generic a, GToSchema (Rep a), TypeHasSimpleShape a "genericDeclareSchemaUnrestricted") => SchemaOptions -> proxy a -> Declare (Definitions Schema) Schema Source #

A configurable generic Schema creator.

genericDeclareNamedSchemaNewtype Source #

Arguments

:: (Generic a, Datatype d, Rep a ~ D1 d (C1 c (S1 s (K1 i inner)))) 
=> SchemaOptions

How to derive the name.

-> (Proxy inner -> Declare (Definitions Schema) Schema)

How to create a schema for the wrapped type.

-> proxy a 
-> Declare (Definitions Schema) NamedSchema 

Declare a named schema for a newtype wrapper.

genericNameSchema :: forall a d f proxy. (Generic a, Rep a ~ D1 d f, Datatype d) => SchemaOptions -> proxy a -> Schema -> NamedSchema Source #

Derive a Generic-based name for a datatype and assign it to a given Schema.

Bounded Integral

genericToNamedSchemaBoundedIntegral :: forall a d f proxy. (Bounded a, Integral a, Generic a, Rep a ~ D1 d f, Datatype d) => SchemaOptions -> proxy a -> NamedSchema Source #

Default generic named schema for Bounded, Integral types.

toSchemaBoundedIntegral :: forall a proxy. (Bounded a, Integral a) => proxy a -> Schema Source #

Default schema for Bounded, Integral types.

>>> encode $ toSchemaBoundedIntegral (Proxy :: Proxy Int16)
"{\"maximum\":32767,\"minimum\":-32768,\"type\":\"integer\"}"

Bounded Enum key mappings

declareSchemaBoundedEnumKeyMapping :: forall map key value proxy. (Bounded key, Enum key, ToJSONKey key, ToSchema key, ToSchema value) => proxy (map key value) -> Declare (Definitions Schema) Schema Source #

Declare Schema for a mapping with Bounded Enum keys. This makes a much more useful schema when there aren't many options for key values.

>>> data ButtonState = Neutral | Focus | Active | Hover | Disabled deriving (Show, Bounded, Enum, Generic)
>>> instance ToJSON ButtonState
>>> instance ToSchema ButtonState
>>> instance ToJSONKey ButtonState where toJSONKey = toJSONKeyText (T.pack . show)
>>> type ImageUrl = T.Text
>>> encode $ toSchemaBoundedEnumKeyMapping (Proxy :: Proxy (Map ButtonState ImageUrl))
"{\"properties\":{\"Neutral\":{\"type\":\"string\"},\"Focus\":{\"type\":\"string\"},\"Active\":{\"type\":\"string\"},\"Hover\":{\"type\":\"string\"},\"Disabled\":{\"type\":\"string\"}},\"type\":\"object\"}"

Note: this is only useful when key is encoded with ToJSONKeyText. If it is encoded with ToJSONKeyValue then a regular schema for [(key, value)] is used.

toSchemaBoundedEnumKeyMapping :: forall map key value proxy. (Bounded key, Enum key, ToJSONKey key, ToSchema key, ToSchema value) => proxy (map key value) -> Schema Source #

A Schema for a mapping with Bounded Enum keys. This makes a much more useful schema when there aren't many options for key values.

>>> data ButtonState = Neutral | Focus | Active | Hover | Disabled deriving (Show, Bounded, Enum, Generic)
>>> instance ToJSON ButtonState
>>> instance ToSchema ButtonState
>>> instance ToJSONKey ButtonState where toJSONKey = toJSONKeyText (T.pack . show)
>>> type ImageUrl = T.Text
>>> encode $ toSchemaBoundedEnumKeyMapping (Proxy :: Proxy (Map ButtonState ImageUrl))
"{\"properties\":{\"Neutral\":{\"type\":\"string\"},\"Focus\":{\"type\":\"string\"},\"Active\":{\"type\":\"string\"},\"Hover\":{\"type\":\"string\"},\"Disabled\":{\"type\":\"string\"}},\"type\":\"object\"}"

Note: this is only useful when key is encoded with ToJSONKeyText. If it is encoded with ToJSONKeyValue then a regular schema for [(key, value)] is used.

Reusing ToParamSchema

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 ParamSchema into a model NamedSchema.

paramSchemaToSchema :: forall a proxy. ToParamSchema a => proxy a -> Schema Source #

Lift a plain ParamSchema into a model Schema.

Unrestricted versions

genericDeclareNamedSchemaUnrestricted :: forall a proxy. (Generic a, GToSchema (Rep a)) => SchemaOptions -> proxy a -> Declare (Definitions Schema) NamedSchema Source #

A configurable generic NamedSchema creator.

Unlike genericDeclareNamedSchema also works for mixed sum types. Use with care since some Swagger tools do not support well schemas for mixed sum types.

genericDeclareSchemaUnrestricted :: (Generic a, GToSchema (Rep a)) => SchemaOptions -> proxy a -> Declare (Definitions Schema) Schema Source #

A configurable generic Schema creator.

Unlike genericDeclareSchema also works for mixed sum types. Use with care since some Swagger tools do not support well schemas for mixed sum types.

Schema templates

passwordSchema :: Schema Source #

Default schema for password string. "password" format is used to hint UIs the input needs to be obscured.

binarySchema :: Schema Source #

Default schema for binary data (any sequence of octets).

byteSchema :: Schema Source #

Default schema for binary data (base64 encoded).

Sketching Schemas using ToJSON

sketchSchema :: ToJSON a => a -> Schema Source #

Make an unrestrictive sketch of a Schema based on a ToJSON instance. Produced schema can be used for further refinement.

>>> encode $ sketchSchema "hello"
"{\"example\":\"hello\",\"type\":\"string\"}"
>>> encode $ sketchSchema (1, 2, 3)
"{\"example\":[1,2,3],\"items\":{\"type\":\"number\"},\"type\":\"array\"}"
>>> encode $ sketchSchema ("Jack", 25)
"{\"example\":[\"Jack\",25],\"items\":[{\"type\":\"string\"},{\"type\":\"number\"}],\"type\":\"array\"}"
>>> data Person = Person { name :: String, age :: Int } deriving (Generic)
>>> instance ToJSON Person
>>> encode $ sketchSchema (Person "Jack" 25)
"{\"required\":[\"age\",\"name\"],\"properties\":{\"age\":{\"type\":\"number\"},\"name\":{\"type\":\"string\"}},\"example\":{\"age\":25,\"name\":\"Jack\"},\"type\":\"object\"}"

sketchStrictSchema :: ToJSON a => a -> Schema Source #

Make a restrictive sketch of a Schema based on a ToJSON instance. Produced schema uses as much constraints as possible.

>>> encode $ sketchStrictSchema "hello"
"{\"maxLength\":5,\"pattern\":\"hello\",\"minLength\":5,\"type\":\"string\",\"enum\":[\"hello\"]}"
>>> encode $ sketchStrictSchema (1, 2, 3)
"{\"minItems\":3,\"uniqueItems\":true,\"items\":[{\"maximum\":1,\"minimum\":1,\"multipleOf\":1,\"type\":\"number\",\"enum\":[1]},{\"maximum\":2,\"minimum\":2,\"multipleOf\":2,\"type\":\"number\",\"enum\":[2]},{\"maximum\":3,\"minimum\":3,\"multipleOf\":3,\"type\":\"number\",\"enum\":[3]}],\"maxItems\":3,\"type\":\"array\",\"enum\":[[1,2,3]]}"
>>> encode $ sketchStrictSchema ("Jack", 25)
"{\"minItems\":2,\"uniqueItems\":true,\"items\":[{\"maxLength\":4,\"pattern\":\"Jack\",\"minLength\":4,\"type\":\"string\",\"enum\":[\"Jack\"]},{\"maximum\":25,\"minimum\":25,\"multipleOf\":25,\"type\":\"number\",\"enum\":[25]}],\"maxItems\":2,\"type\":\"array\",\"enum\":[[\"Jack\",25]]}"
>>> data Person = Person { name :: String, age :: Int } deriving (Generic)
>>> instance ToJSON Person
>>> encode $ sketchStrictSchema (Person "Jack" 25)
"{\"required\":[\"age\",\"name\"],\"properties\":{\"age\":{\"maximum\":25,\"minimum\":25,\"multipleOf\":25,\"type\":\"number\",\"enum\":[25]},\"name\":{\"maxLength\":4,\"pattern\":\"Jack\",\"minLength\":4,\"type\":\"string\",\"enum\":[\"Jack\"]}},\"maxProperties\":2,\"minProperties\":2,\"type\":\"object\",\"enum\":[{\"age\":25,\"name\":\"Jack\"}]}"

Inlining Schemas

inlineNonRecursiveSchemas :: Data s => Definitions Schema -> s -> s Source #

Inline all non-recursive schemas for which the definition can be found in Definitions.

inlineAllSchemas :: Data s => Definitions Schema -> s -> s Source #

Inline all schema references for which the definition can be found in Definitions.

WARNING: inlineAllSchemas will produce infinite schemas when inlining recursive schemas.

inlineSchemas :: Data s => [Text] -> Definitions Schema -> 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: inlineSchemas will produce infinite schemas when inlining recursive schemas.

inlineSchemasWhen :: Data s => (Text -> Bool) -> Definitions Schema -> 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: inlineSchemasWhen will produce infinite schemas when inlining recursive schemas.

Generic encoding configuration

data SchemaOptions Source #

Options that specify how to encode your type to Swagger schema.

Constructors

SchemaOptions 

Fields

fromAesonOptions :: Options -> SchemaOptions Source #

Convert Options to SchemaOptions.

Specifically the following fields get copied:

Note that these fields have no effect on SchemaOptions:

The rest is defined as in defaultSchemaOptions.

Since: swagger2-2.2.1