hjsonschema-1.2.0.2: JSON Schema library

Safe HaskellNone
LanguageHaskell2010

Data.JsonSchema.Draft4

Contents

Synopsis

Draft 4 Schema

data SchemaWithURI schema Source #

Constructors

SchemaWithURI 

Fields

  • _swSchema :: !schema
     
  • _swURI :: !(Maybe Text)

    This is the URI identifying the document containing the schema. It's different than the schema's "id" field, which controls scope when resolving references contained in the schema.

Instances

Eq schema => Eq (SchemaWithURI schema) Source # 

Methods

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

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

Show schema => Show (SchemaWithURI schema) Source # 

Methods

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

show :: SchemaWithURI schema -> String #

showList :: [SchemaWithURI schema] -> ShowS #

data Schema Source #

Constructors

Schema 

One-step validation (getting references over HTTP)

fetchHTTPAndValidate :: SchemaWithURI Schema -> Value -> IO (Either HTTPValidationFailure ()) Source #

Fetch recursively referenced schemas over HTTP, check that both the original and referenced schemas are valid, and then validate data.

type InvalidSchema = NonEmpty (Maybe Text, Failure) Source #

A description of why a schema (or one of its reference) is itself invalid.

Nothing indicates the starting schema. Just indicates a referenced schema -- the contents of the Just is the schema's URI.

NOTE: 'HashMap (Maybe Text) Invalid' would be a nicer way of defining this, but then we lose the guarantee that there's at least one key.

One-step validation (getting references from the filesystem)

fetchFilesystemAndValidate :: SchemaWithURI Schema -> Value -> IO (Either FilesystemValidationFailure ()) Source #

Fetch recursively referenced schemas from the filesystem, check that both the original and referenced schemas are valid, and then validate data.

Validation failure

data Fail err Source #

Validators shouldn't know more about the schema they're going to be used with than necessary. If a validator throws errors using the error sum type of a particular schema, then it can't be used with other schemas later that have different error sum types (at least not without writing partial functions).

Because of this we make Fail a higher order type, so each validator can return a sum type describing only the failures that can occur in that validator (or '()' if that validator can only fail in one way).

It's the job of a schema's validate function to unify the errors produced by the validators it uses into a single error sum type for that schema. The schema's validate function will return a Fail with that sum type as its type argument.

The slightly weird naming (Fail and Failure) is so that we can define a 'type Failure = Fail SchemaErrorType' for each of our schemas, and export it along with 'Fail(..)'. This way the users of the library only use Failure, not Fail.

Constructors

Failure 

Fields

  • _failureValidatorsCalled :: !err

    E.g. Items UniqueItems during draft 4 validation.

  • _failureFinalValidator :: !Value

    The value of the validator that raised the error (e.g. the value of "uniqueItems" in the above example.

  • _failureOffendingPointer :: !Pointer

    A pointer to the part of the data that caused invalidation.

  • _failureOffendingData :: !Value

    The part of the data that caused invalidation. Usually this is identical to the result of resolving _invalidOffendingPointer against the starting data, but not always (e.g. in the case of additionalItems where _invalidOffendingData will be the items in the array that were not allowed, instead of the entire array).

Instances

Functor Fail Source # 

Methods

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

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

Eq err => Eq (Fail err) Source # 

Methods

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

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

Show err => Show (Fail err) Source # 

Methods

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

show :: Fail err -> String #

showList :: [Fail err] -> ShowS #

data ValidatorChain Source #

Distinguish all the different possible causes of failure for Draft 4 validation.

Constructors

MultipleOf 
Maximum 
ExclusiveMaximum 
Minimum 
ExclusiveMinimum 
MaxLength 
MinLength 
PatternValidator 
MaxItems 
MinItems 
UniqueItems 
Items ValidatorChain 
AdditionalItemsBool 
AdditionalItemsObject ValidatorChain 
MaxProperties 
MinProperties 
Required 
SchemaDependency ValidatorChain 
PropertyDependency 
Properties ValidatorChain 
PatternProperties ValidatorChain 
AdditionalPropertiesBool 
AdditionalPropertiesObject ValidatorChain 
RefResolution

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.

RefLoop 
Ref ValidatorChain 
Enum 
TypeValidator 
AllOf ValidatorChain 
AnyOf ValidatorChain 
OneOfTooManySuccesses 
OneOfNoSuccesses ValidatorChain 
NotValidator 

Fetching tools

data ReferencedSchemas schema Source #

Constructors

ReferencedSchemas 

Fields

  • _rsStarting :: !schema

    Used to resolve relative references when we don't know what the scope of the current schema is. This only happens with starting schemas because if we're using a remote schema we had to know its URI in order to fetch it.

    Tracking the starting schema (instead of just resolving the reference to the current schema being used for validation) is necessary for cases where schemas are embedded inside one another. For instance in this case not distinguishing the starting and "foo" schemas sends the code into an infinite loop:

    { "additionalProperties": false, "properties": { "foo": { "$ref": "#" } } }

  • _rsSchemaMap :: !(URISchemaMap schema)
     

Instances

Eq schema => Eq (ReferencedSchemas schema) Source # 

Methods

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

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

Show schema => Show (ReferencedSchemas schema) Source # 

referencesViaHTTP :: SchemaWithURI Schema -> IO (Either HTTPFailure (URISchemaMap Schema)) Source #

Fetch the schemas recursively referenced by a starting schema over HTTP.

referencesViaFilesystem :: SchemaWithURI Schema -> IO (Either FilesystemFailure (URISchemaMap Schema)) Source #

Fetch the schemas recursively referenced by a starting schema from the filesystem.

Other Draft 4 things exported just in case

schemaValidity :: Schema -> [Failure] Source #

Check that a schema itself is valid (if so the returned list will be empty).

referencesValidity Source #

Arguments

:: URISchemaMap Schema 
-> [(Text, Failure)]

The first value in the tuple is the URI of a referenced schema.

Check that a set of referenced schemas are valid (if so the returned list will be empty).

checkSchema :: URISchemaMap Schema -> SchemaWithURI Schema -> Either InvalidSchema (Value -> [Failure]) Source #

A helper function.

Checks if a schema and a set of referenced schemas are valid.

Return a function to validate data.

draft4FetchInfo :: FetchInfo Schema Source #

An instance of FetchInfo specialized for JSON Schema Draft 4.