Safe Haskell | None |
---|---|
Language | Haskell2010 |
- newtype Ref = Ref {}
- data RefInvalid err
- newtype VisitedSchemas = VisitedSchemas {
- _unVisited :: [URIAndFragment]
- refVal :: forall err schema. (FromJSON schema, ToJSON schema) => (Text -> Maybe schema) -> (BaseURI -> schema -> BaseURI) -> (VisitedSchemas -> Scope schema -> schema -> Value -> [err]) -> VisitedSchemas -> Scope schema -> Ref -> Value -> Maybe (RefInvalid err)
- getDocument :: forall schema. (Text -> Maybe schema) -> (BaseURI -> schema -> BaseURI) -> Scope schema -> Maybe Text -> Text -> Either Text (Scope schema, schema)
- data JSONPointerError
- resolveFragment :: forall schema. (FromJSON schema, ToJSON schema) => (BaseURI -> schema -> BaseURI) -> Scope schema -> Text -> Either JSONPointerError (Scope schema, schema)
- newtype EnumValidator = EnumValidator {}
- data EnumInvalid = EnumInvalid EnumValidator Value
- enumVal :: EnumValidator -> Value -> Maybe EnumInvalid
- newtype TypeContext = TypeContext {}
- data TypeValidator
- data SchemaType
- data TypeValidatorInvalid = TypeValidatorInvalid TypeValidator Value
- typeVal :: TypeContext -> Value -> Maybe TypeValidatorInvalid
- setFromTypeValidator :: TypeValidator -> Set SchemaType
- newtype AllOf schema = AllOf {}
- newtype AllOfInvalid err = AllOfInvalid (NonEmpty (Index, NonEmpty err))
- allOfVal :: forall err schema. (schema -> Value -> [err]) -> AllOf schema -> Value -> Maybe (AllOfInvalid err)
- newtype AnyOf schema = AnyOf {}
- newtype AnyOfInvalid err = AnyOfInvalid (NonEmpty (Index, NonEmpty err))
- anyOfVal :: forall err schema. (schema -> Value -> [err]) -> AnyOf schema -> Value -> Maybe (AnyOfInvalid err)
- newtype OneOf schema = OneOf {}
- data OneOfInvalid err
- = TooManySuccesses (NonEmpty (Index, Value)) Value
- | NoSuccesses (NonEmpty (Index, NonEmpty err)) Value
- oneOfVal :: forall err schema. ToJSON schema => (schema -> Value -> [err]) -> OneOf schema -> Value -> Maybe (OneOfInvalid err)
- newtype NotValidator schema = NotValidator {
- _unNotValidator :: schema
- data NotValidatorInvalid = NotValidatorInvalid Value Value
- notVal :: ToJSON schema => (schema -> Value -> [err]) -> NotValidator schema -> Value -> Maybe NotValidatorInvalid
$ref
data RefInvalid err Source #
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) |
Eq err => Eq (RefInvalid err) Source # | |
Show err => Show (RefInvalid err) Source # | |
newtype VisitedSchemas Source #
:: (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) |
data JSONPointerError Source #
URLDecodingError UnicodeException | Aspirationally internal. |
FormatError FormatError | |
ResolutionError ResolutionError | |
SubschemaDecodingError Text | Aspirationally internal. |
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.
data EnumInvalid Source #
enumVal :: EnumValidator -> Value -> Maybe EnumInvalid Source #
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.
data TypeValidator Source #
data SchemaType Source #
data TypeValidatorInvalid Source #
typeVal :: TypeContext -> Value -> Maybe TypeValidatorInvalid Source #
setFromTypeValidator :: TypeValidator -> Set SchemaType Source #
Internal.
allOf
newtype AllOfInvalid err Source #
AllOfInvalid (NonEmpty (Index, NonEmpty err)) |
Eq err => Eq (AllOfInvalid err) Source # | |
Show err => Show (AllOfInvalid err) Source # | |
allOfVal :: forall err schema. (schema -> Value -> [err]) -> AllOf schema -> Value -> Maybe (AllOfInvalid err) Source #
anyOf
newtype AnyOfInvalid err Source #
AnyOfInvalid (NonEmpty (Index, NonEmpty err)) |
Eq err => Eq (AnyOfInvalid err) Source # | |
Show err => Show (AnyOfInvalid err) Source # | |
anyOfVal :: forall err schema. (schema -> Value -> [err]) -> AnyOf schema -> Value -> Maybe (AnyOfInvalid err) Source #
oneOf
data OneOfInvalid err Source #
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. |
Eq err => Eq (OneOfInvalid err) Source # | |
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 #
NotValidator | |
|
Eq schema => Eq (NotValidator schema) Source # | |
Show schema => Show (NotValidator schema) Source # | |
FromJSON schema => FromJSON (NotValidator schema) Source # | |
data NotValidatorInvalid Source #
notVal :: ToJSON schema => (schema -> Value -> [err]) -> NotValidator schema -> Value -> Maybe NotValidatorInvalid Source #