Safe Haskell | None |
---|---|
Language | Haskell2010 |
Data.Swagger.Internal.ParamSchema
Synopsis
- binaryParamSchema :: forall (t :: SwaggerKind Type). ParamSchema t
- byteParamSchema :: forall (t :: SwaggerKind Type). ParamSchema t
- passwordParamSchema :: forall (t :: SwaggerKind Type). ParamSchema t
- class ToParamSchema a where
- toParamSchema :: forall (t :: SwaggerKind Type). Proxy a -> ParamSchema t
- toParamSchemaBoundedIntegral :: forall a (t :: SwaggerKind Type). (Bounded a, Integral a) => Proxy a -> ParamSchema t
- timeParamSchema :: forall (t :: SwaggerKind Type). String -> ParamSchema t
- type family ToParamSchemaByteStringError bs :: k where ...
- genericToParamSchema :: forall a (t :: SwaggerKind Type). (Generic a, GToParamSchema (Rep a)) => SchemaOptions -> Proxy a -> ParamSchema t
- class GToParamSchema (f :: Type -> Type) where
- gtoParamSchema :: forall (t :: SwaggerKind Type). SchemaOptions -> Proxy f -> ParamSchema t -> ParamSchema t
- class GEnumParamSchema (f :: Type -> Type) where
- genumParamSchema :: forall (t :: SwaggerKind Type). SchemaOptions -> Proxy f -> ParamSchema t -> ParamSchema t
- data Proxy3 (a :: k) (b :: k1) (c :: k2) = Proxy3
Documentation
binaryParamSchema :: forall (t :: SwaggerKind Type). ParamSchema t Source #
Default schema for binary data (any sequence of octets).
byteParamSchema :: forall (t :: SwaggerKind Type). ParamSchema t Source #
Default schema for binary data (base64 encoded).
passwordParamSchema :: forall (t :: SwaggerKind Type). 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
Minimal complete definition
Nothing
Methods
toParamSchema :: forall (t :: SwaggerKind Type). Proxy a -> ParamSchema t Source #
Convert a type into a plain parameter schema.
>>>
encode $ toParamSchema (Proxy :: Proxy Integer)
"{\"type\":\"integer\"}"
default toParamSchema :: forall (t :: SwaggerKind Type). (Generic a, GToParamSchema (Rep a)) => Proxy a -> ParamSchema t Source #
Instances
toParamSchemaBoundedIntegral :: forall a (t :: SwaggerKind Type). (Bounded a, Integral a) => Proxy a -> ParamSchema t Source #
timeParamSchema :: forall (t :: SwaggerKind Type). String -> ParamSchema t Source #
type family ToParamSchemaByteStringError bs :: k where ... Source #
Equations
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.") :: k |
genericToParamSchema :: forall a (t :: SwaggerKind Type). (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)
"{\"enum\":[\"Red\",\"Blue\"],\"type\":\"string\"}"
class GToParamSchema (f :: Type -> Type) where Source #
Methods
gtoParamSchema :: forall (t :: SwaggerKind Type). SchemaOptions -> Proxy f -> ParamSchema t -> ParamSchema t Source #
Instances
class GEnumParamSchema (f :: Type -> Type) where Source #
Methods
genumParamSchema :: forall (t :: SwaggerKind Type). SchemaOptions -> Proxy f -> ParamSchema t -> ParamSchema t Source #
Instances
(GEnumParamSchema f, GEnumParamSchema g) => GEnumParamSchema (f :+: g) Source # | |
Defined in Data.Swagger.Internal.ParamSchema Methods genumParamSchema :: forall (t :: SwaggerKind Type). SchemaOptions -> Proxy (f :+: g) -> ParamSchema t -> ParamSchema t Source # | |
Constructor c => GEnumParamSchema (C1 c (U1 :: Type -> Type)) Source # | |
Defined in Data.Swagger.Internal.ParamSchema Methods genumParamSchema :: forall (t :: SwaggerKind Type). SchemaOptions -> Proxy (C1 c (U1 :: Type -> Type)) -> ParamSchema t -> ParamSchema t Source # |
>>>
import Data.Aeson (encode)