{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PackageImports #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-redundant-constraints #-}
{-# OPTIONS_GHC -Wno-unticked-promoted-constructors #-}
module Data.OpenApi.Internal.ParamSchema where
import Control.Lens
import Data.Aeson (ToJSON (..))
import Data.Proxy
import GHC.Generics
import Data.Int
import "unordered-containers" Data.HashSet (HashSet)
import Data.Monoid
import Data.Set (Set)
import Data.Scientific
import Data.Fixed (HasResolution(..), Fixed, Pico)
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import Data.Time
import qualified Data.Vector as V
import qualified Data.Vector.Primitive as VP
import qualified Data.Vector.Storable as VS
import qualified Data.Vector.Unboxed as VU
import Data.Version (Version)
import Numeric.Natural.Compat (Natural)
import Data.Word
import Data.UUID.Types (UUID)
import Web.Cookie (SetCookie)
import Data.OpenApi.Internal
import Data.OpenApi.Lens
import Data.OpenApi.SchemaOptions
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy.Char8 as BSL
import GHC.TypeLits (TypeError, ErrorMessage(..))
binarySchema :: Schema
binarySchema :: Schema
binarySchema = forall a. Monoid a => a
mempty
forall a b. a -> (a -> b) -> b
& forall s a. HasType s a => Lens' s a
type_ forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ OpenApiType
OpenApiString
forall a b. a -> (a -> b) -> b
& forall s a. HasFormat s a => Lens' s a
format forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Text
"binary"
byteSchema :: Schema
byteSchema :: Schema
byteSchema = forall a. Monoid a => a
mempty
forall a b. a -> (a -> b) -> b
& forall s a. HasType s a => Lens' s a
type_ forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ OpenApiType
OpenApiString
forall a b. a -> (a -> b) -> b
& forall s a. HasFormat s a => Lens' s a
format forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Text
"byte"
passwordSchema :: Schema
passwordSchema :: Schema
passwordSchema = forall a. Monoid a => a
mempty
forall a b. a -> (a -> b) -> b
& forall s a. HasType s a => Lens' s a
type_ forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ OpenApiType
OpenApiString
forall a b. a -> (a -> b) -> b
& forall s a. HasFormat s a => Lens' s a
format forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Text
"password"
class ToParamSchema a where
toParamSchema :: Proxy a -> Schema
default toParamSchema :: (Generic a, GToParamSchema (Rep a)) => Proxy a -> Schema
toParamSchema = forall {k} a (t :: k).
(Generic a, GToParamSchema (Rep a)) =>
SchemaOptions -> Proxy a -> Schema
genericToParamSchema SchemaOptions
defaultSchemaOptions
instance {-# OVERLAPPING #-} ToParamSchema String where
toParamSchema :: Proxy String -> Schema
toParamSchema Proxy String
_ = forall a. Monoid a => a
mempty forall a b. a -> (a -> b) -> b
& forall s a. HasType s a => Lens' s a
type_ forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ OpenApiType
OpenApiString
instance ToParamSchema Bool where
toParamSchema :: Proxy Bool -> Schema
toParamSchema Proxy Bool
_ = forall a. Monoid a => a
mempty forall a b. a -> (a -> b) -> b
& forall s a. HasType s a => Lens' s a
type_ forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ OpenApiType
OpenApiBoolean
instance ToParamSchema Integer where
toParamSchema :: Proxy Integer -> Schema
toParamSchema Proxy Integer
_ = forall a. Monoid a => a
mempty forall a b. a -> (a -> b) -> b
& forall s a. HasType s a => Lens' s a
type_ forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ OpenApiType
OpenApiInteger
instance ToParamSchema Natural where
toParamSchema :: Proxy Natural -> Schema
toParamSchema Proxy Natural
_ = forall a. Monoid a => a
mempty
forall a b. a -> (a -> b) -> b
& forall s a. HasType s a => Lens' s a
type_ forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ OpenApiType
OpenApiInteger
forall a b. a -> (a -> b) -> b
& forall s a. HasMinimum s a => Lens' s a
minimum_ forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Scientific
0
forall a b. a -> (a -> b) -> b
& forall s a. HasExclusiveMinimum s a => Lens' s a
exclusiveMinimum forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Bool
False
instance ToParamSchema Int where toParamSchema :: Proxy Int -> Schema
toParamSchema = forall {k} a (t :: k). (Bounded a, Integral a) => Proxy a -> Schema
toParamSchemaBoundedIntegral
instance ToParamSchema Int8 where toParamSchema :: Proxy Int8 -> Schema
toParamSchema = forall {k} a (t :: k). (Bounded a, Integral a) => Proxy a -> Schema
toParamSchemaBoundedIntegral
instance ToParamSchema Int16 where toParamSchema :: Proxy Int16 -> Schema
toParamSchema = forall {k} a (t :: k). (Bounded a, Integral a) => Proxy a -> Schema
toParamSchemaBoundedIntegral
instance ToParamSchema Int32 where
toParamSchema :: Proxy Int32 -> Schema
toParamSchema Proxy Int32
proxy = forall {k} a (t :: k). (Bounded a, Integral a) => Proxy a -> Schema
toParamSchemaBoundedIntegral Proxy Int32
proxy forall a b. a -> (a -> b) -> b
& forall s a. HasFormat s a => Lens' s a
format forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Text
"int32"
instance ToParamSchema Int64 where
toParamSchema :: Proxy Int64 -> Schema
toParamSchema Proxy Int64
proxy = forall {k} a (t :: k). (Bounded a, Integral a) => Proxy a -> Schema
toParamSchemaBoundedIntegral Proxy Int64
proxy forall a b. a -> (a -> b) -> b
& forall s a. HasFormat s a => Lens' s a
format forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Text
"int64"
instance ToParamSchema Word where toParamSchema :: Proxy Word -> Schema
toParamSchema = forall {k} a (t :: k). (Bounded a, Integral a) => Proxy a -> Schema
toParamSchemaBoundedIntegral
instance ToParamSchema Word8 where toParamSchema :: Proxy Word8 -> Schema
toParamSchema = forall {k} a (t :: k). (Bounded a, Integral a) => Proxy a -> Schema
toParamSchemaBoundedIntegral
instance ToParamSchema Word16 where toParamSchema :: Proxy Word16 -> Schema
toParamSchema = forall {k} a (t :: k). (Bounded a, Integral a) => Proxy a -> Schema
toParamSchemaBoundedIntegral
instance ToParamSchema Word32 where
toParamSchema :: Proxy Word32 -> Schema
toParamSchema Proxy Word32
proxy = forall {k} a (t :: k). (Bounded a, Integral a) => Proxy a -> Schema
toParamSchemaBoundedIntegral Proxy Word32
proxy forall a b. a -> (a -> b) -> b
& forall s a. HasFormat s a => Lens' s a
format forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Text
"int32"
instance ToParamSchema Word64 where
toParamSchema :: Proxy Word64 -> Schema
toParamSchema Proxy Word64
proxy = forall {k} a (t :: k). (Bounded a, Integral a) => Proxy a -> Schema
toParamSchemaBoundedIntegral Proxy Word64
proxy forall a b. a -> (a -> b) -> b
& forall s a. HasFormat s a => Lens' s a
format forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Text
"int64"
toParamSchemaBoundedIntegral :: forall a t. (Bounded a, Integral a) => Proxy a -> Schema
toParamSchemaBoundedIntegral :: forall {k} a (t :: k). (Bounded a, Integral a) => Proxy a -> Schema
toParamSchemaBoundedIntegral Proxy a
_ = forall a. Monoid a => a
mempty
forall a b. a -> (a -> b) -> b
& forall s a. HasType s a => Lens' s a
type_ forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ OpenApiType
OpenApiInteger
forall a b. a -> (a -> b) -> b
& forall s a. HasMinimum s a => Lens' s a
minimum_ forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ forall a. Num a => Integer -> a
fromInteger (forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
minBound :: a))
forall a b. a -> (a -> b) -> b
& forall s a. HasMaximum s a => Lens' s a
maximum_ forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ forall a. Num a => Integer -> a
fromInteger (forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
maxBound :: a))
instance ToParamSchema Char where
toParamSchema :: Proxy Char -> Schema
toParamSchema Proxy Char
_ = forall a. Monoid a => a
mempty
forall a b. a -> (a -> b) -> b
& forall s a. HasType s a => Lens' s a
type_ forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ OpenApiType
OpenApiString
forall a b. a -> (a -> b) -> b
& forall s a. HasMaxLength s a => Lens' s a
maxLength forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Integer
1
forall a b. a -> (a -> b) -> b
& forall s a. HasMinLength s a => Lens' s a
minLength forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Integer
1
instance ToParamSchema Scientific where
toParamSchema :: Proxy Scientific -> Schema
toParamSchema Proxy Scientific
_ = forall a. Monoid a => a
mempty forall a b. a -> (a -> b) -> b
& forall s a. HasType s a => Lens' s a
type_ forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ OpenApiType
OpenApiNumber
instance HasResolution a => ToParamSchema (Fixed a) where
toParamSchema :: Proxy (Fixed a) -> Schema
toParamSchema Proxy (Fixed a)
_ = forall a. Monoid a => a
mempty
forall a b. a -> (a -> b) -> b
& forall s a. HasType s a => Lens' s a
type_ forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ OpenApiType
OpenApiNumber
forall a b. a -> (a -> b) -> b
& forall s a. HasMultipleOf s a => Lens' s a
multipleOf forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ (forall a. Fractional a => a -> a
recip forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Num a => Integer -> a
fromInteger forall a b. (a -> b) -> a -> b
$ forall k (a :: k) (p :: k -> *). HasResolution a => p a -> Integer
resolution (forall {k} (t :: k). Proxy t
Proxy :: Proxy a))
instance ToParamSchema Double where
toParamSchema :: Proxy Double -> Schema
toParamSchema Proxy Double
_ = forall a. Monoid a => a
mempty
forall a b. a -> (a -> b) -> b
& forall s a. HasType s a => Lens' s a
type_ forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ OpenApiType
OpenApiNumber
forall a b. a -> (a -> b) -> b
& forall s a. HasFormat s a => Lens' s a
format forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Text
"double"
instance ToParamSchema Float where
toParamSchema :: Proxy Float -> Schema
toParamSchema Proxy Float
_ = forall a. Monoid a => a
mempty
forall a b. a -> (a -> b) -> b
& forall s a. HasType s a => Lens' s a
type_ forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ OpenApiType
OpenApiNumber
forall a b. a -> (a -> b) -> b
& forall s a. HasFormat s a => Lens' s a
format forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Text
"float"
timeParamSchema :: String -> Schema
timeParamSchema :: String -> Schema
timeParamSchema String
fmt = forall a. Monoid a => a
mempty
forall a b. a -> (a -> b) -> b
& forall s a. HasType s a => Lens' s a
type_ forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ OpenApiType
OpenApiString
forall a b. a -> (a -> b) -> b
& forall s a. HasFormat s a => Lens' s a
format forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ String -> Text
T.pack String
fmt
instance ToParamSchema Day where
toParamSchema :: Proxy Day -> Schema
toParamSchema Proxy Day
_ = String -> Schema
timeParamSchema String
"date"
instance ToParamSchema TimeOfDay where
toParamSchema :: Proxy TimeOfDay -> Schema
toParamSchema Proxy TimeOfDay
_ = String -> Schema
timeParamSchema String
"hh:MM:ss"
instance ToParamSchema LocalTime where
toParamSchema :: Proxy LocalTime -> Schema
toParamSchema Proxy LocalTime
_ = String -> Schema
timeParamSchema String
"yyyy-mm-ddThh:MM:ss"
instance ToParamSchema ZonedTime where
toParamSchema :: Proxy ZonedTime -> Schema
toParamSchema Proxy ZonedTime
_ = String -> Schema
timeParamSchema String
"date-time"
instance ToParamSchema UTCTime where
toParamSchema :: Proxy UTCTime -> Schema
toParamSchema Proxy UTCTime
_ = String -> Schema
timeParamSchema String
"yyyy-mm-ddThh:MM:ssZ"
instance ToParamSchema NominalDiffTime where
toParamSchema :: Proxy NominalDiffTime -> Schema
toParamSchema Proxy NominalDiffTime
_ = forall a. ToParamSchema a => Proxy a -> Schema
toParamSchema (forall {k} (t :: k). Proxy t
Proxy :: Proxy Pico)
instance ToParamSchema T.Text where
toParamSchema :: Proxy Text -> Schema
toParamSchema Proxy Text
_ = forall a. ToParamSchema a => Proxy a -> Schema
toParamSchema (forall {k} (t :: k). Proxy t
Proxy :: Proxy String)
instance ToParamSchema TL.Text where
toParamSchema :: Proxy Text -> Schema
toParamSchema Proxy Text
_ = forall a. ToParamSchema a => Proxy a -> Schema
toParamSchema (forall {k} (t :: k). Proxy t
Proxy :: Proxy String)
instance ToParamSchema Version where
toParamSchema :: Proxy Version -> Schema
toParamSchema Proxy Version
_ = forall a. Monoid a => a
mempty
forall a b. a -> (a -> b) -> b
& forall s a. HasType s a => Lens' s a
type_ forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ OpenApiType
OpenApiString
forall a b. a -> (a -> b) -> b
& forall s a. HasPattern s a => Lens' s a
pattern forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Text
"^\\d+(\\.\\d+)*$"
instance ToParamSchema SetCookie where
toParamSchema :: Proxy SetCookie -> Schema
toParamSchema Proxy SetCookie
_ = forall a. Monoid a => a
mempty
forall a b. a -> (a -> b) -> b
& forall s a. HasType s a => Lens' s a
type_ forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ OpenApiType
OpenApiString
type family ToParamSchemaByteStringError bs where
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 binaryParamSchemaemplates." )
instance ToParamSchemaByteStringError BS.ByteString => ToParamSchema BS.ByteString where toParamSchema :: Proxy ByteString -> Schema
toParamSchema = forall a. HasCallStack => String -> a
error String
"impossible"
instance ToParamSchemaByteStringError BSL.ByteString => ToParamSchema BSL.ByteString where toParamSchema :: Proxy ByteString -> Schema
toParamSchema = forall a. HasCallStack => String -> a
error String
"impossible"
instance ToParamSchema All where toParamSchema :: Proxy All -> Schema
toParamSchema Proxy All
_ = forall a. ToParamSchema a => Proxy a -> Schema
toParamSchema (forall {k} (t :: k). Proxy t
Proxy :: Proxy Bool)
instance ToParamSchema Any where toParamSchema :: Proxy Any -> Schema
toParamSchema Proxy Any
_ = forall a. ToParamSchema a => Proxy a -> Schema
toParamSchema (forall {k} (t :: k). Proxy t
Proxy :: Proxy Bool)
instance ToParamSchema a => ToParamSchema (Sum a) where toParamSchema :: Proxy (Sum a) -> Schema
toParamSchema Proxy (Sum a)
_ = forall a. ToParamSchema a => Proxy a -> Schema
toParamSchema (forall {k} (t :: k). Proxy t
Proxy :: Proxy a)
instance ToParamSchema a => ToParamSchema (Product a) where toParamSchema :: Proxy (Product a) -> Schema
toParamSchema Proxy (Product a)
_ = forall a. ToParamSchema a => Proxy a -> Schema
toParamSchema (forall {k} (t :: k). Proxy t
Proxy :: Proxy a)
instance ToParamSchema a => ToParamSchema (First a) where toParamSchema :: Proxy (First a) -> Schema
toParamSchema Proxy (First a)
_ = forall a. ToParamSchema a => Proxy a -> Schema
toParamSchema (forall {k} (t :: k). Proxy t
Proxy :: Proxy a)
instance ToParamSchema a => ToParamSchema (Last a) where toParamSchema :: Proxy (Last a) -> Schema
toParamSchema Proxy (Last a)
_ = forall a. ToParamSchema a => Proxy a -> Schema
toParamSchema (forall {k} (t :: k). Proxy t
Proxy :: Proxy a)
instance ToParamSchema a => ToParamSchema (Dual a) where toParamSchema :: Proxy (Dual a) -> Schema
toParamSchema Proxy (Dual a)
_ = forall a. ToParamSchema a => Proxy a -> Schema
toParamSchema (forall {k} (t :: k). Proxy t
Proxy :: Proxy a)
instance ToParamSchema a => ToParamSchema (Identity a) where toParamSchema :: Proxy (Identity a) -> Schema
toParamSchema Proxy (Identity a)
_ = forall a. ToParamSchema a => Proxy a -> Schema
toParamSchema (forall {k} (t :: k). Proxy t
Proxy :: Proxy a)
instance ToParamSchema a => ToParamSchema [a] where
toParamSchema :: Proxy [a] -> Schema
toParamSchema Proxy [a]
_ = forall a. Monoid a => a
mempty
forall a b. a -> (a -> b) -> b
& forall s a. HasType s a => Lens' s a
type_ forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ OpenApiType
OpenApiArray
forall a b. a -> (a -> b) -> b
& forall s a. HasItems s a => Lens' s a
items forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Referenced Schema -> OpenApiItems
OpenApiItemsObject (forall a. a -> Referenced a
Inline forall a b. (a -> b) -> a -> b
$ forall a. ToParamSchema a => Proxy a -> Schema
toParamSchema (forall {k} (t :: k). Proxy t
Proxy :: Proxy a))
instance ToParamSchema a => ToParamSchema (V.Vector a) where toParamSchema :: Proxy (Vector a) -> Schema
toParamSchema Proxy (Vector a)
_ = forall a. ToParamSchema a => Proxy a -> Schema
toParamSchema (forall {k} (t :: k). Proxy t
Proxy :: Proxy [a])
instance ToParamSchema a => ToParamSchema (VP.Vector a) where toParamSchema :: Proxy (Vector a) -> Schema
toParamSchema Proxy (Vector a)
_ = forall a. ToParamSchema a => Proxy a -> Schema
toParamSchema (forall {k} (t :: k). Proxy t
Proxy :: Proxy [a])
instance ToParamSchema a => ToParamSchema (VS.Vector a) where toParamSchema :: Proxy (Vector a) -> Schema
toParamSchema Proxy (Vector a)
_ = forall a. ToParamSchema a => Proxy a -> Schema
toParamSchema (forall {k} (t :: k). Proxy t
Proxy :: Proxy [a])
instance ToParamSchema a => ToParamSchema (VU.Vector a) where toParamSchema :: Proxy (Vector a) -> Schema
toParamSchema Proxy (Vector a)
_ = forall a. ToParamSchema a => Proxy a -> Schema
toParamSchema (forall {k} (t :: k). Proxy t
Proxy :: Proxy [a])
instance ToParamSchema a => ToParamSchema (Set a) where
toParamSchema :: Proxy (Set a) -> Schema
toParamSchema Proxy (Set a)
_ = forall a. ToParamSchema a => Proxy a -> Schema
toParamSchema (forall {k} (t :: k). Proxy t
Proxy :: Proxy [a])
forall a b. a -> (a -> b) -> b
& forall s a. HasUniqueItems s a => Lens' s a
uniqueItems forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Bool
True
instance ToParamSchema a => ToParamSchema (HashSet a) where
toParamSchema :: Proxy (HashSet a) -> Schema
toParamSchema Proxy (HashSet a)
_ = forall a. ToParamSchema a => Proxy a -> Schema
toParamSchema (forall {k} (t :: k). Proxy t
Proxy :: Proxy (Set a))
instance ToParamSchema () where
toParamSchema :: Proxy () -> Schema
toParamSchema Proxy ()
_ = forall a. Monoid a => a
mempty
forall a b. a -> (a -> b) -> b
& forall s a. HasType s a => Lens' s a
type_ forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ OpenApiType
OpenApiString
forall a b. a -> (a -> b) -> b
& forall s a. HasEnum s a => Lens' s a
enum_ forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ [Value
"_"]
instance ToParamSchema UUID where
toParamSchema :: Proxy UUID -> Schema
toParamSchema Proxy UUID
_ = forall a. Monoid a => a
mempty
forall a b. a -> (a -> b) -> b
& forall s a. HasType s a => Lens' s a
type_ forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ OpenApiType
OpenApiString
forall a b. a -> (a -> b) -> b
& forall s a. HasFormat s a => Lens' s a
format forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Text
"uuid"
genericToParamSchema :: forall a t. (Generic a, GToParamSchema (Rep a)) => SchemaOptions -> Proxy a -> Schema
genericToParamSchema :: forall {k} a (t :: k).
(Generic a, GToParamSchema (Rep a)) =>
SchemaOptions -> Proxy a -> Schema
genericToParamSchema SchemaOptions
opts Proxy a
_ = forall (f :: * -> *).
GToParamSchema f =>
SchemaOptions -> Proxy f -> Schema -> Schema
gtoParamSchema SchemaOptions
opts (forall {k} (t :: k). Proxy t
Proxy :: Proxy (Rep a)) forall a. Monoid a => a
mempty
class GToParamSchema (f :: * -> *) where
gtoParamSchema :: SchemaOptions -> Proxy f -> Schema -> Schema
instance GToParamSchema f => GToParamSchema (D1 d f) where
gtoParamSchema :: SchemaOptions -> Proxy (D1 d f) -> Schema -> Schema
gtoParamSchema SchemaOptions
opts Proxy (D1 d f)
_ = forall (f :: * -> *).
GToParamSchema f =>
SchemaOptions -> Proxy f -> Schema -> Schema
gtoParamSchema SchemaOptions
opts (forall {k} (t :: k). Proxy t
Proxy :: Proxy f)
instance Constructor c => GToParamSchema (C1 c U1) where
gtoParamSchema :: SchemaOptions -> Proxy (C1 c U1) -> Schema -> Schema
gtoParamSchema = forall (f :: * -> *).
GEnumParamSchema f =>
SchemaOptions -> Proxy f -> Schema -> Schema
genumParamSchema
instance GToParamSchema f => GToParamSchema (C1 c (S1 s f)) where
gtoParamSchema :: SchemaOptions -> Proxy (C1 c (S1 s f)) -> Schema -> Schema
gtoParamSchema SchemaOptions
opts Proxy (C1 c (S1 s f))
_ = forall (f :: * -> *).
GToParamSchema f =>
SchemaOptions -> Proxy f -> Schema -> Schema
gtoParamSchema SchemaOptions
opts (forall {k} (t :: k). Proxy t
Proxy :: Proxy f)
instance ToParamSchema c => GToParamSchema (K1 i c) where
gtoParamSchema :: SchemaOptions -> Proxy (K1 i c) -> Schema -> Schema
gtoParamSchema SchemaOptions
_ Proxy (K1 i c)
_ Schema
_ = forall a. ToParamSchema a => Proxy a -> Schema
toParamSchema (forall {k} (t :: k). Proxy t
Proxy :: Proxy c)
instance (GEnumParamSchema f, GEnumParamSchema g) => GToParamSchema (f :+: g) where
gtoParamSchema :: SchemaOptions -> Proxy (f :+: g) -> Schema -> Schema
gtoParamSchema SchemaOptions
opts Proxy (f :+: g)
_ = forall (f :: * -> *).
GEnumParamSchema f =>
SchemaOptions -> Proxy f -> Schema -> Schema
genumParamSchema SchemaOptions
opts (forall {k} (t :: k). Proxy t
Proxy :: Proxy (f :+: g))
class GEnumParamSchema (f :: * -> *) where
genumParamSchema :: SchemaOptions -> Proxy f -> Schema -> Schema
instance (GEnumParamSchema f, GEnumParamSchema g) => GEnumParamSchema (f :+: g) where
genumParamSchema :: SchemaOptions -> Proxy (f :+: g) -> Schema -> Schema
genumParamSchema SchemaOptions
opts Proxy (f :+: g)
_ = forall (f :: * -> *).
GEnumParamSchema f =>
SchemaOptions -> Proxy f -> Schema -> Schema
genumParamSchema SchemaOptions
opts (forall {k} (t :: k). Proxy t
Proxy :: Proxy f) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *).
GEnumParamSchema f =>
SchemaOptions -> Proxy f -> Schema -> Schema
genumParamSchema SchemaOptions
opts (forall {k} (t :: k). Proxy t
Proxy :: Proxy g)
instance Constructor c => GEnumParamSchema (C1 c U1) where
genumParamSchema :: SchemaOptions -> Proxy (C1 c U1) -> Schema -> Schema
genumParamSchema SchemaOptions
opts Proxy (C1 c U1)
_ Schema
s = Schema
s
forall a b. a -> (a -> b) -> b
& forall s a. HasType s a => Lens' s a
type_ forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ OpenApiType
OpenApiString
forall a b. a -> (a -> b) -> b
& forall s a. HasEnum s a => Lens' s a
enum_ forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ forall {a}. a -> Maybe [a] -> Maybe [a]
addEnumValue Value
tag
where
tag :: Value
tag = forall a. ToJSON a => a -> Value
toJSON (SchemaOptions -> String -> String
constructorTagModifier SchemaOptions
opts (forall {k} (c :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
(f :: k1 -> *) (a :: k1).
Constructor c =>
t c f a -> String
conName (forall {k} {k} {k} (a :: k) (b :: k) (c :: k). Proxy3 a b c
Proxy3 :: Proxy3 c f p)))
addEnumValue :: a -> Maybe [a] -> Maybe [a]
addEnumValue a
x Maybe [a]
Nothing = forall a. a -> Maybe a
Just [a
x]
addEnumValue a
x (Just [a]
xs) = forall a. a -> Maybe a
Just (a
xforall a. a -> [a] -> [a]
:[a]
xs)
data Proxy3 a b c = Proxy3