swagger2-1.1: Swagger 2.0 data model

Safe HaskellNone
LanguageHaskell2010

Data.Swagger.Internal.Schema

Synopsis

Documentation

type NamedSchema = (Maybe Text, Schema) Source

A Schema with an optional name. This name can be used in references.

type Definitions = HashMap Text Schema Source

Schema definitions, a mapping from schema name to Schema.

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

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 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

Minimal complete definition

Nothing

Methods

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).

Instances

ToSchema Bool Source 
ToSchema Char Source 
ToSchema Double Source 
ToSchema Float Source 
ToSchema Int Source 
ToSchema Int8 Source 
ToSchema Int16 Source 
ToSchema Int32 Source 
ToSchema Int64 Source 
ToSchema Integer Source 
ToSchema Word Source 
ToSchema Word8 Source 
ToSchema Word16 Source 
ToSchema Word32 Source 
ToSchema Word64 Source 
ToSchema String Source 
ToSchema () Source 
ToSchema Scientific Source 
ToSchema Text Source 
ToSchema UTCTime Source
>>> toSchema (Proxy :: Proxy UTCTime) ^. schemaFormat
Just "yyyy-mm-ddThh:MM:ssZ"
ToSchema Text Source 
ToSchema All Source 
ToSchema Any Source 
ToSchema IntSet Source 
ToSchema LocalTime Source
>>> toSchema (Proxy :: Proxy LocalTime) ^. schemaFormat
Just "yyyy-mm-ddThh:MM:ss"
ToSchema ZonedTime Source

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

ToSchema NominalDiffTime Source 
ToSchema Day Source

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

ToSchema a => ToSchema [a] Source 
ToSchema a => ToSchema (Maybe a) Source 
ToSchema a => ToSchema (Dual a) Source 
ToSchema a => ToSchema (Sum a) Source 
ToSchema a => ToSchema (Product a) Source 
ToSchema a => ToSchema (First a) Source 
ToSchema a => ToSchema (Last a) Source 
ToSchema a => ToSchema (IntMap a) Source

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

ToSchema a => ToSchema (Set a) Source 
ToSchema a => ToSchema (HashSet a) Source 
(ToSchema a, ToSchema b) => ToSchema (Either a b) Source 
(ToSchema a, ToSchema b) => ToSchema (a, b) Source 
ToSchema a => ToSchema (HashMap String a) Source 
ToSchema a => ToSchema (HashMap Text a) Source 
ToSchema a => ToSchema (HashMap Text a) Source 
ToSchema a => ToSchema (Map String a) Source 
ToSchema a => ToSchema (Map Text a) Source 
ToSchema a => ToSchema (Map Text a) Source 
(ToSchema a, ToSchema b, ToSchema c) => ToSchema (a, b, c) Source 
(ToSchema a, ToSchema b, ToSchema c, ToSchema d) => ToSchema (a, b, c, d) Source 
(ToSchema a, ToSchema b, ToSchema c, ToSchema d, ToSchema e) => ToSchema (a, b, c, d, e) Source 
(ToSchema a, ToSchema b, ToSchema c, ToSchema d, ToSchema e, ToSchema f) => ToSchema (a, b, c, d, e, f) Source 
(ToSchema a, ToSchema b, ToSchema c, ToSchema d, ToSchema e, ToSchema f, ToSchema g) => ToSchema (a, b, c, d, e, f, g) Source 

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

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

toNamedSchema :: ToSchema a => proxy a -> NamedSchema Source

Convert a type into an optionally named schema.

>>> encode <$> toNamedSchema (Proxy :: Proxy String)
(Nothing,"{\"type\":\"string\"}")
>>> encode <$> toNamedSchema (Proxy :: Proxy Day)
(Just "Day","{\"format\":\"date\",\"type\":\"string\"}")

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"

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\"}"

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

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: inlineSchemasWhen will produce infinite schemas when inlining recursive schemas.

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: inlineSchemas will produce infinite schemas when inlining recursive schemas.

inlineAllSchemas :: Data s => Definitions -> 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.

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: toInlinedSchema will produce infinite schema when inlining recursive schemas.

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

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

class GToSchema f where Source

Instances

GToSchema U1 Source 
ToSchema c => GToSchema (K1 i c) Source 
ToSchema c => GToSchema (K1 i (Maybe c)) Source 
(GSumToSchema (* -> *) f, GSumToSchema (* -> *) g) => GToSchema ((:+:) f g) Source 
(GToSchema f, GToSchema g) => GToSchema ((:*:) f g) Source 
(Datatype d, GToSchema f) => GToSchema (D1 d f) Source 
(Selector s, GToSchema f) => GToSchema (C1 c (S1 s f)) Source

Single field constructor.

GToSchema f => GToSchema (C1 c f) Source 
(Selector s, GToSchema f) => GToSchema (S1 s f) Source

Record fields.

(Selector s, ToSchema c) => GToSchema (S1 s (K1 i (Maybe c))) Source

Optional record fields.

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\"}"

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.

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

A configurable generic Schema creator.

genericDeclareNamedSchema :: forall a proxy. (Generic a, GToSchema (Rep a)) => SchemaOptions -> proxy a -> Declare Definitions 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.

gdatatypeSchemaName :: forall proxy d. Datatype d => SchemaOptions -> proxy d -> Maybe Text 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 ParamSchema into a model NamedSchema.

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

Lift a plain ParamSchema into a model Schema.

withFieldSchema :: forall proxy s f. (Selector s, GToSchema f) => SchemaOptions -> proxy s f -> Bool -> Schema -> Declare Definitions Schema Source

class GSumToSchema f where Source

Instances

(GSumToSchema (* -> *) f, GSumToSchema (* -> *) g) => GSumToSchema (* -> *) ((:+:) f g) Source 
Constructor c => GSumToSchema (* -> *) (C1 c U1) Source 
(Constructor c, Selector s, GToSchema f) => GSumToSchema (* -> *) (C1 c (S1 s f)) Source 
(Constructor c, GToSchema f) => GSumToSchema (* -> *) (C1 c f) Source 

gsumConToSchema :: forall c f proxy. (GToSchema (C1 c f), Constructor c) => SchemaOptions -> proxy (C1 c f) -> Schema -> Declare Definitions Schema Source

data Proxy2 a b Source

Constructors

Proxy2 

data Proxy3 a b c Source

Constructors

Proxy3