| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Data.Swagger.Internal.ParamSchema
Synopsis
- binaryParamSchema :: ParamSchema t
- byteParamSchema :: ParamSchema t
- passwordParamSchema :: ParamSchema t
- class ToParamSchema a where- toParamSchema :: Proxy a -> ParamSchema t
 
- toParamSchemaBoundedIntegral :: forall a t. (Bounded a, Integral a) => Proxy a -> ParamSchema t
- timeParamSchema :: String -> ParamSchema t
- type family ToParamSchemaByteStringError bs where ...
- genericToParamSchema :: forall a t. (Generic a, GToParamSchema (Rep a)) => SchemaOptions -> Proxy a -> ParamSchema t
- class GToParamSchema (f :: * -> *) where- gtoParamSchema :: SchemaOptions -> Proxy f -> ParamSchema t -> ParamSchema t
 
- class GEnumParamSchema (f :: * -> *) where- genumParamSchema :: SchemaOptions -> Proxy f -> ParamSchema t -> ParamSchema t
 
- 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 ToParamSchematoParamSchema
To do that, simply add deriving  clause to your datatype
 and declare a FPFormatToParamSchematoParamSchema
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 :: 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
toParamSchemaBoundedIntegral :: forall a t. (Bounded a, Integral a) => Proxy a -> ParamSchema t Source #
timeParamSchema :: String -> ParamSchema t Source #
type family ToParamSchemaByteStringError bs 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.") | 
genericToParamSchema :: forall a t. (Generic a, GToParamSchema (Rep a)) => SchemaOptions -> Proxy a -> ParamSchema t Source #
A configurable generic 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 #
Methods
gtoParamSchema :: SchemaOptions -> Proxy f -> ParamSchema t -> ParamSchema t Source #
Instances
class GEnumParamSchema (f :: * -> *) where Source #
Methods
genumParamSchema :: 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 :: 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 :: SchemaOptions -> Proxy (C1 c U1) -> ParamSchema t -> ParamSchema t Source # | |
>>>import Data.Aeson (encode)