| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Data.Swagger.Internal.Schema
- unnamed :: Schema -> NamedSchema
- named :: Text -> Schema -> NamedSchema
- plain :: Schema -> Declare (Definitions Schema) NamedSchema
- unname :: NamedSchema -> NamedSchema
- rename :: Maybe Text -> NamedSchema -> NamedSchema
- class ToSchema a where- declareNamedSchema :: proxy a -> Declare (Definitions Schema) NamedSchema
 
- declareSchema :: ToSchema a => proxy a -> Declare (Definitions Schema) Schema
- toNamedSchema :: ToSchema a => proxy a -> NamedSchema
- schemaName :: ToSchema a => proxy a -> Maybe Text
- toSchema :: ToSchema a => proxy a -> Schema
- toSchemaRef :: ToSchema a => proxy a -> Referenced Schema
- declareSchemaRef :: ToSchema a => proxy a -> Declare (Definitions Schema) (Referenced Schema)
- inlineSchemasWhen :: Data s => (Text -> Bool) -> Definitions Schema -> s -> s
- inlineSchemas :: Data s => [Text] -> Definitions Schema -> s -> s
- inlineAllSchemas :: Data s => Definitions Schema -> s -> s
- toInlinedSchema :: ToSchema a => proxy a -> Schema
- inlineNonRecursiveSchemas :: Data s => Definitions Schema -> s -> s
- binarySchema :: Schema
- byteSchema :: Schema
- passwordSchema :: Schema
- sketchSchema :: ToJSON a => a -> Schema
- sketchStrictSchema :: ToJSON a => a -> Schema
- class GToSchema f where- gdeclareNamedSchema :: SchemaOptions -> proxy f -> Schema -> Declare (Definitions Schema) NamedSchema
 
- timeSchema :: Text -> Schema
- 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
- genericDeclareSchema :: (Generic a, GToSchema (Rep a)) => SchemaOptions -> proxy a -> Declare (Definitions Schema) Schema
- genericDeclareNamedSchema :: forall a proxy. (Generic a, GToSchema (Rep a)) => SchemaOptions -> proxy a -> Declare (Definitions Schema) NamedSchema
- gdatatypeSchemaName :: forall proxy d. Datatype d => SchemaOptions -> proxy d -> Maybe Text
- paramSchemaToNamedSchema :: forall a d f proxy. (ToParamSchema a, Generic a, Rep a ~ D1 d f, Datatype d) => SchemaOptions -> proxy a -> NamedSchema
- paramSchemaToSchema :: forall a proxy. ToParamSchema a => proxy a -> Schema
- nullarySchema :: Schema
- gtoNamedSchema :: GToSchema f => SchemaOptions -> proxy f -> NamedSchema
- gdeclareSchema :: GToSchema f => SchemaOptions -> proxy f -> Declare (Definitions Schema) Schema
- gdeclareSchemaRef :: GToSchema a => SchemaOptions -> proxy a -> Declare (Definitions Schema) (Referenced Schema)
- appendItem :: Referenced Schema -> Maybe (SwaggerItems Schema) -> Maybe (SwaggerItems Schema)
- withFieldSchema :: forall proxy s f. (Selector s, GToSchema f) => SchemaOptions -> proxy s f -> Bool -> Schema -> Declare (Definitions Schema) Schema
- gdeclareNamedSumSchema :: GSumToSchema f => SchemaOptions -> proxy f -> Schema -> Declare (Definitions Schema) NamedSchema
- type AllNullary = All
- class GSumToSchema f where- gsumToSchema :: SchemaOptions -> proxy f -> Schema -> WriterT AllNullary (Declare (Definitions Schema)) Schema
 
- gsumConToSchemaWith :: forall c f proxy. (GToSchema (C1 c f), Constructor c) => Referenced Schema -> SchemaOptions -> proxy (C1 c f) -> Schema -> Schema
- gsumConToSchema :: forall c f proxy. (GToSchema (C1 c f), Constructor c) => SchemaOptions -> proxy (C1 c f) -> Schema -> Declare (Definitions Schema) Schema
- data Proxy2 a b = Proxy2
- data Proxy3 a b c = Proxy3
Documentation
unnamed :: Schema -> NamedSchema Source
named :: Text -> Schema -> NamedSchema Source
plain :: Schema -> Declare (Definitions Schema) NamedSchema Source
unname :: NamedSchema -> NamedSchema Source
rename :: Maybe Text -> NamedSchema -> 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 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
       & type_ .~ SwaggerObject
       & properties .~
           [ ("x", toSchemaRef (Proxy :: Proxy Double))
           , ("y", toSchemaRef (Proxy :: Proxy Double))
           ]
       & 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).
Instances
declareSchema :: ToSchema a => proxy a -> Declare (Definitions Schema) 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.
>>>toNamedSchema (Proxy :: Proxy String) ^. nameNothing>>>encode (toNamedSchema (Proxy :: Proxy String) ^. schema)"{\"type\":\"string\"}"
>>>toNamedSchema (Proxy :: Proxy Day) ^. nameJust "Day">>>encode (toNamedSchema (Proxy :: Proxy Day) ^. schema)"{\"format\":\"date\",\"type\":\"string\"}"
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"
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 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
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
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
inlineAllSchemas :: Data s => Definitions Schema -> s -> s Source
Inline all schema references for which the definition
 can be found in Definitions
WARNING: inlineAllSchemas
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
inlineNonRecursiveSchemas :: Data s => Definitions Schema -> s -> s Source
Inline all non-recursive schemas for which the definition
 can be found in Definitions
Default schema for binary data (any sequence of octets).
Default schema for binary data (base64 encoded).
passwordSchema :: Schema Source
Default schema for password string.
 "password" format is used to hint UIs the input needs to be obscured.
sketchSchema :: ToJSON a => a -> Schema Source
Make an unrestrictive sketch of a SchemaToJSON
>>>encode $ sketchSchema "hello""{\"example\":\"hello\",\"type\":\"string\"}"
>>>encode $ sketchSchema (1, 2, 3)"{\"example\":[1,2,3],\"items\":{\"type\":\"number\"},\"type\":\"array\"}"
>>>encode $ 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>>>encode $ sketchSchema (Person "Jack" 25)"{\"example\":{\"age\":25,\"name\":\"Jack\"},\"required\":[\"age\",\"name\"],\"type\":\"object\",\"properties\":{\"age\":{\"type\":\"number\"},\"name\":{\"type\":\"string\"}}}"
sketchStrictSchema :: ToJSON a => a -> Schema Source
Make a restrictive sketch of a SchemaToJSON
>>>encode $ sketchStrictSchema "hello""{\"maxLength\":5,\"pattern\":\"hello\",\"minLength\":5,\"type\":\"string\",\"enum\":[\"hello\"]}"
>>>encode $ sketchStrictSchema (1, 2, 3)"{\"minItems\":3,\"uniqueItems\":true,\"items\":[{\"maximum\":1,\"minimum\":1,\"multipleOf\":1,\"type\":\"number\",\"enum\":[1]},{\"maximum\":2,\"minimum\":2,\"multipleOf\":2,\"type\":\"number\",\"enum\":[2]},{\"maximum\":3,\"minimum\":3,\"multipleOf\":3,\"type\":\"number\",\"enum\":[3]}],\"maxItems\":3,\"type\":\"array\",\"enum\":[[1,2,3]]}"
>>>encode $ sketchStrictSchema ("Jack", 25)"{\"minItems\":2,\"uniqueItems\":true,\"items\":[{\"maxLength\":4,\"pattern\":\"Jack\",\"minLength\":4,\"type\":\"string\",\"enum\":[\"Jack\"]},{\"maximum\":25,\"minimum\":25,\"multipleOf\":25,\"type\":\"number\",\"enum\":[25]}],\"maxItems\":2,\"type\":\"array\",\"enum\":[[\"Jack\",25]]}"
>>>data Person = Person { name :: String, age :: Int } deriving (Generic)>>>instance ToJSON Person>>>encode $ sketchStrictSchema (Person "Jack" 25)"{\"minProperties\":2,\"required\":[\"age\",\"name\"],\"maxProperties\":2,\"type\":\"object\",\"enum\":[{\"age\":25,\"name\":\"Jack\"}],\"properties\":{\"age\":{\"maximum\":25,\"minimum\":25,\"multipleOf\":25,\"type\":\"number\",\"enum\":[25]},\"name\":{\"maxLength\":4,\"pattern\":\"Jack\",\"minLength\":4,\"type\":\"string\",\"enum\":[\"Jack\"]}}}"
class GToSchema f where Source
Methods
gdeclareNamedSchema :: SchemaOptions -> proxy f -> Schema -> Declare (Definitions Schema) NamedSchema Source
Instances
| 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. | 
| Constructor c => GToSchema (C1 c U1) Source | |
| 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. | 
timeSchema :: Text -> Schema Source
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
genericDeclareSchema :: (Generic a, GToSchema (Rep a)) => SchemaOptions -> proxy a -> Declare (Definitions Schema) Schema Source
A configurable generic Schema
genericDeclareNamedSchema :: forall a proxy. (Generic a, GToSchema (Rep a)) => SchemaOptions -> proxy a -> Declare (Definitions Schema) NamedSchema Source
A configurable generic NamedSchemadefaultSchemaOptionsdeclareNamedSchemaGeneric
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 ParamSchemaNamedSchema
paramSchemaToSchema :: forall a proxy. ToParamSchema a => proxy a -> Schema Source
Lift a plain ParamSchemaSchema
gtoNamedSchema :: GToSchema f => SchemaOptions -> proxy f -> NamedSchema Source
gdeclareSchema :: GToSchema f => SchemaOptions -> proxy f -> Declare (Definitions Schema) Schema Source
gdeclareSchemaRef :: GToSchema a => SchemaOptions -> proxy a -> Declare (Definitions Schema) (Referenced Schema) Source
appendItem :: Referenced Schema -> Maybe (SwaggerItems Schema) -> Maybe (SwaggerItems Schema) Source
withFieldSchema :: forall proxy s f. (Selector s, GToSchema f) => SchemaOptions -> proxy s f -> Bool -> Schema -> Declare (Definitions Schema) Schema Source
gdeclareNamedSumSchema :: GSumToSchema f => SchemaOptions -> proxy f -> Schema -> Declare (Definitions Schema) NamedSchema Source
type AllNullary = All Source
class GSumToSchema f where Source
Methods
gsumToSchema :: SchemaOptions -> proxy f -> Schema -> WriterT AllNullary (Declare (Definitions Schema)) Schema 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 | 
gsumConToSchemaWith :: forall c f proxy. (GToSchema (C1 c f), Constructor c) => Referenced Schema -> SchemaOptions -> proxy (C1 c f) -> Schema -> Schema Source
gsumConToSchema :: forall c f proxy. (GToSchema (C1 c f), Constructor c) => SchemaOptions -> proxy (C1 c f) -> Schema -> Declare (Definitions Schema) Schema Source