swagger2-0.4.1: Swagger 2.0 data model

Safe HaskellNone
LanguageHaskell2010

Data.Swagger.Schema.Internal

Synopsis

Documentation

type NamedSchema = (Maybe String, Schema) Source

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

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

import Control.Lens

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

instance ToSchema Coord where
  toNamedSchema = (Just "Coord", mempty
     & schemaType .~ SchemaObject
     & 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 toNamedSchema.

To do that, simply add deriving Generic clause to your datatype and declare a ToSchema instance for your datatype without giving definition for toNamedSchema.

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

toNamedSchema :: proxy a -> NamedSchema Source

Convert a type into an optionally named schema.

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
>>> toSchema (Proxy :: Proxy ZonedTime) ^. schemaFormat
Just "yyyy-mm-ddThh:MM:ss(Z|+hh:MM)"
ToSchema NominalDiffTime Source 
ToSchema Day Source
>>> toSchema (Proxy :: Proxy Day) ^. schemaFormat
Just "yyyy-mm-dd"
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 

schemaName :: ToSchema a => proxy a -> Maybe String Source

Get type's schema name according to its ToSchema instance.

toSchema :: ToSchema a => proxy a -> Schema Source

Convert a type into a schema.

toSchemaRef :: ToSchema a => proxy a -> Referenced Schema Source

Convert a type into a referenced schema if possible. Only named schemas can be references, nameless schemas are inlined.

class GToSchema f where Source

Instances

GToSchema U1 Source 
ToSchema c => GToSchema (K1 i 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.

data SchemaOptions Source

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

Constructors

SchemaOptions 

Fields

fieldLabelModifier :: String -> String

Function applied to field labels. Handy for removing common record prefixes for example.

constructorTagModifier :: String -> String

Function applied to constructor tags which could be handy for lower-casing them for example.

datatypeNameModifier :: String -> String

Function applied to datatype name.

allNullaryToStringTag :: Bool

If True the constructors of a datatype, with all nullary constructors, will be encoded to a string enumeration schema with the constructor tags as possible values.

useReferences :: Bool

If True direct subschemas will be referenced if possible (rather than inlined). Note that this option does not influence nested schemas, e.g. for these types

data Object = Object String deriving Generic
instance ToSchema Object

newtype Objects = Objects [Object] deriving Generic
instance ToSchema Objects where
   toNamedSchema = genericToNamedSchema defaultSchemaOptions
     { useReferences = False }

Schema for Objects will not inline Object schema because it is nested in a [] schema.

unwrapUnaryRecords :: Bool

Hide the field name when a record constructor has only one field, like a newtype.

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

Default schema for Bounded, Integral types.

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.

genericToSchema :: (Generic a, GToSchema (Rep a)) => SchemaOptions -> proxy a -> Schema Source

A configurable generic Schema creator.

genericToNamedSchema :: forall a proxy. (Generic a, GToSchema (Rep a)) => SchemaOptions -> proxy a -> NamedSchema Source

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

gdatatypeSchemaName :: forall proxy d. Datatype d => SchemaOptions -> proxy d -> Maybe String Source

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

class GSumToSchema f where Source

Instances

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

gsumConToSchema :: forall c f proxy. Constructor c => Bool -> Referenced Schema -> SchemaOptions -> proxy (C1 c f) -> Schema -> (AllNullary, Schema) Source

data Proxy2 a b Source

Constructors

Proxy2 

data Proxy3 a b c Source

Constructors

Proxy3