hjsonschema-1.6.3: JSON Schema library

Safe HaskellNone
LanguageHaskell2010

JSONSchema.Validator.Draft4.Object

Contents

Synopsis

maxProperties

maxPropertiesVal :: MaxProperties -> HashMap Text Value -> Maybe MaxPropertiesInvalid Source #

The spec requires "maxProperties" to be non-negative.

minProperties

minPropertiesVal :: MinProperties -> HashMap Text Value -> Maybe MinPropertiesInvalid Source #

The spec requires "minProperties" to be non-negative.

required

newtype Required Source #

From the spec:

The value of this keyword MUST be an array.
This array MUST have at least one element.
Elements of this array MUST be strings, and MUST be unique.

Constructors

Required 

Fields

dependencies

data Dependency schema Source #

Instances

Eq schema => Eq (Dependency schema) Source # 

Methods

(==) :: Dependency schema -> Dependency schema -> Bool #

(/=) :: Dependency schema -> Dependency schema -> Bool #

Show schema => Show (Dependency schema) Source # 

Methods

showsPrec :: Int -> Dependency schema -> ShowS #

show :: Dependency schema -> String #

showList :: [Dependency schema] -> ShowS #

Arbitrary schema => Arbitrary (Dependency schema) Source # 

Methods

arbitrary :: Gen (Dependency schema) #

shrink :: Dependency schema -> [Dependency schema] #

ToJSON schema => ToJSON (Dependency schema) Source # 

Methods

toJSON :: Dependency schema -> Value #

toEncoding :: Dependency schema -> Encoding #

toJSONList :: [Dependency schema] -> Value #

toEncodingList :: [Dependency schema] -> Encoding #

FromJSON schema => FromJSON (Dependency schema) Source # 

Methods

parseJSON :: Value -> Parser (Dependency schema) #

parseJSONList :: Value -> Parser [Dependency schema] #

dependenciesVal :: forall err schema. (schema -> Value -> [err]) -> DependenciesValidator schema -> HashMap Text Value -> Maybe (DependenciesInvalid err) Source #

From the spec: http://json-schema.org/latest/json-schema-validation.html#anchor70

This keyword's value MUST be an object.
Each value of this object MUST be either an object or an array.

If the value is an object, it MUST be a valid JSON Schema.
This is called a schema dependency.

If the value is an array, it MUST have at least one element.
Each element MUST be a string, and elements in the array MUST be unique.
This is called a property dependency.

data PropertiesRelated schema Source #

Constructors

PropertiesRelated 

Fields

Instances

Eq schema => Eq (PropertiesRelated schema) Source # 

Methods

(==) :: PropertiesRelated schema -> PropertiesRelated schema -> Bool #

(/=) :: PropertiesRelated schema -> PropertiesRelated schema -> Bool #

Show schema => Show (PropertiesRelated schema) Source # 
FromJSON schema => FromJSON (PropertiesRelated schema) Source # 

newtype Regex Source #

A glorified type alias.

Constructors

Regex 

Fields

Instances

Eq Regex Source # 

Methods

(==) :: Regex -> Regex -> Bool #

(/=) :: Regex -> Regex -> Bool #

Show Regex Source # 

Methods

showsPrec :: Int -> Regex -> ShowS #

show :: Regex -> String #

showList :: [Regex] -> ShowS #

Generic Regex Source # 

Associated Types

type Rep Regex :: * -> * #

Methods

from :: Regex -> Rep Regex x #

to :: Rep Regex x -> Regex #

Hashable Regex Source # 

Methods

hashWithSalt :: Int -> Regex -> Int #

hash :: Regex -> Int #

type Rep Regex Source # 
type Rep Regex = D1 (MetaData "Regex" "JSONSchema.Validator.Draft4.Object.Properties" "hjsonschema-1.6.3-7fJ3ZtAkaGF5swnMLiAgXs" True) (C1 (MetaCons "Regex" PrefixI True) (S1 (MetaSel (Just Symbol "_unRegex") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data APInvalid err Source #

Instances

Eq err => Eq (APInvalid err) Source # 

Methods

(==) :: APInvalid err -> APInvalid err -> Bool #

(/=) :: APInvalid err -> APInvalid err -> Bool #

Show err => Show (APInvalid err) Source # 

Methods

showsPrec :: Int -> APInvalid err -> ShowS #

show :: APInvalid err -> String #

showList :: [APInvalid err] -> ShowS #

propertiesRelatedVal :: forall err schema. (schema -> Value -> [err]) -> PropertiesRelated schema -> HashMap Text Value -> Maybe (PropertiesRelatedInvalid err) Source #

First "properties" and "patternProperties" are run simultaneously on the data, then "additionalProperties" is run on the remainder.

newtype Remaining Source #

Internal.

Constructors

Remaining 

patternAndUnmatched :: forall err schema. (schema -> Value -> [err]) -> HashMap Text schema -> HashMap Text Value -> (HashMap (Regex, Key) [err], Remaining) Source #

Internal.

additionalProperties :: forall err schema. (schema -> Value -> [err]) -> AdditionalProperties schema -> Remaining -> Maybe (APInvalid err) Source #

additionalPropertiesObject :: forall err schema. (schema -> Value -> [err]) -> schema -> Remaining -> Maybe (HashMap Text (NonEmpty err)) Source #

Internal.