{-# OPTIONS_GHC -Wall #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PackageImports #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE ViewPatterns #-}
module Data.OpenApi.Internal.Schema.Validation where
import Prelude ()
import Prelude.Compat
import Control.Applicative
import Control.Lens hiding (allOf)
import Control.Monad (forM, forM_, when)
import Data.Aeson hiding (Result)
#if MIN_VERSION_aeson(2,0,0)
import qualified Data.Aeson.KeyMap as KeyMap
#endif
import Data.Foldable (for_, sequenceA_,
traverse_)
#if !MIN_VERSION_aeson(2,0,0)
import Data.HashMap.Strict (HashMap)
#endif
import qualified Data.HashMap.Strict.InsOrd as InsOrdHashMap
import qualified "unordered-containers" Data.HashSet as HashSet
import Data.Maybe (fromMaybe)
import Data.Proxy
import Data.Scientific (Scientific, isInteger)
import Data.Text (Text)
import qualified Data.Text as Text
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Encoding as TL
import Data.Vector (Vector)
import qualified Data.Vector as Vector
import Data.OpenApi.Aeson.Compat (hasKey, keyToText, lookupKey, objectToList)
import Data.OpenApi.Declare
import Data.OpenApi.Internal
import Data.OpenApi.Internal.Schema
import Data.OpenApi.Internal.Utils
import Data.OpenApi.Lens
validatePrettyToJSON :: forall a. (ToJSON a, ToSchema a) => a -> Maybe String
validatePrettyToJSON :: forall a. (ToJSON a, ToSchema a) => a -> Maybe String
validatePrettyToJSON = (a -> [String]) -> a -> Maybe String
forall a.
(ToJSON a, ToSchema a) =>
(a -> [String]) -> a -> Maybe String
renderValidationErrors a -> [String]
forall a. (ToJSON a, ToSchema a) => a -> [String]
validateToJSON
validateToJSON :: forall a. (ToJSON a, ToSchema a) => a -> [ValidationError]
validateToJSON :: forall a. (ToJSON a, ToSchema a) => a -> [String]
validateToJSON = (Text -> Text -> Bool) -> a -> [String]
forall a.
(ToJSON a, ToSchema a) =>
(Text -> Text -> Bool) -> a -> [String]
validateToJSONWithPatternChecker (\Text
_pattern Text
_str -> Bool
True)
validateToJSONWithPatternChecker :: forall a. (ToJSON a, ToSchema a) => (Pattern -> Text -> Bool) -> a -> [ValidationError]
validateToJSONWithPatternChecker :: forall a.
(ToJSON a, ToSchema a) =>
(Text -> Text -> Bool) -> a -> [String]
validateToJSONWithPatternChecker Text -> Text -> Bool
checker = (Text -> Text -> Bool)
-> Definitions Schema -> Schema -> Value -> [String]
validateJSONWithPatternChecker Text -> Text -> Bool
checker Definitions Schema
defs Schema
sch (Value -> [String]) -> (a -> Value) -> a -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Value
forall a. ToJSON a => a -> Value
toJSON
where
(Definitions Schema
defs, Schema
sch) = Declare (Definitions Schema) Schema
-> Definitions Schema -> (Definitions Schema, Schema)
forall d a. Declare d a -> d -> (d, a)
runDeclare (Proxy a -> Declare (Definitions Schema) Schema
forall a.
ToSchema a =>
Proxy a -> Declare (Definitions Schema) Schema
declareSchema (Proxy a
forall {k} (t :: k). Proxy t
Proxy :: Proxy a)) Definitions Schema
forall a. Monoid a => a
mempty
renderValidationErrors
:: forall a. (ToJSON a, ToSchema a)
=> (a -> [ValidationError]) -> a -> Maybe String
renderValidationErrors :: forall a.
(ToJSON a, ToSchema a) =>
(a -> [String]) -> a -> Maybe String
renderValidationErrors a -> [String]
f a
x =
case a -> [String]
f a
x of
[] -> Maybe String
forall a. Maybe a
Nothing
[String]
errors -> String -> Maybe String
forall a. a -> Maybe a
Just (String -> Maybe String) -> String -> Maybe String
forall a b. (a -> b) -> a -> b
$ [String] -> String
unlines
[ String
"Validation against the schema fails:"
, [String] -> String
unlines ((String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String
" * " String -> String -> String
forall a. [a] -> [a] -> [a]
++) [String]
errors)
, String
"JSON value:"
, Value -> String
ppJSONString (a -> Value
forall a. ToJSON a => a -> Value
toJSON a
x)
, String
""
, String
"Swagger Schema:"
, Value -> String
ppJSONString (Schema -> Value
forall a. ToJSON a => a -> Value
toJSON Schema
schema_)
, String
""
, String
"Swagger Description Context:"
, Value -> String
ppJSONString (Definitions Schema -> Value
forall a. ToJSON a => a -> Value
toJSON Definitions Schema
refs_)
]
where
ppJSONString :: Value -> String
ppJSONString = Text -> String
TL.unpack (Text -> String) -> (Value -> Text) -> Value -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
TL.decodeUtf8 (ByteString -> Text) -> (Value -> ByteString) -> Value -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> ByteString
forall a. ToJSON a => a -> ByteString
encodePretty
(Definitions Schema
refs_, Schema
schema_) = Declare (Definitions Schema) Schema
-> Definitions Schema -> (Definitions Schema, Schema)
forall d a. Declare d a -> d -> (d, a)
runDeclare (Proxy a -> Declare (Definitions Schema) Schema
forall a.
ToSchema a =>
Proxy a -> Declare (Definitions Schema) Schema
declareSchema (Proxy a
forall {k} (t :: k). Proxy t
Proxy :: Proxy a)) Definitions Schema
forall a. Monoid a => a
mempty
validateJSON :: Definitions Schema -> Schema -> Value -> [ValidationError]
validateJSON :: Definitions Schema -> Schema -> Value -> [String]
validateJSON = (Text -> Text -> Bool)
-> Definitions Schema -> Schema -> Value -> [String]
validateJSONWithPatternChecker (\Text
_pattern Text
_str -> Bool
True)
validateJSONWithPatternChecker :: (Pattern -> Text -> Bool) -> Definitions Schema -> Schema -> Value -> [ValidationError]
validateJSONWithPatternChecker :: (Text -> Text -> Bool)
-> Definitions Schema -> Schema -> Value -> [String]
validateJSONWithPatternChecker Text -> Text -> Bool
checker Definitions Schema
defs Schema
sch Value
js =
case Validation Schema () -> Config -> Schema -> Result ()
forall s a. Validation s a -> Config -> s -> Result a
runValidation (Value -> Validation Schema ()
validateWithSchema Value
js) Config
cfg Schema
sch of
Failed [String]
xs -> [String]
xs
Passed ()
_ -> [String]
forall a. Monoid a => a
mempty
where
cfg :: Config
cfg = Config
defaultConfig
{ configPatternChecker = checker
, configDefinitions = defs }
type ValidationError = String
data Result a
= Failed [ValidationError]
| Passed a
deriving (Result a -> Result a -> Bool
(Result a -> Result a -> Bool)
-> (Result a -> Result a -> Bool) -> Eq (Result a)
forall a. Eq a => Result a -> Result a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => Result a -> Result a -> Bool
== :: Result a -> Result a -> Bool
$c/= :: forall a. Eq a => Result a -> Result a -> Bool
/= :: Result a -> Result a -> Bool
Eq, Int -> Result a -> String -> String
[Result a] -> String -> String
Result a -> String
(Int -> Result a -> String -> String)
-> (Result a -> String)
-> ([Result a] -> String -> String)
-> Show (Result a)
forall a. Show a => Int -> Result a -> String -> String
forall a. Show a => [Result a] -> String -> String
forall a. Show a => Result a -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: forall a. Show a => Int -> Result a -> String -> String
showsPrec :: Int -> Result a -> String -> String
$cshow :: forall a. Show a => Result a -> String
show :: Result a -> String
$cshowList :: forall a. Show a => [Result a] -> String -> String
showList :: [Result a] -> String -> String
Show, (forall a b. (a -> b) -> Result a -> Result b)
-> (forall a b. a -> Result b -> Result a) -> Functor Result
forall a b. a -> Result b -> Result a
forall a b. (a -> b) -> Result a -> Result b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> Result a -> Result b
fmap :: forall a b. (a -> b) -> Result a -> Result b
$c<$ :: forall a b. a -> Result b -> Result a
<$ :: forall a b. a -> Result b -> Result a
Functor)
instance Applicative Result where
pure :: forall a. a -> Result a
pure = a -> Result a
forall a. a -> Result a
Passed
Passed a -> b
f <*> :: forall a b. Result (a -> b) -> Result a -> Result b
<*> Passed a
x = b -> Result b
forall a. a -> Result a
Passed (a -> b
f a
x)
Failed [String]
xs <*> Failed [String]
ys = [String] -> Result b
forall a. [String] -> Result a
Failed ([String]
xs [String] -> [String] -> [String]
forall a. Semigroup a => a -> a -> a
<> [String]
ys)
Failed [String]
xs <*> Result a
_ = [String] -> Result b
forall a. [String] -> Result a
Failed [String]
xs
Result (a -> b)
_ <*> Failed [String]
ys = [String] -> Result b
forall a. [String] -> Result a
Failed [String]
ys
instance Alternative Result where
empty :: forall a. Result a
empty = [String] -> Result a
forall a. [String] -> Result a
Failed [String]
forall a. Monoid a => a
mempty
Passed a
x <|> :: forall a. Result a -> Result a -> Result a
<|> Result a
_ = a -> Result a
forall a. a -> Result a
Passed a
x
Result a
_ <|> Result a
y = Result a
y
instance Monad Result where
return :: forall a. a -> Result a
return = a -> Result a
forall a. a -> Result a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
Passed a
x >>= :: forall a b. Result a -> (a -> Result b) -> Result b
>>= a -> Result b
f = a -> Result b
f a
x
Failed [String]
xs >>= a -> Result b
_ = [String] -> Result b
forall a. [String] -> Result a
Failed [String]
xs
data Config = Config
{
Config -> Text -> Text -> Bool
configPatternChecker :: Pattern -> Text -> Bool
, Config -> Definitions Schema
configDefinitions :: Definitions Schema
}
defaultConfig :: Config
defaultConfig :: Config
defaultConfig = Config
{ configPatternChecker :: Text -> Text -> Bool
configPatternChecker = \Text
_pattern Text
_str -> Bool
True
, configDefinitions :: Definitions Schema
configDefinitions = Definitions Schema
forall a. Monoid a => a
mempty
}
newtype Validation s a = Validation { forall s a. Validation s a -> Config -> s -> Result a
runValidation :: Config -> s -> Result a }
deriving ((forall a b. (a -> b) -> Validation s a -> Validation s b)
-> (forall a b. a -> Validation s b -> Validation s a)
-> Functor (Validation s)
forall a b. a -> Validation s b -> Validation s a
forall a b. (a -> b) -> Validation s a -> Validation s b
forall s a b. a -> Validation s b -> Validation s a
forall s a b. (a -> b) -> Validation s a -> Validation s b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall s a b. (a -> b) -> Validation s a -> Validation s b
fmap :: forall a b. (a -> b) -> Validation s a -> Validation s b
$c<$ :: forall s a b. a -> Validation s b -> Validation s a
<$ :: forall a b. a -> Validation s b -> Validation s a
Functor)
instance Applicative (Validation schema) where
pure :: forall a. a -> Validation schema a
pure a
x = (Config -> schema -> Result a) -> Validation schema a
forall s a. (Config -> s -> Result a) -> Validation s a
Validation (\Config
_ schema
_ -> a -> Result a
forall a. a -> Result a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
x)
Validation Config -> schema -> Result (a -> b)
f <*> :: forall a b.
Validation schema (a -> b)
-> Validation schema a -> Validation schema b
<*> Validation Config -> schema -> Result a
x = (Config -> schema -> Result b) -> Validation schema b
forall s a. (Config -> s -> Result a) -> Validation s a
Validation (\Config
c schema
s -> Config -> schema -> Result (a -> b)
f Config
c schema
s Result (a -> b) -> Result a -> Result b
forall a b. Result (a -> b) -> Result a -> Result b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Config -> schema -> Result a
x Config
c schema
s)
instance Alternative (Validation schema) where
empty :: forall a. Validation schema a
empty = (Config -> schema -> Result a) -> Validation schema a
forall s a. (Config -> s -> Result a) -> Validation s a
Validation (\Config
_ schema
_ -> Result a
forall a. Result a
forall (f :: * -> *) a. Alternative f => f a
empty)
Validation Config -> schema -> Result a
x <|> :: forall a.
Validation schema a -> Validation schema a -> Validation schema a
<|> Validation Config -> schema -> Result a
y = (Config -> schema -> Result a) -> Validation schema a
forall s a. (Config -> s -> Result a) -> Validation s a
Validation (\Config
c schema
s -> Config -> schema -> Result a
x Config
c schema
s Result a -> Result a -> Result a
forall a. Result a -> Result a -> Result a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Config -> schema -> Result a
y Config
c schema
s)
instance Profunctor Validation where
dimap :: forall a b c d.
(a -> b) -> (c -> d) -> Validation b c -> Validation a d
dimap a -> b
f c -> d
g (Validation Config -> b -> Result c
k) = (Config -> a -> Result d) -> Validation a d
forall s a. (Config -> s -> Result a) -> Validation s a
Validation (\Config
c a
s -> (c -> d) -> Result c -> Result d
forall a b. (a -> b) -> Result a -> Result b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap c -> d
g (Config -> b -> Result c
k Config
c (a -> b
f a
s)))
instance Choice Validation where
left' :: forall a b c.
Validation a b -> Validation (Either a c) (Either b c)
left' (Validation Config -> a -> Result b
g) = (Config -> Either a c -> Result (Either b c))
-> Validation (Either a c) (Either b c)
forall s a. (Config -> s -> Result a) -> Validation s a
Validation (\Config
c -> (a -> Result (Either b c))
-> (c -> Result (Either b c)) -> Either a c -> Result (Either b c)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ((b -> Either b c) -> Result b -> Result (Either b c)
forall a b. (a -> b) -> Result a -> Result b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap b -> Either b c
forall a b. a -> Either a b
Left (Result b -> Result (Either b c))
-> (a -> Result b) -> a -> Result (Either b c)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Config -> a -> Result b
g Config
c) (Either b c -> Result (Either b c)
forall a. a -> Result a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either b c -> Result (Either b c))
-> (c -> Either b c) -> c -> Result (Either b c)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. c -> Either b c
forall a b. b -> Either a b
Right))
right' :: forall a b c.
Validation a b -> Validation (Either c a) (Either c b)
right' (Validation Config -> a -> Result b
g) = (Config -> Either c a -> Result (Either c b))
-> Validation (Either c a) (Either c b)
forall s a. (Config -> s -> Result a) -> Validation s a
Validation (\Config
c -> (c -> Result (Either c b))
-> (a -> Result (Either c b)) -> Either c a -> Result (Either c b)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Either c b -> Result (Either c b)
forall a. a -> Result a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either c b -> Result (Either c b))
-> (c -> Either c b) -> c -> Result (Either c b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. c -> Either c b
forall a b. a -> Either a b
Left) ((b -> Either c b) -> Result b -> Result (Either c b)
forall a b. (a -> b) -> Result a -> Result b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap b -> Either c b
forall a b. b -> Either a b
Right (Result b -> Result (Either c b))
-> (a -> Result b) -> a -> Result (Either c b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Config -> a -> Result b
g Config
c))
instance Monad (Validation s) where
return :: forall a. a -> Validation s a
return = a -> Validation s a
forall a. a -> Validation s a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
Validation Config -> s -> Result a
x >>= :: forall a b.
Validation s a -> (a -> Validation s b) -> Validation s b
>>= a -> Validation s b
f = (Config -> s -> Result b) -> Validation s b
forall s a. (Config -> s -> Result a) -> Validation s a
Validation (\Config
c s
s -> Config -> s -> Result a
x Config
c s
s Result a -> (a -> Result b) -> Result b
forall a b. Result a -> (a -> Result b) -> Result b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \a
y -> Validation s b -> Config -> s -> Result b
forall s a. Validation s a -> Config -> s -> Result a
runValidation (a -> Validation s b
f a
y) Config
c s
s)
>> :: forall a b. Validation s a -> Validation s b -> Validation s b
(>>) = Validation s a -> Validation s b -> Validation s b
forall a b. Validation s a -> Validation s b -> Validation s b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
(*>)
withConfig :: (Config -> Validation s a) -> Validation s a
withConfig :: forall s a. (Config -> Validation s a) -> Validation s a
withConfig Config -> Validation s a
f = (Config -> s -> Result a) -> Validation s a
forall s a. (Config -> s -> Result a) -> Validation s a
Validation (\Config
c -> Validation s a -> Config -> s -> Result a
forall s a. Validation s a -> Config -> s -> Result a
runValidation (Config -> Validation s a
f Config
c) Config
c)
withSchema :: (s -> Validation s a) -> Validation s a
withSchema :: forall s a. (s -> Validation s a) -> Validation s a
withSchema s -> Validation s a
f = (Config -> s -> Result a) -> Validation s a
forall s a. (Config -> s -> Result a) -> Validation s a
Validation (\Config
c s
s -> Validation s a -> Config -> s -> Result a
forall s a. Validation s a -> Config -> s -> Result a
runValidation (s -> Validation s a
f s
s) Config
c s
s)
invalid :: String -> Validation schema a
invalid :: forall schema a. String -> Validation schema a
invalid String
msg = (Config -> schema -> Result a) -> Validation schema a
forall s a. (Config -> s -> Result a) -> Validation s a
Validation (\Config
_ schema
_ -> [String] -> Result a
forall a. [String] -> Result a
Failed [String
msg])
valid :: Validation schema ()
valid :: forall schema. Validation schema ()
valid = () -> Validation schema ()
forall a. a -> Validation schema a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
checkMissing :: Validation s () -> Lens' s (Maybe a) -> (a -> Validation s ()) -> Validation s ()
checkMissing :: forall s a.
Validation s ()
-> Lens' s (Maybe a) -> (a -> Validation s ()) -> Validation s ()
checkMissing Validation s ()
missing Lens' s (Maybe a)
l a -> Validation s ()
g = (s -> Validation s ()) -> Validation s ()
forall s a. (s -> Validation s a) -> Validation s a
withSchema ((s -> Validation s ()) -> Validation s ())
-> (s -> Validation s ()) -> Validation s ()
forall a b. (a -> b) -> a -> b
$ \s
sch ->
case s
sch s -> Getting (Maybe a) s (Maybe a) -> Maybe a
forall s a. s -> Getting a s a -> a
^. Getting (Maybe a) s (Maybe a)
Lens' s (Maybe a)
l of
Maybe a
Nothing -> Validation s ()
missing
Just a
x -> a -> Validation s ()
g a
x
check :: Lens' s (Maybe a) -> (a -> Validation s ()) -> Validation s ()
check :: forall s a.
Lens' s (Maybe a) -> (a -> Validation s ()) -> Validation s ()
check = Validation s ()
-> Lens' s (Maybe a) -> (a -> Validation s ()) -> Validation s ()
forall s a.
Validation s ()
-> Lens' s (Maybe a) -> (a -> Validation s ()) -> Validation s ()
checkMissing Validation s ()
forall schema. Validation schema ()
valid
sub :: t -> Validation t a -> Validation s a
sub :: forall t a s. t -> Validation t a -> Validation s a
sub = (s -> t) -> Validation t a -> Validation s a
forall a b c. (a -> b) -> Validation b c -> Validation a c
forall (p :: * -> * -> *) a b c.
Profunctor p =>
(a -> b) -> p b c -> p a c
lmap ((s -> t) -> Validation t a -> Validation s a)
-> (t -> s -> t) -> t -> Validation t a -> Validation s a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. t -> s -> t
forall a b. a -> b -> a
const
sub_ :: Getting a s a -> Validation a r -> Validation s r
sub_ :: forall a s r. Getting a s a -> Validation a r -> Validation s r
sub_ = (s -> a) -> Validation a r -> Validation s r
forall a b c. (a -> b) -> Validation b c -> Validation a c
forall (p :: * -> * -> *) a b c.
Profunctor p =>
(a -> b) -> p b c -> p a c
lmap ((s -> a) -> Validation a r -> Validation s r)
-> (Getting a s a -> s -> a)
-> Getting a s a
-> Validation a r
-> Validation s r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting a s a -> s -> a
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view
withRef :: Reference -> (Schema -> Validation s a) -> Validation s a
withRef :: forall s a.
Reference -> (Schema -> Validation s a) -> Validation s a
withRef (Reference Text
ref) Schema -> Validation s a
f = (Config -> Validation s a) -> Validation s a
forall s a. (Config -> Validation s a) -> Validation s a
withConfig ((Config -> Validation s a) -> Validation s a)
-> (Config -> Validation s a) -> Validation s a
forall a b. (a -> b) -> a -> b
$ \Config
cfg ->
case Text -> Definitions Schema -> Maybe Schema
forall k v. (Eq k, Hashable k) => k -> InsOrdHashMap k v -> Maybe v
InsOrdHashMap.lookup Text
ref (Config -> Definitions Schema
configDefinitions Config
cfg) of
Maybe Schema
Nothing -> String -> Validation s a
forall schema a. String -> Validation schema a
invalid (String -> Validation s a) -> String -> Validation s a
forall a b. (a -> b) -> a -> b
$ String
"unknown schema " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Text -> String
forall a. Show a => a -> String
show Text
ref
Just Schema
s -> Schema -> Validation s a
f Schema
s
validateWithSchemaRef :: Referenced Schema -> Value -> Validation s ()
validateWithSchemaRef :: forall s. Referenced Schema -> Value -> Validation s ()
validateWithSchemaRef (Ref Reference
ref) Value
js = Reference -> (Schema -> Validation s ()) -> Validation s ()
forall s a.
Reference -> (Schema -> Validation s a) -> Validation s a
withRef Reference
ref ((Schema -> Validation s ()) -> Validation s ())
-> (Schema -> Validation s ()) -> Validation s ()
forall a b. (a -> b) -> a -> b
$ \Schema
sch -> Schema -> Validation Schema () -> Validation s ()
forall t a s. t -> Validation t a -> Validation s a
sub Schema
sch (Value -> Validation Schema ()
validateWithSchema Value
js)
validateWithSchemaRef (Inline Schema
s) Value
js = Schema -> Validation Schema () -> Validation s ()
forall t a s. t -> Validation t a -> Validation s a
sub Schema
s (Value -> Validation Schema ()
validateWithSchema Value
js)
validateWithSchema :: Value -> Validation Schema ()
validateWithSchema :: Value -> Validation Schema ()
validateWithSchema Value
val = do
Value -> Validation Schema ()
validateSchemaType Value
val
Value -> Validation Schema ()
validateEnum Value
val
validateInteger :: Scientific -> Validation Schema ()
validateInteger :: Scientific -> Validation Schema ()
validateInteger Scientific
n = do
Bool -> Validation Schema () -> Validation Schema ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not (Scientific -> Bool
isInteger Scientific
n)) (Validation Schema () -> Validation Schema ())
-> Validation Schema () -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$
String -> Validation Schema ()
forall schema a. String -> Validation schema a
invalid (String
"not an integer")
Scientific -> Validation Schema ()
validateNumber Scientific
n
validateNumber :: Scientific -> Validation Schema ()
validateNumber :: Scientific -> Validation Schema ()
validateNumber Scientific
n = (Config -> Validation Schema ()) -> Validation Schema ()
forall s a. (Config -> Validation s a) -> Validation s a
withConfig ((Config -> Validation Schema ()) -> Validation Schema ())
-> (Config -> Validation Schema ()) -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$ \Config
_cfg -> (Schema -> Validation Schema ()) -> Validation Schema ()
forall s a. (s -> Validation s a) -> Validation s a
withSchema ((Schema -> Validation Schema ()) -> Validation Schema ())
-> (Schema -> Validation Schema ()) -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$ \Schema
sch -> do
let exMax :: Bool
exMax = Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True Maybe Bool -> Maybe Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Schema
sch Schema -> Getting (Maybe Bool) Schema (Maybe Bool) -> Maybe Bool
forall s a. s -> Getting a s a -> a
^. Getting (Maybe Bool) Schema (Maybe Bool)
forall s a. HasExclusiveMaximum s a => Lens' s a
Lens' Schema (Maybe Bool)
exclusiveMaximum
exMin :: Bool
exMin = Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True Maybe Bool -> Maybe Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Schema
sch Schema -> Getting (Maybe Bool) Schema (Maybe Bool) -> Maybe Bool
forall s a. s -> Getting a s a -> a
^. Getting (Maybe Bool) Schema (Maybe Bool)
forall s a. HasExclusiveMinimum s a => Lens' s a
Lens' Schema (Maybe Bool)
exclusiveMinimum
Lens' Schema (Maybe Scientific)
-> (Scientific -> Validation Schema ()) -> Validation Schema ()
forall s a.
Lens' s (Maybe a) -> (a -> Validation s ()) -> Validation s ()
check (Maybe Scientific -> f (Maybe Scientific)) -> Schema -> f Schema
forall s a. HasMaximum s a => Lens' s a
Lens' Schema (Maybe Scientific)
maximum_ ((Scientific -> Validation Schema ()) -> Validation Schema ())
-> (Scientific -> Validation Schema ()) -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$ \Scientific
m ->
Bool -> Validation Schema () -> Validation Schema ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (if Bool
exMax then (Scientific
n Scientific -> Scientific -> Bool
forall a. Ord a => a -> a -> Bool
>= Scientific
m) else (Scientific
n Scientific -> Scientific -> Bool
forall a. Ord a => a -> a -> Bool
> Scientific
m)) (Validation Schema () -> Validation Schema ())
-> Validation Schema () -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$
String -> Validation Schema ()
forall schema a. String -> Validation schema a
invalid (String
"value " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Scientific -> String
forall a. Show a => a -> String
show Scientific
n String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" exceeds maximum (should be " String -> String -> String
forall a. [a] -> [a] -> [a]
++ (if Bool
exMax then String
"<" else String
"<=") String -> String -> String
forall a. [a] -> [a] -> [a]
++ Scientific -> String
forall a. Show a => a -> String
show Scientific
m String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
")")
Lens' Schema (Maybe Scientific)
-> (Scientific -> Validation Schema ()) -> Validation Schema ()
forall s a.
Lens' s (Maybe a) -> (a -> Validation s ()) -> Validation s ()
check (Maybe Scientific -> f (Maybe Scientific)) -> Schema -> f Schema
forall s a. HasMinimum s a => Lens' s a
Lens' Schema (Maybe Scientific)
minimum_ ((Scientific -> Validation Schema ()) -> Validation Schema ())
-> (Scientific -> Validation Schema ()) -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$ \Scientific
m ->
Bool -> Validation Schema () -> Validation Schema ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (if Bool
exMin then (Scientific
n Scientific -> Scientific -> Bool
forall a. Ord a => a -> a -> Bool
<= Scientific
m) else (Scientific
n Scientific -> Scientific -> Bool
forall a. Ord a => a -> a -> Bool
< Scientific
m)) (Validation Schema () -> Validation Schema ())
-> Validation Schema () -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$
String -> Validation Schema ()
forall schema a. String -> Validation schema a
invalid (String
"value " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Scientific -> String
forall a. Show a => a -> String
show Scientific
n String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" falls below minimum (should be " String -> String -> String
forall a. [a] -> [a] -> [a]
++ (if Bool
exMin then String
">" else String
">=") String -> String -> String
forall a. [a] -> [a] -> [a]
++ Scientific -> String
forall a. Show a => a -> String
show Scientific
m String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
")")
Lens' Schema (Maybe Scientific)
-> (Scientific -> Validation Schema ()) -> Validation Schema ()
forall s a.
Lens' s (Maybe a) -> (a -> Validation s ()) -> Validation s ()
check (Maybe Scientific -> f (Maybe Scientific)) -> Schema -> f Schema
forall s a. HasMultipleOf s a => Lens' s a
Lens' Schema (Maybe Scientific)
multipleOf ((Scientific -> Validation Schema ()) -> Validation Schema ())
-> (Scientific -> Validation Schema ()) -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$ \Scientific
k ->
Bool -> Validation Schema () -> Validation Schema ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not (Scientific -> Bool
isInteger (Scientific
n Scientific -> Scientific -> Scientific
forall a. Fractional a => a -> a -> a
/ Scientific
k))) (Validation Schema () -> Validation Schema ())
-> Validation Schema () -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$
String -> Validation Schema ()
forall schema a. String -> Validation schema a
invalid (String
"expected a multiple of " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Scientific -> String
forall a. Show a => a -> String
show Scientific
k String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" but got " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Scientific -> String
forall a. Show a => a -> String
show Scientific
n)
validateString :: Text -> Validation Schema ()
validateString :: Text -> Validation Schema ()
validateString Text
s = do
Lens' Schema (Maybe Integer)
-> (Integer -> Validation Schema ()) -> Validation Schema ()
forall s a.
Lens' s (Maybe a) -> (a -> Validation s ()) -> Validation s ()
check (Maybe Integer -> f (Maybe Integer)) -> Schema -> f Schema
forall s a. HasMaxLength s a => Lens' s a
Lens' Schema (Maybe Integer)
maxLength ((Integer -> Validation Schema ()) -> Validation Schema ())
-> (Integer -> Validation Schema ()) -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$ \Integer
n ->
Bool -> Validation Schema () -> Validation Schema ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
len Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Integer -> Int
forall a. Num a => Integer -> a
fromInteger Integer
n) (Validation Schema () -> Validation Schema ())
-> Validation Schema () -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$
String -> Validation Schema ()
forall schema a. String -> Validation schema a
invalid (String
"string is too long (length should be <=" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Integer -> String
forall a. Show a => a -> String
show Integer
n String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
")")
Lens' Schema (Maybe Integer)
-> (Integer -> Validation Schema ()) -> Validation Schema ()
forall s a.
Lens' s (Maybe a) -> (a -> Validation s ()) -> Validation s ()
check (Maybe Integer -> f (Maybe Integer)) -> Schema -> f Schema
forall s a. HasMinLength s a => Lens' s a
Lens' Schema (Maybe Integer)
minLength ((Integer -> Validation Schema ()) -> Validation Schema ())
-> (Integer -> Validation Schema ()) -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$ \Integer
n ->
Bool -> Validation Schema () -> Validation Schema ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
len Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Integer -> Int
forall a. Num a => Integer -> a
fromInteger Integer
n) (Validation Schema () -> Validation Schema ())
-> Validation Schema () -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$
String -> Validation Schema ()
forall schema a. String -> Validation schema a
invalid (String
"string is too short (length should be >=" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Integer -> String
forall a. Show a => a -> String
show Integer
n String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
")")
Lens' Schema (Maybe Text)
-> (Text -> Validation Schema ()) -> Validation Schema ()
forall s a.
Lens' s (Maybe a) -> (a -> Validation s ()) -> Validation s ()
check (Maybe Text -> f (Maybe Text)) -> Schema -> f Schema
forall s a. HasPattern s a => Lens' s a
Lens' Schema (Maybe Text)
pattern ((Text -> Validation Schema ()) -> Validation Schema ())
-> (Text -> Validation Schema ()) -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$ \Text
regex -> do
(Config -> Validation Schema ()) -> Validation Schema ()
forall s a. (Config -> Validation s a) -> Validation s a
withConfig ((Config -> Validation Schema ()) -> Validation Schema ())
-> (Config -> Validation Schema ()) -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$ \Config
cfg -> do
Bool -> Validation Schema () -> Validation Schema ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not (Config -> Text -> Text -> Bool
configPatternChecker Config
cfg Text
regex Text
s)) (Validation Schema () -> Validation Schema ())
-> Validation Schema () -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$
String -> Validation Schema ()
forall schema a. String -> Validation schema a
invalid (String
"string does not match pattern " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Text -> String
forall a. Show a => a -> String
show Text
regex)
where
len :: Int
len = Text -> Int
Text.length Text
s
validateArray :: Vector Value -> Validation Schema ()
validateArray :: Vector Value -> Validation Schema ()
validateArray Vector Value
xs = do
Lens' Schema (Maybe Integer)
-> (Integer -> Validation Schema ()) -> Validation Schema ()
forall s a.
Lens' s (Maybe a) -> (a -> Validation s ()) -> Validation s ()
check (Maybe Integer -> f (Maybe Integer)) -> Schema -> f Schema
forall s a. HasMaxItems s a => Lens' s a
Lens' Schema (Maybe Integer)
maxItems ((Integer -> Validation Schema ()) -> Validation Schema ())
-> (Integer -> Validation Schema ()) -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$ \Integer
n ->
Bool -> Validation Schema () -> Validation Schema ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
len Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Integer -> Int
forall a. Num a => Integer -> a
fromInteger Integer
n) (Validation Schema () -> Validation Schema ())
-> Validation Schema () -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$
String -> Validation Schema ()
forall schema a. String -> Validation schema a
invalid (String
"array exceeds maximum size (should be <=" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Integer -> String
forall a. Show a => a -> String
show Integer
n String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
")")
Lens' Schema (Maybe Integer)
-> (Integer -> Validation Schema ()) -> Validation Schema ()
forall s a.
Lens' s (Maybe a) -> (a -> Validation s ()) -> Validation s ()
check (Maybe Integer -> f (Maybe Integer)) -> Schema -> f Schema
forall s a. HasMinItems s a => Lens' s a
Lens' Schema (Maybe Integer)
minItems ((Integer -> Validation Schema ()) -> Validation Schema ())
-> (Integer -> Validation Schema ()) -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$ \Integer
n ->
Bool -> Validation Schema () -> Validation Schema ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
len Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Integer -> Int
forall a. Num a => Integer -> a
fromInteger Integer
n) (Validation Schema () -> Validation Schema ())
-> Validation Schema () -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$
String -> Validation Schema ()
forall schema a. String -> Validation schema a
invalid (String
"array is too short (size should be >=" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Integer -> String
forall a. Show a => a -> String
show Integer
n String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
")")
Lens' Schema (Maybe OpenApiItems)
-> (OpenApiItems -> Validation Schema ()) -> Validation Schema ()
forall s a.
Lens' s (Maybe a) -> (a -> Validation s ()) -> Validation s ()
check (Maybe OpenApiItems -> f (Maybe OpenApiItems))
-> Schema -> f Schema
forall s a. HasItems s a => Lens' s a
Lens' Schema (Maybe OpenApiItems)
items ((OpenApiItems -> Validation Schema ()) -> Validation Schema ())
-> (OpenApiItems -> Validation Schema ()) -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$ \case
OpenApiItemsObject Referenced Schema
itemSchema -> (Value -> Validation Schema ())
-> Vector Value -> Validation Schema ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ (Referenced Schema -> Value -> Validation Schema ()
forall s. Referenced Schema -> Value -> Validation s ()
validateWithSchemaRef Referenced Schema
itemSchema) Vector Value
xs
OpenApiItemsArray [Referenced Schema]
itemSchemas -> do
Bool -> Validation Schema () -> Validation Schema ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
len Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= [Referenced Schema] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Referenced Schema]
itemSchemas) (Validation Schema () -> Validation Schema ())
-> Validation Schema () -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$
String -> Validation Schema ()
forall schema a. String -> Validation schema a
invalid (String
"array size is invalid (should be exactly " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show ([Referenced Schema] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Referenced Schema]
itemSchemas) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
")")
[Validation Schema ()] -> Validation Schema ()
forall (t :: * -> *) (f :: * -> *) a.
(Foldable t, Applicative f) =>
t (f a) -> f ()
sequenceA_ ((Referenced Schema -> Value -> Validation Schema ())
-> [Referenced Schema] -> [Value] -> [Validation Schema ()]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Referenced Schema -> Value -> Validation Schema ()
forall s. Referenced Schema -> Value -> Validation s ()
validateWithSchemaRef [Referenced Schema]
itemSchemas (Vector Value -> [Value]
forall a. Vector a -> [a]
Vector.toList Vector Value
xs))
Lens' Schema (Maybe Bool)
-> (Bool -> Validation Schema ()) -> Validation Schema ()
forall s a.
Lens' s (Maybe a) -> (a -> Validation s ()) -> Validation s ()
check (Maybe Bool -> f (Maybe Bool)) -> Schema -> f Schema
forall s a. HasUniqueItems s a => Lens' s a
Lens' Schema (Maybe Bool)
uniqueItems ((Bool -> Validation Schema ()) -> Validation Schema ())
-> (Bool -> Validation Schema ()) -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$ \Bool
unique ->
Bool -> Validation Schema () -> Validation Schema ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool
unique Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
allUnique) (Validation Schema () -> Validation Schema ())
-> Validation Schema () -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$
String -> Validation Schema ()
forall schema a. String -> Validation schema a
invalid (String
"array is expected to contain unique items, but it does not")
where
len :: Int
len = Vector Value -> Int
forall a. Vector a -> Int
Vector.length Vector Value
xs
allUnique :: Bool
allUnique = Int
len Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== HashSet Value -> Int
forall a. HashSet a -> Int
HashSet.size ([Value] -> HashSet Value
forall a. (Eq a, Hashable a) => [a] -> HashSet a
HashSet.fromList (Vector Value -> [Value]
forall a. Vector a -> [a]
Vector.toList Vector Value
xs))
validateObject ::
#if MIN_VERSION_aeson(2,0,0)
KeyMap.KeyMap Value
#else
HashMap Text Value
#endif
-> Validation Schema ()
validateObject :: KeyMap Value -> Validation Schema ()
validateObject KeyMap Value
o = (Schema -> Validation Schema ()) -> Validation Schema ()
forall s a. (s -> Validation s a) -> Validation s a
withSchema ((Schema -> Validation Schema ()) -> Validation Schema ())
-> (Schema -> Validation Schema ()) -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$ \Schema
sch ->
case Schema
sch Schema
-> Getting (Maybe Discriminator) Schema (Maybe Discriminator)
-> Maybe Discriminator
forall s a. s -> Getting a s a -> a
^. Getting (Maybe Discriminator) Schema (Maybe Discriminator)
forall s a. HasDiscriminator s a => Lens' s a
Lens' Schema (Maybe Discriminator)
discriminator of
Just (Discriminator Text
pname InsOrdHashMap Text Text
types) -> case Value -> Result Text
forall a. FromJSON a => Value -> Result a
fromJSON (Value -> Result Text) -> Maybe Value -> Maybe (Result Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> KeyMap Value -> Maybe Value
forall v. Text -> KeyMap v -> Maybe v
lookupKey Text
pname KeyMap Value
o of
Just (Success Text
pvalue) ->
let ref :: Text
ref = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
pvalue (Maybe Text -> Text) -> Maybe Text -> Text
forall a b. (a -> b) -> a -> b
$ Text -> InsOrdHashMap Text Text -> Maybe Text
forall k v. (Eq k, Hashable k) => k -> InsOrdHashMap k v -> Maybe v
InsOrdHashMap.lookup Text
pvalue InsOrdHashMap Text Text
types
in Referenced Schema -> Value -> Validation Schema ()
forall s. Referenced Schema -> Value -> Validation s ()
validateWithSchemaRef (Reference -> Referenced Schema
forall a. Reference -> Referenced a
Ref (Text -> Reference
Reference Text
ref)) (KeyMap Value -> Value
Object KeyMap Value
o)
Just (Error String
msg) -> String -> Validation Schema ()
forall schema a. String -> Validation schema a
invalid (String
"failed to parse discriminator property " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Text -> String
forall a. Show a => a -> String
show Text
pname String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show String
msg)
Maybe (Result Text)
Nothing -> String -> Validation Schema ()
forall schema a. String -> Validation schema a
invalid (String
"discriminator property " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Text -> String
forall a. Show a => a -> String
show Text
pname String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"is missing")
Maybe Discriminator
Nothing -> do
Lens' Schema (Maybe Integer)
-> (Integer -> Validation Schema ()) -> Validation Schema ()
forall s a.
Lens' s (Maybe a) -> (a -> Validation s ()) -> Validation s ()
check (Maybe Integer -> f (Maybe Integer)) -> Schema -> f Schema
forall s a. HasMaxProperties s a => Lens' s a
Lens' Schema (Maybe Integer)
maxProperties ((Integer -> Validation Schema ()) -> Validation Schema ())
-> (Integer -> Validation Schema ()) -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$ \Integer
n ->
Bool -> Validation Schema () -> Validation Schema ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Integer
size Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
n) (Validation Schema () -> Validation Schema ())
-> Validation Schema () -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$
String -> Validation Schema ()
forall schema a. String -> Validation schema a
invalid (String
"object size exceeds maximum (total number of properties should be <=" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Integer -> String
forall a. Show a => a -> String
show Integer
n String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
")")
Lens' Schema (Maybe Integer)
-> (Integer -> Validation Schema ()) -> Validation Schema ()
forall s a.
Lens' s (Maybe a) -> (a -> Validation s ()) -> Validation s ()
check (Maybe Integer -> f (Maybe Integer)) -> Schema -> f Schema
forall s a. HasMinProperties s a => Lens' s a
Lens' Schema (Maybe Integer)
minProperties ((Integer -> Validation Schema ()) -> Validation Schema ())
-> (Integer -> Validation Schema ()) -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$ \Integer
n ->
Bool -> Validation Schema () -> Validation Schema ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Integer
size Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
n) (Validation Schema () -> Validation Schema ())
-> Validation Schema () -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$
String -> Validation Schema ()
forall schema a. String -> Validation schema a
invalid (String
"object size is too small (total number of properties should be >=" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Integer -> String
forall a. Show a => a -> String
show Integer
n String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
")")
Validation Schema ()
validateRequired
Validation Schema ()
validateProps
where
size :: Integer
size = Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (KeyMap Value -> Int
forall a. KeyMap a -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length KeyMap Value
o)
validateRequired :: Validation Schema ()
validateRequired = (Schema -> Validation Schema ()) -> Validation Schema ()
forall s a. (s -> Validation s a) -> Validation s a
withSchema ((Schema -> Validation Schema ()) -> Validation Schema ())
-> (Schema -> Validation Schema ()) -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$ \Schema
sch -> (Text -> Validation Schema ()) -> [Text] -> Validation Schema ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ Text -> Validation Schema ()
validateReq (Schema
sch Schema -> Getting [Text] Schema [Text] -> [Text]
forall s a. s -> Getting a s a -> a
^. Getting [Text] Schema [Text]
forall s a. HasRequired s a => Lens' s a
Lens' Schema [Text]
required)
validateReq :: Text -> Validation Schema ()
validateReq Text
n =
Bool -> Validation Schema () -> Validation Schema ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not (Text -> KeyMap Value -> Bool
forall a. Text -> KeyMap a -> Bool
hasKey Text
n KeyMap Value
o)) (Validation Schema () -> Validation Schema ())
-> Validation Schema () -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$
String -> Validation Schema ()
forall schema a. String -> Validation schema a
invalid (String
"property " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Text -> String
forall a. Show a => a -> String
show Text
n String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" is required, but not found in " String -> String -> String
forall a. [a] -> [a] -> [a]
++ ByteString -> String
forall a. Show a => a -> String
show (KeyMap Value -> ByteString
forall a. ToJSON a => a -> ByteString
encode KeyMap Value
o))
validateProps :: Validation Schema ()
validateProps = (Schema -> Validation Schema ()) -> Validation Schema ()
forall s a. (s -> Validation s a) -> Validation s a
withSchema ((Schema -> Validation Schema ()) -> Validation Schema ())
-> (Schema -> Validation Schema ()) -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$ \Schema
sch -> do
[(Key, Value)]
-> ((Key, Value) -> Validation Schema ()) -> Validation Schema ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ (KeyMap Value -> [(Key, Value)]
forall v. KeyMap v -> [(Key, v)]
objectToList KeyMap Value
o) (((Key, Value) -> Validation Schema ()) -> Validation Schema ())
-> ((Key, Value) -> Validation Schema ()) -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$ \(Key -> Text
keyToText -> Text
k, Value
v) ->
case Value
v of
Value
Null | Bool -> Bool
not (Text
k Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (Schema
sch Schema -> Getting [Text] Schema [Text] -> [Text]
forall s a. s -> Getting a s a -> a
^. Getting [Text] Schema [Text]
forall s a. HasRequired s a => Lens' s a
Lens' Schema [Text]
required)) -> Validation Schema ()
forall schema. Validation schema ()
valid
Value
_ ->
case Text
-> InsOrdHashMap Text (Referenced Schema)
-> Maybe (Referenced Schema)
forall k v. (Eq k, Hashable k) => k -> InsOrdHashMap k v -> Maybe v
InsOrdHashMap.lookup Text
k (Schema
sch Schema
-> Getting
(InsOrdHashMap Text (Referenced Schema))
Schema
(InsOrdHashMap Text (Referenced Schema))
-> InsOrdHashMap Text (Referenced Schema)
forall s a. s -> Getting a s a -> a
^. Getting
(InsOrdHashMap Text (Referenced Schema))
Schema
(InsOrdHashMap Text (Referenced Schema))
forall s a. HasProperties s a => Lens' s a
Lens' Schema (InsOrdHashMap Text (Referenced Schema))
properties) of
Maybe (Referenced Schema)
Nothing -> Validation Schema ()
-> Lens' Schema (Maybe AdditionalProperties)
-> (AdditionalProperties -> Validation Schema ())
-> Validation Schema ()
forall s a.
Validation s ()
-> Lens' s (Maybe a) -> (a -> Validation s ()) -> Validation s ()
checkMissing (Text -> Validation Schema ()
forall s a. Text -> Validation s a
unknownProperty Text
k) (Maybe AdditionalProperties -> f (Maybe AdditionalProperties))
-> Schema -> f Schema
forall s a. HasAdditionalProperties s a => Lens' s a
Lens' Schema (Maybe AdditionalProperties)
additionalProperties ((AdditionalProperties -> Validation Schema ())
-> Validation Schema ())
-> (AdditionalProperties -> Validation Schema ())
-> Validation Schema ()
forall a b. (a -> b) -> a -> b
$ Text -> Value -> AdditionalProperties -> Validation Schema ()
forall {a} {schema}.
Show a =>
a -> Value -> AdditionalProperties -> Validation schema ()
validateAdditional Text
k Value
v
Just Referenced Schema
s -> Referenced Schema -> Value -> Validation Schema ()
forall s. Referenced Schema -> Value -> Validation s ()
validateWithSchemaRef Referenced Schema
s Value
v
validateAdditional :: a -> Value -> AdditionalProperties -> Validation schema ()
validateAdditional a
_ Value
_ (AdditionalPropertiesAllowed Bool
True) = Validation schema ()
forall schema. Validation schema ()
valid
validateAdditional a
k Value
_ (AdditionalPropertiesAllowed Bool
False) = String -> Validation schema ()
forall schema a. String -> Validation schema a
invalid (String -> Validation schema ()) -> String -> Validation schema ()
forall a b. (a -> b) -> a -> b
$ String
"additionalProperties=false but extra property " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> a -> String
forall a. Show a => a -> String
show a
k String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" found"
validateAdditional a
_ Value
v (AdditionalPropertiesSchema Referenced Schema
s) = Referenced Schema -> Value -> Validation schema ()
forall s. Referenced Schema -> Value -> Validation s ()
validateWithSchemaRef Referenced Schema
s Value
v
unknownProperty :: Text -> Validation s a
unknownProperty :: forall s a. Text -> Validation s a
unknownProperty Text
pname = String -> Validation s a
forall schema a. String -> Validation schema a
invalid (String -> Validation s a) -> String -> Validation s a
forall a b. (a -> b) -> a -> b
$
String
"property " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Text -> String
forall a. Show a => a -> String
show Text
pname String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" is found in JSON value, but it is not mentioned in Swagger schema"
validateEnum :: Value -> Validation Schema ()
validateEnum :: Value -> Validation Schema ()
validateEnum Value
val = do
Lens' Schema (Maybe [Value])
-> ([Value] -> Validation Schema ()) -> Validation Schema ()
forall s a.
Lens' s (Maybe a) -> (a -> Validation s ()) -> Validation s ()
check (Maybe [Value] -> f (Maybe [Value])) -> Schema -> f Schema
forall s a. HasEnum s a => Lens' s a
Lens' Schema (Maybe [Value])
enum_ (([Value] -> Validation Schema ()) -> Validation Schema ())
-> ([Value] -> Validation Schema ()) -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$ \[Value]
xs ->
Bool -> Validation Schema () -> Validation Schema ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Value
val Value -> [Value] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [Value]
xs) (Validation Schema () -> Validation Schema ())
-> Validation Schema () -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$
String -> Validation Schema ()
forall schema a. String -> Validation schema a
invalid (String
"expected one of " String -> String -> String
forall a. [a] -> [a] -> [a]
++ ByteString -> String
forall a. Show a => a -> String
show ([Value] -> ByteString
forall a. ToJSON a => a -> ByteString
encode [Value]
xs) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" but got " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Value -> String
forall a. Show a => a -> String
show Value
val)
inferSchemaTypes :: Schema -> [OpenApiType]
inferSchemaTypes :: Schema -> [OpenApiType]
inferSchemaTypes Schema
sch = Schema -> [OpenApiType]
inferParamSchemaTypes Schema
sch [OpenApiType] -> [OpenApiType] -> [OpenApiType]
forall a. [a] -> [a] -> [a]
++
[ OpenApiType
OpenApiObject | ((Schema -> Bool) -> Bool) -> [Schema -> Bool] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ((Schema -> Bool) -> Schema -> Bool
forall a b. (a -> b) -> a -> b
$ Schema
sch)
[ Getting Any Schema AdditionalProperties -> Schema -> Bool
forall s a. Getting Any s a -> s -> Bool
has ((Maybe AdditionalProperties
-> Const Any (Maybe AdditionalProperties))
-> Schema -> Const Any Schema
forall s a. HasAdditionalProperties s a => Lens' s a
Lens' Schema (Maybe AdditionalProperties)
additionalProperties((Maybe AdditionalProperties
-> Const Any (Maybe AdditionalProperties))
-> Schema -> Const Any Schema)
-> ((AdditionalProperties -> Const Any AdditionalProperties)
-> Maybe AdditionalProperties
-> Const Any (Maybe AdditionalProperties))
-> Getting Any Schema AdditionalProperties
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(AdditionalProperties -> Const Any AdditionalProperties)
-> Maybe AdditionalProperties
-> Const Any (Maybe AdditionalProperties)
forall a b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Maybe a) (f (Maybe b))
_Just)
, Getting Any Schema Integer -> Schema -> Bool
forall s a. Getting Any s a -> s -> Bool
has ((Maybe Integer -> Const Any (Maybe Integer))
-> Schema -> Const Any Schema
forall s a. HasMaxProperties s a => Lens' s a
Lens' Schema (Maybe Integer)
maxProperties((Maybe Integer -> Const Any (Maybe Integer))
-> Schema -> Const Any Schema)
-> ((Integer -> Const Any Integer)
-> Maybe Integer -> Const Any (Maybe Integer))
-> Getting Any Schema Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Integer -> Const Any Integer)
-> Maybe Integer -> Const Any (Maybe Integer)
forall a b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Maybe a) (f (Maybe b))
_Just)
, Getting Any Schema Integer -> Schema -> Bool
forall s a. Getting Any s a -> s -> Bool
has ((Maybe Integer -> Const Any (Maybe Integer))
-> Schema -> Const Any Schema
forall s a. HasMinProperties s a => Lens' s a
Lens' Schema (Maybe Integer)
minProperties((Maybe Integer -> Const Any (Maybe Integer))
-> Schema -> Const Any Schema)
-> ((Integer -> Const Any Integer)
-> Maybe Integer -> Const Any (Maybe Integer))
-> Getting Any Schema Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Integer -> Const Any Integer)
-> Maybe Integer -> Const Any (Maybe Integer)
forall a b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Maybe a) (f (Maybe b))
_Just)
, Getting Any Schema (Referenced Schema) -> Schema -> Bool
forall s a. Getting Any s a -> s -> Bool
has ((InsOrdHashMap Text (Referenced Schema)
-> Const Any (InsOrdHashMap Text (Referenced Schema)))
-> Schema -> Const Any Schema
forall s a. HasProperties s a => Lens' s a
Lens' Schema (InsOrdHashMap Text (Referenced Schema))
properties((InsOrdHashMap Text (Referenced Schema)
-> Const Any (InsOrdHashMap Text (Referenced Schema)))
-> Schema -> Const Any Schema)
-> ((Referenced Schema -> Const Any (Referenced Schema))
-> InsOrdHashMap Text (Referenced Schema)
-> Const Any (InsOrdHashMap Text (Referenced Schema)))
-> Getting Any Schema (Referenced Schema)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Referenced Schema -> Const Any (Referenced Schema))
-> InsOrdHashMap Text (Referenced Schema)
-> Const Any (InsOrdHashMap Text (Referenced Schema))
forall (f :: * -> *) a. Foldable f => IndexedFold Int (f a) a
IndexedFold
Int (InsOrdHashMap Text (Referenced Schema)) (Referenced Schema)
folded)
, Getting Any Schema Text -> Schema -> Bool
forall s a. Getting Any s a -> s -> Bool
has (([Text] -> Const Any [Text]) -> Schema -> Const Any Schema
forall s a. HasRequired s a => Lens' s a
Lens' Schema [Text]
required(([Text] -> Const Any [Text]) -> Schema -> Const Any Schema)
-> ((Text -> Const Any Text) -> [Text] -> Const Any [Text])
-> Getting Any Schema Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Text -> Const Any Text) -> [Text] -> Const Any [Text]
forall (f :: * -> *) a. Foldable f => IndexedFold Int (f a) a
IndexedFold Int [Text] Text
folded) ] ]
inferParamSchemaTypes :: Schema -> [OpenApiType]
inferParamSchemaTypes :: Schema -> [OpenApiType]
inferParamSchemaTypes Schema
sch = [[OpenApiType]] -> [OpenApiType]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ [ OpenApiType
OpenApiArray | ((Schema -> Bool) -> Bool) -> [Schema -> Bool] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ((Schema -> Bool) -> Schema -> Bool
forall a b. (a -> b) -> a -> b
$ Schema
sch)
[ Getting Any Schema OpenApiItems -> Schema -> Bool
forall s a. Getting Any s a -> s -> Bool
has ((Maybe OpenApiItems -> Const Any (Maybe OpenApiItems))
-> Schema -> Const Any Schema
forall s a. HasItems s a => Lens' s a
Lens' Schema (Maybe OpenApiItems)
items((Maybe OpenApiItems -> Const Any (Maybe OpenApiItems))
-> Schema -> Const Any Schema)
-> ((OpenApiItems -> Const Any OpenApiItems)
-> Maybe OpenApiItems -> Const Any (Maybe OpenApiItems))
-> Getting Any Schema OpenApiItems
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(OpenApiItems -> Const Any OpenApiItems)
-> Maybe OpenApiItems -> Const Any (Maybe OpenApiItems)
forall a b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Maybe a) (f (Maybe b))
_Just)
, Getting Any Schema Integer -> Schema -> Bool
forall s a. Getting Any s a -> s -> Bool
has ((Maybe Integer -> Const Any (Maybe Integer))
-> Schema -> Const Any Schema
forall s a. HasMaxItems s a => Lens' s a
Lens' Schema (Maybe Integer)
maxItems((Maybe Integer -> Const Any (Maybe Integer))
-> Schema -> Const Any Schema)
-> ((Integer -> Const Any Integer)
-> Maybe Integer -> Const Any (Maybe Integer))
-> Getting Any Schema Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Integer -> Const Any Integer)
-> Maybe Integer -> Const Any (Maybe Integer)
forall a b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Maybe a) (f (Maybe b))
_Just)
, Getting Any Schema Integer -> Schema -> Bool
forall s a. Getting Any s a -> s -> Bool
has ((Maybe Integer -> Const Any (Maybe Integer))
-> Schema -> Const Any Schema
forall s a. HasMinItems s a => Lens' s a
Lens' Schema (Maybe Integer)
minItems((Maybe Integer -> Const Any (Maybe Integer))
-> Schema -> Const Any Schema)
-> ((Integer -> Const Any Integer)
-> Maybe Integer -> Const Any (Maybe Integer))
-> Getting Any Schema Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Integer -> Const Any Integer)
-> Maybe Integer -> Const Any (Maybe Integer)
forall a b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Maybe a) (f (Maybe b))
_Just)
, Getting Any Schema Bool -> Schema -> Bool
forall s a. Getting Any s a -> s -> Bool
has ((Maybe Bool -> Const Any (Maybe Bool))
-> Schema -> Const Any Schema
forall s a. HasUniqueItems s a => Lens' s a
Lens' Schema (Maybe Bool)
uniqueItems((Maybe Bool -> Const Any (Maybe Bool))
-> Schema -> Const Any Schema)
-> ((Bool -> Const Any Bool)
-> Maybe Bool -> Const Any (Maybe Bool))
-> Getting Any Schema Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Bool -> Const Any Bool) -> Maybe Bool -> Const Any (Maybe Bool)
forall a b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Maybe a) (f (Maybe b))
_Just) ] ]
, [ OpenApiType
OpenApiInteger | ((Schema -> Bool) -> Bool) -> [Schema -> Bool] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ((Schema -> Bool) -> Schema -> Bool
forall a b. (a -> b) -> a -> b
$ Schema
sch)
[ Getting Any Schema Bool -> Schema -> Bool
forall s a. Getting Any s a -> s -> Bool
has ((Maybe Bool -> Const Any (Maybe Bool))
-> Schema -> Const Any Schema
forall s a. HasExclusiveMaximum s a => Lens' s a
Lens' Schema (Maybe Bool)
exclusiveMaximum((Maybe Bool -> Const Any (Maybe Bool))
-> Schema -> Const Any Schema)
-> ((Bool -> Const Any Bool)
-> Maybe Bool -> Const Any (Maybe Bool))
-> Getting Any Schema Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Bool -> Const Any Bool) -> Maybe Bool -> Const Any (Maybe Bool)
forall a b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Maybe a) (f (Maybe b))
_Just)
, Getting Any Schema Bool -> Schema -> Bool
forall s a. Getting Any s a -> s -> Bool
has ((Maybe Bool -> Const Any (Maybe Bool))
-> Schema -> Const Any Schema
forall s a. HasExclusiveMinimum s a => Lens' s a
Lens' Schema (Maybe Bool)
exclusiveMinimum((Maybe Bool -> Const Any (Maybe Bool))
-> Schema -> Const Any Schema)
-> ((Bool -> Const Any Bool)
-> Maybe Bool -> Const Any (Maybe Bool))
-> Getting Any Schema Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Bool -> Const Any Bool) -> Maybe Bool -> Const Any (Maybe Bool)
forall a b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Maybe a) (f (Maybe b))
_Just)
, Getting Any Schema Scientific -> Schema -> Bool
forall s a. Getting Any s a -> s -> Bool
has ((Maybe Scientific -> Const Any (Maybe Scientific))
-> Schema -> Const Any Schema
forall s a. HasMaximum s a => Lens' s a
Lens' Schema (Maybe Scientific)
maximum_((Maybe Scientific -> Const Any (Maybe Scientific))
-> Schema -> Const Any Schema)
-> ((Scientific -> Const Any Scientific)
-> Maybe Scientific -> Const Any (Maybe Scientific))
-> Getting Any Schema Scientific
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Scientific -> Const Any Scientific)
-> Maybe Scientific -> Const Any (Maybe Scientific)
forall a b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Maybe a) (f (Maybe b))
_Just)
, Getting Any Schema Scientific -> Schema -> Bool
forall s a. Getting Any s a -> s -> Bool
has ((Maybe Scientific -> Const Any (Maybe Scientific))
-> Schema -> Const Any Schema
forall s a. HasMinimum s a => Lens' s a
Lens' Schema (Maybe Scientific)
minimum_((Maybe Scientific -> Const Any (Maybe Scientific))
-> Schema -> Const Any Schema)
-> ((Scientific -> Const Any Scientific)
-> Maybe Scientific -> Const Any (Maybe Scientific))
-> Getting Any Schema Scientific
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Scientific -> Const Any Scientific)
-> Maybe Scientific -> Const Any (Maybe Scientific)
forall a b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Maybe a) (f (Maybe b))
_Just)
, Getting Any Schema Scientific -> Schema -> Bool
forall s a. Getting Any s a -> s -> Bool
has ((Maybe Scientific -> Const Any (Maybe Scientific))
-> Schema -> Const Any Schema
forall s a. HasMultipleOf s a => Lens' s a
Lens' Schema (Maybe Scientific)
multipleOf((Maybe Scientific -> Const Any (Maybe Scientific))
-> Schema -> Const Any Schema)
-> ((Scientific -> Const Any Scientific)
-> Maybe Scientific -> Const Any (Maybe Scientific))
-> Getting Any Schema Scientific
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Scientific -> Const Any Scientific)
-> Maybe Scientific -> Const Any (Maybe Scientific)
forall a b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Maybe a) (f (Maybe b))
_Just) ] ]
, [ OpenApiType
OpenApiString | ((Schema -> Bool) -> Bool) -> [Schema -> Bool] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ((Schema -> Bool) -> Schema -> Bool
forall a b. (a -> b) -> a -> b
$ Schema
sch)
[ Getting Any Schema Integer -> Schema -> Bool
forall s a. Getting Any s a -> s -> Bool
has ((Maybe Integer -> Const Any (Maybe Integer))
-> Schema -> Const Any Schema
forall s a. HasMaxLength s a => Lens' s a
Lens' Schema (Maybe Integer)
maxLength((Maybe Integer -> Const Any (Maybe Integer))
-> Schema -> Const Any Schema)
-> ((Integer -> Const Any Integer)
-> Maybe Integer -> Const Any (Maybe Integer))
-> Getting Any Schema Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Integer -> Const Any Integer)
-> Maybe Integer -> Const Any (Maybe Integer)
forall a b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Maybe a) (f (Maybe b))
_Just)
, Getting Any Schema Integer -> Schema -> Bool
forall s a. Getting Any s a -> s -> Bool
has ((Maybe Integer -> Const Any (Maybe Integer))
-> Schema -> Const Any Schema
forall s a. HasMinLength s a => Lens' s a
Lens' Schema (Maybe Integer)
minLength((Maybe Integer -> Const Any (Maybe Integer))
-> Schema -> Const Any Schema)
-> ((Integer -> Const Any Integer)
-> Maybe Integer -> Const Any (Maybe Integer))
-> Getting Any Schema Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Integer -> Const Any Integer)
-> Maybe Integer -> Const Any (Maybe Integer)
forall a b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Maybe a) (f (Maybe b))
_Just)
, Getting Any Schema Text -> Schema -> Bool
forall s a. Getting Any s a -> s -> Bool
has ((Maybe Text -> Const Any (Maybe Text))
-> Schema -> Const Any Schema
forall s a. HasPattern s a => Lens' s a
Lens' Schema (Maybe Text)
pattern((Maybe Text -> Const Any (Maybe Text))
-> Schema -> Const Any Schema)
-> ((Text -> Const Any Text)
-> Maybe Text -> Const Any (Maybe Text))
-> Getting Any Schema Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Text -> Const Any Text) -> Maybe Text -> Const Any (Maybe Text)
forall a b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Maybe a) (f (Maybe b))
_Just) ] ]
]
validateSchemaType :: Value -> Validation Schema ()
validateSchemaType :: Value -> Validation Schema ()
validateSchemaType Value
val = (Schema -> Validation Schema ()) -> Validation Schema ()
forall s a. (s -> Validation s a) -> Validation s a
withSchema ((Schema -> Validation Schema ()) -> Validation Schema ())
-> (Schema -> Validation Schema ()) -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$ \Schema
sch ->
case Schema
sch of
(Getting
(Maybe [Referenced Schema]) Schema (Maybe [Referenced Schema])
-> Schema -> Maybe [Referenced Schema]
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting
(Maybe [Referenced Schema]) Schema (Maybe [Referenced Schema])
forall s a. HasOneOf s a => Lens' s a
Lens' Schema (Maybe [Referenced Schema])
oneOf -> Just [Referenced Schema]
variants) -> do
[Bool]
res <- [Referenced Schema]
-> (Referenced Schema -> Validation Schema Bool)
-> Validation Schema [Bool]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [Referenced Schema]
variants ((Referenced Schema -> Validation Schema Bool)
-> Validation Schema [Bool])
-> (Referenced Schema -> Validation Schema Bool)
-> Validation Schema [Bool]
forall a b. (a -> b) -> a -> b
$ \Referenced Schema
var ->
(Bool
True Bool -> Validation Schema () -> Validation Schema Bool
forall a b. a -> Validation Schema b -> Validation Schema a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Referenced Schema -> Value -> Validation Schema ()
forall s. Referenced Schema -> Value -> Validation s ()
validateWithSchemaRef Referenced Schema
var Value
val) Validation Schema Bool
-> Validation Schema Bool -> Validation Schema Bool
forall a.
Validation Schema a -> Validation Schema a -> Validation Schema a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Bool -> Validation Schema Bool
forall a. a -> Validation Schema a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False)
case [Bool] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([Bool] -> Int) -> [Bool] -> Int
forall a b. (a -> b) -> a -> b
$ (Bool -> Bool) -> [Bool] -> [Bool]
forall a. (a -> Bool) -> [a] -> [a]
filter Bool -> Bool
forall a. a -> a
id [Bool]
res of
Int
0 -> String -> Validation Schema ()
forall schema a. String -> Validation schema a
invalid (String -> Validation Schema ()) -> String -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$ String
"Value not valid under any of 'oneOf' schemas: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Value -> String
forall a. Show a => a -> String
show Value
val
Int
1 -> Validation Schema ()
forall schema. Validation schema ()
valid
Int
_ -> String -> Validation Schema ()
forall schema a. String -> Validation schema a
invalid (String -> Validation Schema ()) -> String -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$ String
"Value matches more than one of 'oneOf' schemas: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Value -> String
forall a. Show a => a -> String
show Value
val
(Getting
(Maybe [Referenced Schema]) Schema (Maybe [Referenced Schema])
-> Schema -> Maybe [Referenced Schema]
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting
(Maybe [Referenced Schema]) Schema (Maybe [Referenced Schema])
forall s a. HasAllOf s a => Lens' s a
Lens' Schema (Maybe [Referenced Schema])
allOf -> Just [Referenced Schema]
variants) -> do
[Referenced Schema]
-> (Referenced Schema -> Validation Schema ())
-> Validation Schema ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [Referenced Schema]
variants ((Referenced Schema -> Validation Schema ())
-> Validation Schema ())
-> (Referenced Schema -> Validation Schema ())
-> Validation Schema ()
forall a b. (a -> b) -> a -> b
$ \Referenced Schema
var ->
Referenced Schema -> Value -> Validation Schema ()
forall s. Referenced Schema -> Value -> Validation s ()
validateWithSchemaRef Referenced Schema
var Value
val
Schema
_ ->
case (Schema
sch Schema
-> Getting (Maybe OpenApiType) Schema (Maybe OpenApiType)
-> Maybe OpenApiType
forall s a. s -> Getting a s a -> a
^. Getting (Maybe OpenApiType) Schema (Maybe OpenApiType)
forall s a. HasType s a => Lens' s a
Lens' Schema (Maybe OpenApiType)
type_, Value
val) of
(Just OpenApiType
OpenApiNull, Value
Null) -> Validation Schema ()
forall schema. Validation schema ()
valid
(Just OpenApiType
OpenApiBoolean, Bool Bool
_) -> Validation Schema ()
forall schema. Validation schema ()
valid
(Just OpenApiType
OpenApiInteger, Number Scientific
n) -> Scientific -> Validation Schema ()
validateInteger Scientific
n
(Just OpenApiType
OpenApiNumber, Number Scientific
n) -> Scientific -> Validation Schema ()
validateNumber Scientific
n
(Just OpenApiType
OpenApiString, String Text
s) -> Text -> Validation Schema ()
validateString Text
s
(Just OpenApiType
OpenApiArray, Array Vector Value
xs) -> Vector Value -> Validation Schema ()
validateArray Vector Value
xs
(Just OpenApiType
OpenApiObject, Object KeyMap Value
o) -> KeyMap Value -> Validation Schema ()
validateObject KeyMap Value
o
(Maybe OpenApiType
Nothing, Value
Null) -> Validation Schema ()
forall schema. Validation schema ()
valid
(Maybe OpenApiType
Nothing, Bool Bool
_) -> Validation Schema ()
forall schema. Validation schema ()
valid
(Maybe OpenApiType
Nothing, Number Scientific
n) -> Scientific -> Validation Schema ()
validateNumber Scientific
n
(Maybe OpenApiType
Nothing, String Text
s) -> Text -> Validation Schema ()
validateString Text
s
(Maybe OpenApiType
Nothing, Array Vector Value
xs) -> Vector Value -> Validation Schema ()
validateArray Vector Value
xs
(Maybe OpenApiType
Nothing, Object KeyMap Value
o) -> KeyMap Value -> Validation Schema ()
validateObject KeyMap Value
o
(Maybe OpenApiType, Value)
bad -> String -> Validation Schema ()
forall schema a. String -> Validation schema a
invalid (String -> Validation Schema ()) -> String -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$ String
"expected JSON value of type " String -> String -> String
forall a. [a] -> [a] -> [a]
++ (Maybe OpenApiType, Value) -> String
showType (Maybe OpenApiType, Value)
bad
validateParamSchemaType :: Value -> Validation Schema ()
validateParamSchemaType :: Value -> Validation Schema ()
validateParamSchemaType Value
val = (Schema -> Validation Schema ()) -> Validation Schema ()
forall s a. (s -> Validation s a) -> Validation s a
withSchema ((Schema -> Validation Schema ()) -> Validation Schema ())
-> (Schema -> Validation Schema ()) -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$ \Schema
sch ->
case (Schema
sch Schema
-> Getting (Maybe OpenApiType) Schema (Maybe OpenApiType)
-> Maybe OpenApiType
forall s a. s -> Getting a s a -> a
^. Getting (Maybe OpenApiType) Schema (Maybe OpenApiType)
forall s a. HasType s a => Lens' s a
Lens' Schema (Maybe OpenApiType)
type_, Value
val) of
(Just OpenApiType
OpenApiBoolean, Bool Bool
_) -> Validation Schema ()
forall schema. Validation schema ()
valid
(Just OpenApiType
OpenApiInteger, Number Scientific
n) -> Scientific -> Validation Schema ()
validateInteger Scientific
n
(Just OpenApiType
OpenApiNumber, Number Scientific
n) -> Scientific -> Validation Schema ()
validateNumber Scientific
n
(Just OpenApiType
OpenApiString, String Text
s) -> Text -> Validation Schema ()
validateString Text
s
(Just OpenApiType
OpenApiArray, Array Vector Value
xs) -> Vector Value -> Validation Schema ()
validateArray Vector Value
xs
(Maybe OpenApiType
Nothing, Bool Bool
_) -> Validation Schema ()
forall schema. Validation schema ()
valid
(Maybe OpenApiType
Nothing, Number Scientific
n) -> Scientific -> Validation Schema ()
validateNumber Scientific
n
(Maybe OpenApiType
Nothing, String Text
s) -> Text -> Validation Schema ()
validateString Text
s
(Maybe OpenApiType
Nothing, Array Vector Value
xs) -> Vector Value -> Validation Schema ()
validateArray Vector Value
xs
(Maybe OpenApiType, Value)
bad -> String -> Validation Schema ()
forall schema a. String -> Validation schema a
invalid (String -> Validation Schema ()) -> String -> Validation Schema ()
forall a b. (a -> b) -> a -> b
$ String
"expected JSON value of type " String -> String -> String
forall a. [a] -> [a] -> [a]
++ (Maybe OpenApiType, Value) -> String
showType (Maybe OpenApiType, Value)
bad
showType :: (Maybe OpenApiType, Value) -> String
showType :: (Maybe OpenApiType, Value) -> String
showType (Just OpenApiType
ty, Value
_) = OpenApiType -> String
forall a. Show a => a -> String
show OpenApiType
ty
showType (Maybe OpenApiType
Nothing, Value
Null) = String
"OpenApiNull"
showType (Maybe OpenApiType
Nothing, Bool Bool
_) = String
"OpenApiBoolean"
showType (Maybe OpenApiType
Nothing, Number Scientific
_) = String
"OpenApiNumber"
showType (Maybe OpenApiType
Nothing, String Text
_) = String
"OpenApiString"
showType (Maybe OpenApiType
Nothing, Array Vector Value
_) = String
"OpenApiArray"
showType (Maybe OpenApiType
Nothing, Object KeyMap Value
_) = String
"OpenApiObject"