Maintainer | Nickolay Kudasov <nickolay@getshoptv.com> |
---|---|
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Types and functions for working with Swagger parameter schema.
Synopsis
- class ToParamSchema a where
- toParamSchema :: Proxy a -> Schema
- genericToParamSchema :: forall a t. (Generic a, GToParamSchema (Rep a)) => SchemaOptions -> Proxy a -> Schema
- toParamSchemaBoundedIntegral :: forall a t. (Bounded a, Integral a) => Proxy a -> Schema
- passwordSchema :: Schema
- binarySchema :: Schema
- byteSchema :: Schema
- data SchemaOptions = SchemaOptions {}
- defaultSchemaOptions :: SchemaOptions
Encoding
class ToParamSchema a where Source #
Convert a type into a plain
.Schema
In previous versions of the package there was a separate type called ParamSchema
, which was
included in a greater Schema
. Now this is a single class, but distinction for schema generators
for "simple" types is preserved.
ToParamSchema
is suited only for primitive-like types without nested fields and such.
An example type and instance:
{-# LANGUAGE OverloadedStrings #-} -- allows to write Text
literals
import Control.Lens
data Direction = Up | Down
instance ToParamSchema Direction where
toParamSchema _ = mempty
& type_ ?~ OpenApiString
& enum_ ?~ [ "Up", "Down" ]
Instead of manually writing your
instance you can
use a default generic implementation of ToParamSchema
.toParamSchema
To do that, simply add deriving
clause to your datatype
and declare a Generic
instance for your datatype without
giving definition for ToParamSchema
.toParamSchema
For instance, the previous example can be simplified into this:
{-# LANGUAGE DeriveGeneric #-} import GHC.Generics (Generic) data Direction = Up | Down deriving Generic instance ToParamSchema Direction
Nothing
toParamSchema :: Proxy a -> Schema Source #
Convert a type into a plain parameter schema.
>>>
BSL.putStrLn $ encodePretty $ toParamSchema (Proxy :: Proxy Integer)
{ "type": "integer" }
default toParamSchema :: (Generic a, GToParamSchema (Rep a)) => Proxy a -> Schema Source #
Instances
Generic schema encoding
genericToParamSchema :: forall a t. (Generic a, GToParamSchema (Rep a)) => SchemaOptions -> Proxy a -> Schema Source #
A configurable generic
creator.Schema
>>>
:set -XDeriveGeneric
>>>
data Color = Red | Blue deriving Generic
>>>
BSL.putStrLn $ encodePretty $ genericToParamSchema defaultSchemaOptions (Proxy :: Proxy Color)
{ "enum": [ "Red", "Blue" ], "type": "string" }
Schema templates
passwordSchema :: Schema Source #
Default schema for password string.
"password"
format is used to hint UIs the input needs to be obscured.
binarySchema :: Schema Source #
Default schema for binary data (any sequence of octets).
byteSchema :: Schema Source #
Default schema for binary data (base64 encoded).
Generic encoding configuration
data SchemaOptions Source #
Options that specify how to encode your type to Swagger schema.
SchemaOptions | |
|
defaultSchemaOptions :: SchemaOptions Source #
Default encoding
.SchemaOptions
SchemaOptions
{fieldLabelModifier
= id ,constructorTagModifier
= id ,datatypeNameModifier
= id ,allNullaryToStringTag
= True ,unwrapUnaryRecords
= False ,sumEncoding
=defaultTaggedObject
}