Copyright | (c) 2015 GetShopTV |
---|---|
License | BSD3 |
Maintainer | Nickolay Kudasov <nickolay@getshoptv.com> |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Validate JSON values with Swagger Schema.
Synopsis
- validatePrettyToJSON :: forall a. (ToJSON a, ToSchema a) => a -> Maybe String
- validateToJSON :: forall a. (ToJSON a, ToSchema a) => a -> [ValidationError]
- validateToJSONWithPatternChecker :: forall a. (ToJSON a, ToSchema a) => (Pattern -> Text -> Bool) -> a -> [ValidationError]
- renderValidationErrors :: forall a. (ToJSON a, ToSchema a) => (a -> [ValidationError]) -> a -> Maybe String
- validateJSON :: Definitions Schema -> Schema -> Value -> [ValidationError]
- validateJSONWithPatternChecker :: (Pattern -> Text -> Bool) -> Definitions Schema -> Schema -> Value -> [ValidationError]
- type ValidationError = String
- data Result a
- = Failed [ValidationError]
- | Passed a
- data Config = Config {}
- defaultConfig :: Config
- newtype Validation s a = Validation {
- runValidation :: Config -> s -> Result a
- withConfig :: (Config -> Validation s a) -> Validation s a
- withSchema :: (s -> Validation s a) -> Validation s a
- invalid :: String -> Validation schema a
- valid :: Validation schema ()
- checkMissing :: Validation s () -> Lens' s (Maybe a) -> (a -> Validation s ()) -> Validation s ()
- check :: Lens' s (Maybe a) -> (a -> Validation s ()) -> Validation s ()
- sub :: t -> Validation t a -> Validation s a
- sub_ :: Getting a s a -> Validation a r -> Validation s r
- withRef :: Reference -> (Schema -> Validation s a) -> Validation s a
- validateWithSchemaRef :: Referenced Schema -> Value -> Validation s ()
- validateWithSchema :: Value -> Validation Schema ()
- validateWithParamSchema :: Value -> Validation (ParamSchema t) ()
- validateInteger :: Scientific -> Validation (ParamSchema t) ()
- validateNumber :: Scientific -> Validation (ParamSchema t) ()
- validateString :: Text -> Validation (ParamSchema t) ()
- validateArray :: Vector Value -> Validation (ParamSchema t) ()
- validateObject :: HashMap Text Value -> Validation Schema ()
- validateEnum :: Value -> Validation (ParamSchema t) ()
- inferSchemaTypes :: Schema -> [SwaggerType 'SwaggerKindSchema]
- inferParamSchemaTypes :: ParamSchema t -> [SwaggerType t]
- validateSchemaType :: Value -> Validation Schema ()
- validateParamSchemaType :: Value -> Validation (ParamSchema t) ()
- showType :: (Maybe (SwaggerType t), Value) -> String
Documentation
validatePrettyToJSON :: forall a. (ToJSON a, ToSchema a) => a -> Maybe String Source #
Validate
instance matches ToJSON
for a given value.
This can be used with QuickCheck to ensure those instances are coherent:ToSchema
validateToJSON (x :: Int) == []
NOTE:
does not perform string pattern validation.
See validateToJSON
.validateToJSONWithPatternChecker
See renderValidationErrors
on how the output is structured.
validateToJSON :: forall a. (ToJSON a, ToSchema a) => a -> [ValidationError] Source #
Variant of validatePrettyToJSON
with typed output.
validateToJSONWithPatternChecker :: forall a. (ToJSON a, ToSchema a) => (Pattern -> Text -> Bool) -> a -> [ValidationError] Source #
Validate
instance matches ToJSON
for a given value and pattern checker.
This can be used with QuickCheck to ensure those instances are coherent.ToSchema
For validation without patterns see
. See also:
validateToJSON
renderValidationErrors
.
renderValidationErrors :: forall a. (ToJSON a, ToSchema a) => (a -> [ValidationError]) -> a -> Maybe String Source #
Pretty print validation errors
together with actual JSON and Swagger Schema
(using encodePretty
).
>>>
import Data.Aeson as Aeson
>>>
import Data.Foldable (traverse_)
>>>
import GHC.Generics
>>>
data Phone = Phone { value :: String } deriving (Generic)
>>>
data Person = Person { name :: String, phone :: Phone } deriving (Generic)
>>>
instance ToJSON Person where toJSON p = object [ "name" Aeson..= name p ]
>>>
instance ToSchema Phone
>>>
instance ToSchema Person
>>>
let person = Person { name = "John", phone = Phone "123456" }
>>>
traverse_ putStrLn $ renderValidationErrors validateToJSON person
Validation against the schema fails: * property "phone" is required, but not found in "{\"name\":\"John\"}" JSON value: { "name": "John" } Swagger Schema: { "properties": { "name": { "type": "string" }, "phone": { "$ref": "#/definitions/Phone" } }, "required": [ "name", "phone" ], "type": "object" } Swagger Description Context: { "Phone": { "properties": { "value": { "type": "string" } }, "required": [ "value" ], "type": "object" } }
validateJSON :: Definitions Schema -> Schema -> Value -> [ValidationError] Source #
Validate JSON
against Swagger Value
.Schema
validateJSON mempty (toSchema (Proxy :: Proxy Int)) (toJSON (x :: Int)) == []
NOTE:
does not perform string pattern validation.
See validateJSON
.validateJSONWithPatternChecker
validateJSONWithPatternChecker :: (Pattern -> Text -> Bool) -> Definitions Schema -> Schema -> Value -> [ValidationError] Source #
Validate JSON
agains Swagger Value
for a given value and pattern checker.ToSchema
For validation without patterns see
.validateJSON
type ValidationError = String Source #
Validation error message.
Validation result type.
Failed [ValidationError] | Validation failed with a list of error messages. |
Passed a | Validation passed. |
Validation configuration.
Config | |
|
defaultConfig :: Config Source #
Default
:Config
defaultConfig =Config
{configPatternChecker
= \_pattern _str -> True ,configDefinitions
= mempty }
newtype Validation s a Source #
Value validation.
Validation | |
|
Instances
withConfig :: (Config -> Validation s a) -> Validation s a Source #
withSchema :: (s -> Validation s a) -> Validation s a Source #
invalid :: String -> Validation schema a Source #
Issue an error message.
valid :: Validation schema () Source #
Validation passed.
checkMissing :: Validation s () -> Lens' s (Maybe a) -> (a -> Validation s ()) -> Validation s () Source #
Validate schema's property given a lens into that property and property checker.
check :: Lens' s (Maybe a) -> (a -> Validation s ()) -> Validation s () Source #
Validate schema's property given a lens into that property and property checker. If property is missing in schema, consider it valid.
sub :: t -> Validation t a -> Validation s a Source #
Validate same value with different schema.
sub_ :: Getting a s a -> Validation a r -> Validation s r Source #
Validate same value with a part of the original schema.
withRef :: Reference -> (Schema -> Validation s a) -> Validation s a Source #
Validate value against a schema given schema reference and validation function.
validateWithSchemaRef :: Referenced Schema -> Value -> Validation s () Source #
validateWithSchema :: Value -> Validation Schema () Source #
validateWithParamSchema :: Value -> Validation (ParamSchema t) () Source #
Validate JSON
with Swagger Value
.ParamSchema
validateInteger :: Scientific -> Validation (ParamSchema t) () Source #
validateNumber :: Scientific -> Validation (ParamSchema t) () Source #
validateString :: Text -> Validation (ParamSchema t) () Source #
validateArray :: Vector Value -> Validation (ParamSchema t) () Source #
validateObject :: HashMap Text Value -> Validation Schema () Source #
validateEnum :: Value -> Validation (ParamSchema t) () Source #
inferSchemaTypes :: Schema -> [SwaggerType 'SwaggerKindSchema] Source #
Infer schema type based on used properties.
This is like inferParamSchemaTypes
, but also works for objects:
>>>
inferSchemaTypes <$> decode "{\"minProperties\": 1}"
Just [SwaggerObject]
inferParamSchemaTypes :: ParamSchema t -> [SwaggerType t] Source #
Infer schema type based on used properties.
>>>
inferSchemaTypes <$> decode "{\"minLength\": 2}"
Just [SwaggerString]
>>>
inferSchemaTypes <$> decode "{\"maxItems\": 0}"
Just [SwaggerArray]
From numeric properties SwaggerInteger
type is inferred.
If you want SwaggerNumber
instead, you must specify it explicitly.
>>>
inferSchemaTypes <$> decode "{\"minimum\": 1}"
Just [SwaggerInteger]
validateSchemaType :: Value -> Validation Schema () Source #
validateParamSchemaType :: Value -> Validation (ParamSchema t) () Source #