| Copyright | (c) 2015 GetShopTV |
|---|---|
| License | BSD3 |
| Maintainer | Nickolay Kudasov <nickolay@getshoptv.com> |
| Stability | experimental |
| Safe Haskell | None |
| Language | Haskell2010 |
Data.Swagger.Schema
Description
Types and functions for working with Swagger schema.
- class ToSchema a where
- toNamedSchema :: proxy a -> NamedSchema
- type NamedSchema = (Maybe String, Schema)
- toSchema :: ToSchema a => proxy a -> Schema
- toSchemaRef :: ToSchema a => proxy a -> Referenced Schema
- schemaName :: ToSchema a => proxy a -> Maybe String
- genericToSchema :: (Generic a, GToSchema (Rep a)) => SchemaOptions -> proxy a -> Schema
- genericToNamedSchema :: forall a proxy. (Generic a, GToSchema (Rep a)) => SchemaOptions -> proxy a -> NamedSchema
- 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
- data SchemaOptions = SchemaOptions {}
- defaultSchemaOptions :: SchemaOptions
Encoding
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 instance you can
use a default generic implementation of ToSchema.toNamedSchema
To do that, simply add deriving clause to your datatype
and declare a Generic instance for your datatype without
giving definition for ToSchema.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
type NamedSchema = (Maybe String, Schema) Source
A with an optional name.
This name can be used in references.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.
schemaName :: ToSchema a => proxy a -> Maybe String Source
Get type's schema name according to its instance.ToSchema
Generic schema encoding
genericToSchema :: (Generic a, GToSchema (Rep a)) => SchemaOptions -> proxy a -> Schema Source
A configurable generic creator.Schema
genericToNamedSchema :: forall a proxy. (Generic a, GToSchema (Rep a)) => SchemaOptions -> proxy a -> 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 toNamedSchema.Generic
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
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 ,useReferences= True ,unwrapUnaryRecords= False }