| Maintainer | Nickolay Kudasov <nickolay@getshoptv.com> | 
|---|---|
| Stability | experimental | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
Data.OpenApi.Schema
Description
Types and functions for working with Swagger schema.
Synopsis
- class Typeable a => ToSchema a where- declareNamedSchema :: Proxy a -> Declare (Definitions Schema) NamedSchema
 
- declareSchema :: ToSchema a => Proxy a -> Declare (Definitions Schema) Schema
- declareSchemaRef :: ToSchema a => Proxy a -> Declare (Definitions Schema) (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. (Generic a, GToSchema (Rep a), Typeable a) => SchemaOptions -> Proxy a -> Declare (Definitions Schema) NamedSchema
- genericDeclareSchema :: (Generic a, GToSchema (Rep a), Typeable a) => SchemaOptions -> Proxy a -> Declare (Definitions Schema) Schema
- genericDeclareNamedSchemaNewtype :: forall a d c s i inner. (Generic a, Datatype d, Rep a ~ D1 d (C1 c (S1 s (K1 i inner)))) => SchemaOptions -> (Proxy inner -> Declare (Definitions Schema) Schema) -> Proxy a -> Declare (Definitions Schema) NamedSchema
- genericNameSchema :: forall a d f. (Generic a, Rep a ~ D1 d f, Datatype d) => SchemaOptions -> Proxy a -> Schema -> NamedSchema
- genericToNamedSchemaBoundedIntegral :: forall a d f. (Bounded a, Integral a, Generic a, Rep a ~ D1 d f, Datatype d) => SchemaOptions -> Proxy a -> NamedSchema
- toSchemaBoundedIntegral :: forall a. (Bounded a, Integral a) => Proxy a -> Schema
- declareSchemaBoundedEnumKeyMapping :: forall map key value. (Bounded key, Enum key, ToJSONKey key, ToSchema key, ToSchema value) => Proxy (map key value) -> Declare (Definitions Schema) Schema
- toSchemaBoundedEnumKeyMapping :: forall map key value. (Bounded key, Enum key, ToJSONKey key, ToSchema key, ToSchema value) => Proxy (map key value) -> Schema
- paramSchemaToNamedSchema :: (ToParamSchema a, Generic a, Rep a ~ D1 d f, Datatype d) => SchemaOptions -> Proxy a -> NamedSchema
- paramSchemaToSchema :: ToParamSchema a => Proxy a -> Schema
- sketchSchema :: ToJSON a => a -> Schema
- sketchStrictSchema :: ToJSON a => a -> Schema
- inlineNonRecursiveSchemas :: Data s => Definitions Schema -> s -> s
- inlineAllSchemas :: Data s => Definitions Schema -> s -> s
- inlineSchemas :: Data s => [Text] -> Definitions Schema -> s -> s
- inlineSchemasWhen :: Data s => (Text -> Bool) -> Definitions Schema -> s -> s
- data SchemaOptions = SchemaOptions {}
- defaultSchemaOptions :: SchemaOptions
- fromAesonOptions :: Options -> SchemaOptions
Encoding
class Typeable a => 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.OpenApi
data Coord = Coord { x :: Double, y :: Double }
instance ToSchema Coord where
  declareNamedSchema _ = do
    doubleSchema <- declareSchemaRef (Proxy :: Proxy Double)
    return $ NamedSchema (Just "Coord") $ mempty
      & type_ ?~ OpenApiObject
      & properties .~
          [ ("x", doubleSchema)
          , ("y", doubleSchema)
          ]
      & required .~ [ "x", "y" ]
Instead of manually writing your ToSchemadeclareNamedSchema
To do that, simply add deriving  clause to your datatype
 and declare a GenericToSchemadeclareNamedSchema
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 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).
default declareNamedSchema :: (Generic a, GToSchema (Rep a)) => Proxy a -> Declare (Definitions Schema) NamedSchema Source #
Instances
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
toSchema :: ToSchema a => Proxy a -> Schema Source #
Convert a type into a schema.
>>>BSL.putStrLn $ encodePretty $ toSchema (Proxy :: Proxy Int8){ "maximum": 127, "minimum": -128, "type": "integer" }
>>>BSL.putStrLn $ encodePretty $ toSchema (Proxy :: Proxy [Day]){ "items": { "$ref": "#/components/schemas/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.
>>>BSL.putStrLn $ encodePretty $ toSchemaRef (Proxy :: Proxy Integer){ "type": "integer" }
>>>BSL.putStrLn $ encodePretty $ toSchemaRef (Proxy :: Proxy Day){ "$ref": "#/components/schemas/Day" }
schemaName :: ToSchema a => Proxy a -> Maybe Text Source #
Get type's schema name according to its 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.
>>>BSL.putStrLn $ encodePretty $ toInlinedSchema (Proxy :: Proxy [Day]){ "items": { "example": "2016-07-22", "format": "date", "type": "string" }, "type": "array" }
WARNING: toInlinedSchema
Generic schema encoding
genericDeclareNamedSchema :: forall a. (Generic a, GToSchema (Rep a), Typeable a) => SchemaOptions -> Proxy a -> Declare (Definitions Schema) NamedSchema Source #
A configurable generic NamedSchemadefaultSchemaOptionsdeclareNamedSchemaGeneric
Default implementation will use the name from Typeable instance, including concrete
 instantioations of type variables.
For example:
>>>_namedSchemaName $ undeclare $ genericDeclareNamedSchema defaultSchemaOptions (Proxy :: Proxy (Either Int Bool))Just "Either_Int_Bool"
genericDeclareSchema :: (Generic a, GToSchema (Rep a), Typeable a) => SchemaOptions -> Proxy a -> Declare (Definitions Schema) Schema Source #
A configurable generic Schema
genericDeclareNamedSchemaNewtype Source #
Arguments
| :: forall a d c s i inner. (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. (Generic a, Rep a ~ D1 d f, Datatype d) => SchemaOptions -> Proxy a -> Schema -> NamedSchema Source #
Bounded Integral
genericToNamedSchemaBoundedIntegral :: forall a d f. (Bounded a, Integral a, Generic a, Rep a ~ D1 d f, Datatype d) => SchemaOptions -> Proxy a -> NamedSchema Source #
Bounded Enum key mappings
declareSchemaBoundedEnumKeyMapping :: forall map key value. (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>>>BSL.putStrLn $ encodePretty $ toSchemaBoundedEnumKeyMapping (Proxy :: Proxy (Map ButtonState ImageUrl)){ "properties": { "Active": { "type": "string" }, "Disabled": { "type": "string" }, "Focus": { "type": "string" }, "Hover": { "type": "string" }, "Neutral": { "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. (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>>>BSL.putStrLn $ encodePretty $ toSchemaBoundedEnumKeyMapping (Proxy :: Proxy (Map ButtonState ImageUrl)){ "properties": { "Active": { "type": "string" }, "Disabled": { "type": "string" }, "Focus": { "type": "string" }, "Hover": { "type": "string" }, "Neutral": { "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 :: (ToParamSchema a, Generic a, Rep a ~ D1 d f, Datatype d) => SchemaOptions -> Proxy a -> NamedSchema Source #
Construct NamedSchema usinng ToParamSchema.
paramSchemaToSchema :: ToParamSchema a => Proxy a -> Schema Source #
Construct Schema usinng ToParamSchema.
Sketching SchemaToJSON
SchemaToJSONsketchSchema :: ToJSON a => a -> Schema Source #
Make an unrestrictive sketch of a SchemaToJSON
>>>BSL.putStrLn $ encodePretty $ sketchSchema "hello"{ "example": "hello", "type": "string" }
>>>BSL.putStrLn $ encodePretty $ sketchSchema (1, 2, 3){ "example": [ 1, 2, 3 ], "items": { "type": "number" }, "type": "array" }
>>>BSL.putStrLn $ encodePretty $ 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>>>BSL.putStrLn $ encodePretty $ sketchSchema (Person "Jack" 25){ "example": { "age": 25, "name": "Jack" }, "properties": { "age": { "type": "number" }, "name": { "type": "string" } }, "required": [ "age", "name" ], "type": "object" }
sketchStrictSchema :: ToJSON a => a -> Schema Source #
Make a restrictive sketch of a SchemaToJSON
>>>BSL.putStrLn $ encodePretty $ sketchStrictSchema "hello"{ "enum": [ "hello" ], "maxLength": 5, "minLength": 5, "pattern": "hello", "type": "string" }
>>>BSL.putStrLn $ encodePretty $ sketchStrictSchema (1, 2, 3){ "enum": [ [ 1, 2, 3 ] ], "items": [ { "enum": [ 1 ], "maximum": 1, "minimum": 1, "multipleOf": 1, "type": "number" }, { "enum": [ 2 ], "maximum": 2, "minimum": 2, "multipleOf": 2, "type": "number" }, { "enum": [ 3 ], "maximum": 3, "minimum": 3, "multipleOf": 3, "type": "number" } ], "maxItems": 3, "minItems": 3, "type": "array", "uniqueItems": true }
>>>BSL.putStrLn $ encodePretty $ sketchStrictSchema ("Jack", 25){ "enum": [ [ "Jack", 25 ] ], "items": [ { "enum": [ "Jack" ], "maxLength": 4, "minLength": 4, "pattern": "Jack", "type": "string" }, { "enum": [ 25 ], "maximum": 25, "minimum": 25, "multipleOf": 25, "type": "number" } ], "maxItems": 2, "minItems": 2, "type": "array", "uniqueItems": true }
>>>data Person = Person { name :: String, age :: Int } deriving (Generic)>>>instance ToJSON Person>>>BSL.putStrLn $ encodePretty $ sketchStrictSchema (Person "Jack" 25){ "enum": [ { "age": 25, "name": "Jack" } ], "maxProperties": 2, "minProperties": 2, "properties": { "age": { "enum": [ 25 ], "maximum": 25, "minimum": 25, "multipleOf": 25, "type": "number" }, "name": { "enum": [ "Jack" ], "maxLength": 4, "minLength": 4, "pattern": "Jack", "type": "string" } }, "required": [ "age", "name" ], "type": "object" }
Inlining Schema
SchemainlineNonRecursiveSchemas :: 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
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
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
Generic encoding configuration
data SchemaOptions Source #
Options that specify how to encode your type to Swagger schema.
Constructors
| SchemaOptions | |
| Fields 
 | |
defaultSchemaOptions :: SchemaOptions Source #
Default encoding SchemaOptions
SchemaOptions{fieldLabelModifier= id ,constructorTagModifier= id ,datatypeNameModifier= id ,allNullaryToStringTag= True ,unwrapUnaryRecords= False ,sumEncoding=defaultTaggedObject}
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: 2.2.1