Safe Haskell | None |
---|---|
Language | Haskell2010 |
- binaryParamSchema :: ParamSchema t
- byteParamSchema :: ParamSchema t
- passwordParamSchema :: ParamSchema t
- class ToParamSchema a where
- toParamSchemaBoundedIntegral :: forall proxy a t. (Bounded a, Integral a) => proxy a -> ParamSchema t
- timeParamSchema :: String -> ParamSchema t
- type family ToParamSchemaByteStringError bs where ...
- genericToParamSchema :: forall proxy a t. (Generic a, GToParamSchema (Rep a)) => SchemaOptions -> proxy a -> ParamSchema t
- class GToParamSchema f where
- class GEnumParamSchema f where
- data Proxy3 a b c = Proxy3
Documentation
binaryParamSchema :: ParamSchema t Source #
Default schema for binary data (any sequence of octets).
byteParamSchema :: ParamSchema t Source #
Default schema for binary data (base64 encoded).
passwordParamSchema :: ParamSchema t Source #
Default schema for password string.
"password"
format is used to hint UIs the input needs to be obscured.
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 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
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\"}"
toParamSchemaBoundedIntegral :: forall proxy a t. (Bounded a, Integral a) => proxy a -> ParamSchema t Source #
timeParamSchema :: String -> ParamSchema t Source #
type family ToParamSchemaByteStringError bs where ... Source #
ToParamSchemaByteStringError bs = TypeError ((((Text "Impossible to have an instance " :<>: ShowType (ToParamSchema bs)) :<>: Text ".") :$$: ((Text "Please, use a newtype wrapper around " :<>: ShowType bs) :<>: Text " instead.")) :$$: Text "Consider using byteParamSchema or binaryParamSchema templates.") |
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\"]}"
class GToParamSchema f where Source #
gtoParamSchema :: SchemaOptions -> proxy f -> ParamSchema t -> ParamSchema t Source #
ToParamSchema c => GToParamSchema (K1 i c) Source # | |
(GEnumParamSchema f, GEnumParamSchema g) => GToParamSchema ((:+:) f g) Source # | |
GToParamSchema f => GToParamSchema (D1 d f) Source # | |
GToParamSchema f => GToParamSchema (C1 c (S1 s f)) Source # | |
Constructor Meta c => GToParamSchema (C1 c U1) Source # | |
class GEnumParamSchema f where Source #
genumParamSchema :: SchemaOptions -> proxy f -> ParamSchema t -> ParamSchema t Source #
(GEnumParamSchema f, GEnumParamSchema g) => GEnumParamSchema ((:+:) f g) Source # | |
Constructor Meta c => GEnumParamSchema (C1 c U1) Source # | |