hjsonschema-1.6.1: JSON Schema library

Safe HaskellNone
LanguageHaskell2010

JSONSchema.Validator.Draft4.Any

Contents

Synopsis

$ref

newtype Ref Source #

Constructors

Ref 

Fields

Instances

Eq Ref Source # 

Methods

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

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

Show Ref Source # 

Methods

showsPrec :: Int -> Ref -> ShowS #

show :: Ref -> String #

showList :: [Ref] -> ShowS #

FromJSON Ref Source # 

data RefInvalid err Source #

Constructors

RefResolution Text

Indicates a reference that failed to resolve.

NOTE: The language agnostic test suite doesn't specify if this should cause a validation error or should allow data to pass. We choose to return a validation error.

Also note that ideally we would enforce in the type system that any failing references be dealt with before valididation. Then this could be removed entirely.

RefPointerResolution JSONPointerError 
RefLoop Text VisitedSchemas URIAndFragment 
RefInvalid Text Value (NonEmpty err)

Text is the URI and Value is the linked schema.

Instances

Eq err => Eq (RefInvalid err) Source # 

Methods

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

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

Show err => Show (RefInvalid err) Source # 

Methods

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

show :: RefInvalid err -> String #

showList :: [RefInvalid err] -> ShowS #

refVal Source #

Arguments

:: (FromJSON schema, ToJSON schema) 
=> (Text -> Maybe schema)

Look up a schema.

-> (BaseURI -> schema -> BaseURI)

Update scope (needed after moving deeper into nested schemas).

-> (VisitedSchemas -> Scope schema -> schema -> Value -> [err])

Validate data.

-> VisitedSchemas 
-> Scope schema 
-> Ref 
-> Value 
-> Maybe (RefInvalid err) 

getDocument Source #

Arguments

:: (Text -> Maybe schema) 
-> (BaseURI -> schema -> BaseURI) 
-> Scope schema 
-> Maybe Text 
-> Text 
-> Either Text (Scope schema, schema)

Left is the URI of the document we failed to resolve.

resolveFragment :: forall schema. (FromJSON schema, ToJSON schema) => (BaseURI -> schema -> BaseURI) -> Scope schema -> Text -> Either JSONPointerError (Scope schema, schema) Source #

enum

newtype EnumValidator Source #

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

The value of this keyword MUST be an array.
This array MUST have at least one element.
Elements in the array MUST be unique.

NOTE: We don't enforce the uniqueness constraint in the haskell code, but we do in the FromJSON instance.

type

newtype TypeContext Source #

This is separate from TypeValidator so that TypeValidator can be used to write Schema without messing up the FromJSON instance of that data type.

Constructors

TypeContext 

data SchemaType Source #

Instances

Bounded SchemaType Source # 
Enum SchemaType Source # 
Eq SchemaType Source # 
Ord SchemaType Source # 
Show SchemaType Source # 
Generic SchemaType Source # 

Associated Types

type Rep SchemaType :: * -> * #

Arbitrary SchemaType Source # 
ToJSON SchemaType Source # 
FromJSON SchemaType Source # 
type Rep SchemaType Source # 
type Rep SchemaType = D1 (MetaData "SchemaType" "JSONSchema.Validator.Draft4.Any" "hjsonschema-1.6.1-ILl9gxDrDbb26xDwF9VrZ1" False) ((:+:) ((:+:) (C1 (MetaCons "SchemaObject" PrefixI False) U1) ((:+:) (C1 (MetaCons "SchemaArray" PrefixI False) U1) (C1 (MetaCons "SchemaString" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "SchemaNumber" PrefixI False) U1) (C1 (MetaCons "SchemaInteger" PrefixI False) U1)) ((:+:) (C1 (MetaCons "SchemaBoolean" PrefixI False) U1) (C1 (MetaCons "SchemaNull" PrefixI False) U1))))

allOf

newtype AllOf schema Source #

Constructors

AllOf 

Fields

Instances

Eq schema => Eq (AllOf schema) Source # 

Methods

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

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

Show schema => Show (AllOf schema) Source # 

Methods

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

show :: AllOf schema -> String #

showList :: [AllOf schema] -> ShowS #

FromJSON schema => FromJSON (AllOf schema) Source # 

Methods

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

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

newtype AllOfInvalid err Source #

Constructors

AllOfInvalid (NonEmpty (Index, NonEmpty err)) 

Instances

Eq err => Eq (AllOfInvalid err) Source # 

Methods

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

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

Show err => Show (AllOfInvalid err) Source # 

allOfVal :: forall err schema. (schema -> Value -> [err]) -> AllOf schema -> Value -> Maybe (AllOfInvalid err) Source #

anyOf

newtype AnyOf schema Source #

Constructors

AnyOf 

Fields

Instances

Eq schema => Eq (AnyOf schema) Source # 

Methods

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

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

Show schema => Show (AnyOf schema) Source # 

Methods

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

show :: AnyOf schema -> String #

showList :: [AnyOf schema] -> ShowS #

FromJSON schema => FromJSON (AnyOf schema) Source # 

Methods

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

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

newtype AnyOfInvalid err Source #

Constructors

AnyOfInvalid (NonEmpty (Index, NonEmpty err)) 

Instances

Eq err => Eq (AnyOfInvalid err) Source # 

Methods

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

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

Show err => Show (AnyOfInvalid err) Source # 

anyOfVal :: forall err schema. (schema -> Value -> [err]) -> AnyOf schema -> Value -> Maybe (AnyOfInvalid err) Source #

oneOf

newtype OneOf schema Source #

Constructors

OneOf 

Fields

Instances

Eq schema => Eq (OneOf schema) Source # 

Methods

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

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

Show schema => Show (OneOf schema) Source # 

Methods

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

show :: OneOf schema -> String #

showList :: [OneOf schema] -> ShowS #

FromJSON schema => FromJSON (OneOf schema) Source # 

Methods

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

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

data OneOfInvalid err Source #

Constructors

TooManySuccesses (NonEmpty (Index, Value)) Value

The NonEmpty lists contains tuples whose contents are the index of a schema that validated the data and the contents of that schema.

NoSuccesses (NonEmpty (Index, NonEmpty err)) Value

The NonEmpty lists contains tuples whose contents are the index of a schema that failed to validate the data and the failures it produced.

Instances

Eq err => Eq (OneOfInvalid err) Source # 

Methods

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

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

Show err => Show (OneOfInvalid err) Source # 

oneOfVal :: forall err schema. ToJSON schema => (schema -> Value -> [err]) -> OneOf schema -> Value -> Maybe (OneOfInvalid err) Source #

not

newtype NotValidator schema Source #

Constructors

NotValidator 

Fields

Instances

Eq schema => Eq (NotValidator schema) Source # 

Methods

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

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

Show schema => Show (NotValidator schema) Source # 

Methods

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

show :: NotValidator schema -> String #

showList :: [NotValidator schema] -> ShowS #

FromJSON schema => FromJSON (NotValidator schema) Source # 

notVal :: ToJSON schema => (schema -> Value -> [err]) -> NotValidator schema -> Value -> Maybe NotValidatorInvalid Source #