| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Swagger.Schema.Internal
- type NamedSchema = (Maybe String, Schema)
- unnamed :: Schema -> NamedSchema
- named :: String -> Schema -> NamedSchema
- class ToSchema a where
- toNamedSchema :: proxy a -> NamedSchema
- schemaName :: ToSchema a => proxy a -> Maybe String
- toSchema :: ToSchema a => proxy a -> Schema
- toSchemaRef :: ToSchema a => proxy a -> Referenced Schema
- class GToSchema f where
- gtoNamedSchema :: SchemaOptions -> proxy f -> Schema -> NamedSchema
- gtoSchema :: GToSchema f => SchemaOptions -> proxy f -> Schema -> Schema
- timeNamedSchema :: String -> String -> NamedSchema
- data SchemaOptions = SchemaOptions {}
- defaultSchemaOptions :: SchemaOptions
- toSchemaBoundedIntegral :: forall a proxy. (Bounded a, Integral a) => proxy a -> Schema
- genericToNamedSchemaBoundedIntegral :: forall a d f proxy. (Bounded a, Integral a, Generic a, Rep a ~ D1 d f, Datatype d) => SchemaOptions -> proxy a -> NamedSchema
- genericToSchema :: (Generic a, GToSchema (Rep a)) => SchemaOptions -> proxy a -> Schema
- genericToNamedSchema :: forall a proxy. (Generic a, GToSchema (Rep a)) => SchemaOptions -> proxy a -> NamedSchema
- gdatatypeSchemaName :: forall proxy d. Datatype d => SchemaOptions -> proxy d -> Maybe String
- nullarySchema :: Schema
- gtoSchemaRef :: GToSchema f => SchemaOptions -> proxy f -> Referenced Schema
- appendItem :: Referenced Schema -> Maybe SchemaItems -> Maybe SchemaItems
- withFieldSchema :: forall proxy s f. (Selector s, GToSchema f) => SchemaOptions -> proxy s f -> Bool -> Schema -> Schema
- type AllNullary = All
- class GSumToSchema f where
- gsumToSchema :: SchemaOptions -> proxy f -> Schema -> (AllNullary, Schema)
- gsumConToSchema :: forall c f proxy. Constructor c => Bool -> Referenced Schema -> SchemaOptions -> proxy (C1 c f) -> Schema -> (AllNullary, Schema)
- data Proxy2 a b = Proxy2
- data Proxy3 a b c = Proxy3
Documentation
type NamedSchema = (Maybe String, Schema) Source
A with an optional name.
This name can be used in references.Schema
unnamed :: Schema -> NamedSchema Source
named :: String -> Schema -> NamedSchema 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 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
schemaName :: ToSchema a => proxy a -> Maybe String Source
Get type's schema name according to its instance.ToSchema
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
Methods
gtoNamedSchema :: SchemaOptions -> proxy f -> Schema -> NamedSchema 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. |
timeNamedSchema :: String -> String -> NamedSchema Source
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 }
toSchemaBoundedIntegral :: forall a proxy. (Bounded a, Integral a) => proxy a -> Schema Source
genericToNamedSchemaBoundedIntegral :: forall a d f proxy. (Bounded a, Integral a, Generic a, Rep a ~ D1 d f, Datatype d) => SchemaOptions -> proxy a -> NamedSchema Source
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
gdatatypeSchemaName :: forall proxy d. Datatype d => SchemaOptions -> proxy d -> Maybe String Source
gtoSchemaRef :: GToSchema f => SchemaOptions -> proxy f -> Referenced Schema Source
appendItem :: Referenced Schema -> Maybe SchemaItems -> Maybe SchemaItems Source
withFieldSchema :: forall proxy s f. (Selector s, GToSchema f) => SchemaOptions -> proxy s f -> Bool -> Schema -> Schema Source
type AllNullary = All Source
class GSumToSchema f where Source
Methods
gsumToSchema :: SchemaOptions -> proxy f -> Schema -> (AllNullary, Schema) 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