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 -> ParamSchema t
- genericToParamSchema :: forall proxy a t. (Generic a, GToParamSchema (Rep a)) => SchemaOptions -> proxy a -> ParamSchema t
- toParamSchemaBoundedIntegral :: forall proxy a t. (Bounded a, Integral a) => proxy a -> ParamSchema t
- passwordParamSchema :: ParamSchema t
- binaryParamSchema :: ParamSchema t
- byteParamSchema :: ParamSchema t
- data SchemaOptions = SchemaOptions {}
- defaultSchemaOptions :: SchemaOptions
Encoding
class ToParamSchema a where Source #
Convert a type into a plain
.ParamSchema
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_ .~ SwaggerString
& 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 FPFormat
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 -> ParamSchema t Source #
Convert a type into a plain parameter schema.
>>>
encode $ toParamSchema (Proxy :: Proxy Integer)
"{\"type\":\"integer\"}"
toParamSchema :: (Generic a, GToParamSchema (Rep a)) => proxy a -> ParamSchema t Source #
Convert a type into a plain parameter schema.
>>>
encode $ toParamSchema (Proxy :: Proxy Integer)
"{\"type\":\"integer\"}"
Instances
Generic schema encoding
genericToParamSchema :: forall proxy a t. (Generic a, GToParamSchema (Rep a)) => SchemaOptions -> proxy a -> ParamSchema t Source #
A configurable generic
creator.ParamSchema
>>>
:set -XDeriveGeneric
>>>
data Color = Red | Blue deriving Generic
>>>
encode $ genericToParamSchema defaultSchemaOptions (Proxy :: Proxy Color)
"{\"type\":\"string\",\"enum\":[\"Red\",\"Blue\"]}"
toParamSchemaBoundedIntegral :: forall proxy a t. (Bounded a, Integral a) => proxy a -> ParamSchema t Source #
Schema templates
passwordParamSchema :: ParamSchema t Source #
Default schema for password string.
"password"
format is used to hint UIs the input needs to be obscured.
binaryParamSchema :: ParamSchema t Source #
Default schema for binary data (any sequence of octets).
byteParamSchema :: ParamSchema t 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 }