swagger2-2.4: Swagger 2.0 data model

Copyright(c) 2015 GetShopTV
LicenseBSD3
MaintainerNickolay Kudasov <nickolay@getshoptv.com>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Data.Swagger.Internal.Schema.Validation

Description

Validate JSON values with Swagger Schema.

Synopsis

Documentation

validateToJSON :: forall a. (ToJSON a, ToSchema a) => a -> [ValidationError] Source #

Validate ToJSON instance matches ToSchema for a given value. This can be used with QuickCheck to ensure those instances are coherent:

validateToJSON (x :: Int) == []

NOTE: validateToJSON does not perform string pattern validation. See validateToJSONWithPatternChecker.

validateToJSONWithPatternChecker :: forall a. (ToJSON a, ToSchema a) => (Pattern -> Text -> Bool) -> a -> [ValidationError] Source #

Validate ToJSON instance matches ToSchema for a given value and pattern checker. This can be used with QuickCheck to ensure those instances are coherent.

For validation without patterns see validateToJSON.

validateJSON :: Definitions Schema -> Schema -> Value -> [ValidationError] Source #

Validate JSON Value against Swagger Schema.

validateJSON mempty (toSchema (Proxy :: Proxy Int)) (toJSON (x :: Int)) == []

NOTE: validateJSON does not perform string pattern validation. See validateJSONWithPatternChecker.

validateJSONWithPatternChecker :: (Pattern -> Text -> Bool) -> Definitions Schema -> Schema -> Value -> [ValidationError] Source #

Validate JSON Value agains Swagger ToSchema for a given value and pattern checker.

For validation without patterns see validateJSON.

type ValidationError = String Source #

Validation error message.

data Result a Source #

Validation result type.

Constructors

Failed [ValidationError]

Validation failed with a list of error messages.

Passed a

Validation passed.

Instances
Monad Result Source # 
Instance details

Defined in Data.Swagger.Internal.Schema.Validation

Methods

(>>=) :: Result a -> (a -> Result b) -> Result b #

(>>) :: Result a -> Result b -> Result b #

return :: a -> Result a #

fail :: String -> Result a #

Functor Result Source # 
Instance details

Defined in Data.Swagger.Internal.Schema.Validation

Methods

fmap :: (a -> b) -> Result a -> Result b #

(<$) :: a -> Result b -> Result a #

Applicative Result Source # 
Instance details

Defined in Data.Swagger.Internal.Schema.Validation

Methods

pure :: a -> Result a #

(<*>) :: Result (a -> b) -> Result a -> Result b #

liftA2 :: (a -> b -> c) -> Result a -> Result b -> Result c #

(*>) :: Result a -> Result b -> Result b #

(<*) :: Result a -> Result b -> Result a #

Alternative Result Source # 
Instance details

Defined in Data.Swagger.Internal.Schema.Validation

Methods

empty :: Result a #

(<|>) :: Result a -> Result a -> Result a #

some :: Result a -> Result [a] #

many :: Result a -> Result [a] #

Eq a => Eq (Result a) Source # 
Instance details

Defined in Data.Swagger.Internal.Schema.Validation

Methods

(==) :: Result a -> Result a -> Bool #

(/=) :: Result a -> Result a -> Bool #

Show a => Show (Result a) Source # 
Instance details

Defined in Data.Swagger.Internal.Schema.Validation

Methods

showsPrec :: Int -> Result a -> ShowS #

show :: Result a -> String #

showList :: [Result a] -> ShowS #

data Config Source #

Validation configuration.

Constructors

Config 

Fields

defaultConfig :: Config Source #

Default Config:

defaultConfig = Config
  { configPatternChecker = \_pattern _str -> True
  , configDefinitions    = mempty
  }

newtype Validation s a Source #

Value validation.

Constructors

Validation 

Fields

Instances
Profunctor Validation Source # 
Instance details

Defined in Data.Swagger.Internal.Schema.Validation

Methods

dimap :: (a -> b) -> (c -> d) -> Validation b c -> Validation a d #

lmap :: (a -> b) -> Validation b c -> Validation a c #

rmap :: (b -> c) -> Validation a b -> Validation a c #

(#.) :: Coercible c b => q b c -> Validation a b -> Validation a c #

(.#) :: Coercible b a => Validation b c -> q a b -> Validation a c #

Choice Validation Source # 
Instance details

Defined in Data.Swagger.Internal.Schema.Validation

Methods

left' :: Validation a b -> Validation (Either a c) (Either b c) #

right' :: Validation a b -> Validation (Either c a) (Either c b) #

Monad (Validation s) Source # 
Instance details

Defined in Data.Swagger.Internal.Schema.Validation

Methods

(>>=) :: Validation s a -> (a -> Validation s b) -> Validation s b #

(>>) :: Validation s a -> Validation s b -> Validation s b #

return :: a -> Validation s a #

fail :: String -> Validation s a #

Functor (Validation s) Source # 
Instance details

Defined in Data.Swagger.Internal.Schema.Validation

Methods

fmap :: (a -> b) -> Validation s a -> Validation s b #

(<$) :: a -> Validation s b -> Validation s a #

Applicative (Validation schema) Source # 
Instance details

Defined in Data.Swagger.Internal.Schema.Validation

Methods

pure :: a -> Validation schema a #

(<*>) :: Validation schema (a -> b) -> Validation schema a -> Validation schema b #

liftA2 :: (a -> b -> c) -> Validation schema a -> Validation schema b -> Validation schema c #

(*>) :: Validation schema a -> Validation schema b -> Validation schema b #

(<*) :: Validation schema a -> Validation schema b -> Validation schema a #

Alternative (Validation schema) Source # 
Instance details

Defined in Data.Swagger.Internal.Schema.Validation

Methods

empty :: Validation schema a #

(<|>) :: Validation schema a -> Validation schema a -> Validation schema a #

some :: Validation schema a -> Validation schema [a] #

many :: Validation schema a -> Validation schema [a] #

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.

validateWithSchema :: Value -> Validation Schema () Source #

Validate JSON Value with Swagger Schema.

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]