Copyright | (C) Juspay Technologies Pvt Ltd 2020 |
---|---|
License | MIT |
Maintainer | koz.ross@retro-freedom.nz |
Stability | Experimental |
Portability | GHC only |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
This module contains the reference Haskell implementation of a Medea validator, providing both schema graph file loading and validation, with some convenience functions.
A minimal example of use follows. This example first attempts to load a Medea
schema graph file from /path/to/schema.medea
, and, if successful, attempts
to validate the JSON file at /path/to/my.json
against the schemata so
loaded.
import Data.Medea (loadSchemaFromFile, validateFromFile) main :: IO () main = do -- try to load the schema graph file loaded <- loadSchemaFromFile "/path/to/schema.medea" case loaded of Left err -> print err -- or some other handling Right scm -> do -- try to validate validated <- validateFromFile scm "/path/to/my.json" case validated of Left err -> print err -- or some other handling Right validJson -> print validJson -- or some other useful thing
For more details about how to create Medea schema graph files, see
TUTORIAL.md
and SPEC.md
.
Synopsis
- data Schema
- data LoaderError
- = NotUtf8
- | ParsingFailed !(ParseErrorBundle Text ParseError)
- | StartSchemaMissing
- | SelfTypingSchema
- | MultipleSchemaDefinition !Text
- | MissingSchemaDefinition !Text !Text
- | SchemaNameReserved !Text
- | IsolatedSchemata !Text
- | MissingPropSchemaDefinition !Text !Text
- | MinimumLengthGreaterThanMaximum !Text
- | MultiplePropSchemaDefinition !Text !Text
- | MissingListSchemaDefinition !Text !Text
- | MissingTupleSchemaDefinition !Text !Text
- | PropertySpecWithoutObjectType !Text
- | ListSpecWithoutArrayType !Text
- | TupleSpecWithoutArrayType !Text
- | StringSpecWithoutStringType !Text
- data ParseError
- buildSchema :: ByteString -> Either LoaderError Schema
- loadSchemaFromFile :: MonadIO m => FilePath -> m (Either LoaderError Schema)
- loadSchemaFromHandle :: MonadIO m => Handle -> m (Either LoaderError Schema)
- data JSONType
- data SchemaInformation
- data ValidationError
- = EmptyError
- | NotJSON
- | WrongType !Value !JSONType
- | NotOneOfOptions !Value
- | AdditionalPropFoundButBanned !Text !Text
- | RequiredPropertyIsMissing !Text !Text
- | OutOfBoundsArrayLength !Text !Value
- | ImplementationError !Text
- data ValidatedJSON
- toValue :: ValidatedJSON -> Value
- validAgainst :: ValidatedJSON -> SchemaInformation
- validate :: Schema -> ByteString -> Either ValidationError ValidatedJSON
- validateFromFile :: MonadIO m => Schema -> FilePath -> m (Either ValidationError ValidatedJSON)
- validateFromHandle :: MonadIO m => Schema -> Handle -> m (Either ValidationError ValidatedJSON)
Schema loading
A compiled Medea schema.
data LoaderError Source #
Possible errors from loading Medea schemata.
NotUtf8 | The data provided wasn't UTF-8. |
ParsingFailed !(ParseErrorBundle Text ParseError) | Parsing failed. |
StartSchemaMissing | No schema labelled |
SelfTypingSchema | A schema was typed in terms of itself. |
MultipleSchemaDefinition !Text | A schema was defined more than once. |
MissingSchemaDefinition | We expected a schema, but couldn't find it. |
SchemaNameReserved !Text | A schema was named with a reserved identifier (other than |
IsolatedSchemata !Text | An isolated schema was found. |
MissingPropSchemaDefinition | A property schema refers to a non-existent schema. |
MinimumLengthGreaterThanMaximum !Text | A minimum length specification was more than its corresponding maximum length specification. |
MultiplePropSchemaDefinition | A property was specified more than once. |
MissingListSchemaDefinition | A list specification did not provide an element type. |
MissingTupleSchemaDefinition | A tuple specification does not provide a positional schema. |
PropertySpecWithoutObjectType !Text | Schema had a property specification, but no |
ListSpecWithoutArrayType !Text | Schema had a list specification, but no |
TupleSpecWithoutArrayType !Text | Schema had a tuple specification, but no |
StringSpecWithoutStringType !Text | Schema had a string specification, but no |
Instances
Eq LoaderError Source # | |
Defined in Data.Medea.Loader (==) :: LoaderError -> LoaderError -> Bool # (/=) :: LoaderError -> LoaderError -> Bool # | |
Show LoaderError Source # | |
Defined in Data.Medea.Loader showsPrec :: Int -> LoaderError -> ShowS # show :: LoaderError -> String # showList :: [LoaderError] -> ShowS # |
data ParseError Source #
All possible errors from the Medea parser.
IdentifierTooLong !Text | An identifier exceeded 32 bytes. |
ExpectedReservedIdentifier !Text | We saw a non-reserved identifier where we wanted a reserved one. |
LeadingZero !Text | A Medea natural number had literal zeroes. |
ConflictingSpecRequirements | We were given incompatible requirements within a specification. |
EmptyLengthArraySpec | We were not given a length in an array specification. |
EmptyArrayElements | We were not given an element specification in an array specification. |
EmptyStringValuesSpec | We were given no string values in a string specification. |
Instances
Eq ParseError Source # | |
Defined in Data.Medea.Parser.Types (==) :: ParseError -> ParseError -> Bool # (/=) :: ParseError -> ParseError -> Bool # | |
Ord ParseError Source # | |
Defined in Data.Medea.Parser.Types compare :: ParseError -> ParseError -> Ordering # (<) :: ParseError -> ParseError -> Bool # (<=) :: ParseError -> ParseError -> Bool # (>) :: ParseError -> ParseError -> Bool # (>=) :: ParseError -> ParseError -> Bool # max :: ParseError -> ParseError -> ParseError # min :: ParseError -> ParseError -> ParseError # | |
Show ParseError Source # | |
Defined in Data.Medea.Parser.Types showsPrec :: Int -> ParseError -> ShowS # show :: ParseError -> String # showList :: [ParseError] -> ShowS # | |
ShowErrorComponent ParseError Source # | |
Defined in Data.Medea.Parser.Types showErrorComponent :: ParseError -> String errorComponentLen :: ParseError -> Int |
buildSchema :: ByteString -> Either LoaderError Schema Source #
Attempt to produce a schema from UTF-8 data in memory.
loadSchemaFromFile :: MonadIO m => FilePath -> m (Either LoaderError Schema) Source #
Parse and process a Medea schema graph file.
Any file handle(s) will be closed if an exception is thrown.
loadSchemaFromHandle :: MonadIO m => Handle -> m (Either LoaderError Schema) Source #
Load data corresponding to a Medea schema graph file from a Handle
.
This relies on hGetContents
to do its work, and all caveats about the state
a Handle
can be left in afterwards apply here.
Schema validation
The basic types of JSON value (as per ECMA-404).
Instances
Eq JSONType Source # | |
Ord JSONType Source # | |
Defined in Data.Medea.JSONType | |
Show JSONType Source # | |
Generic JSONType Source # | |
Hashable JSONType Source # | |
Defined in Data.Medea.JSONType | |
type Rep JSONType Source # | |
Defined in Data.Medea.JSONType type Rep JSONType = D1 (MetaData "JSONType" "Data.Medea.JSONType" "medea-1.2.0-inplace" False) ((C1 (MetaCons "JSONNull" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "JSONBoolean" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "JSONNumber" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "JSONString" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "JSONArray" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "JSONObject" PrefixI False) (U1 :: Type -> Type)))) |
data SchemaInformation Source #
An annotation, describing which schema a given chunk of JSON was deemed to be valid against.
AnySchema | No requirements were placed on this chunk. |
NullSchema | Validated as JSON |
BooleanSchema | Validated as JSON boolean. |
NumberSchema | Validated as JSON number. |
StringSchema | Validated as JSON string. |
ArraySchema | Validated as JSON array. |
ObjectSchema | Validated as JSON object. |
StartSchema | Validated against the start schema. |
UserDefined !Text | Validated against the schema with the given name. |
Instances
data ValidationError Source #
All possible validation errors.
EmptyError | |
NotJSON | We could not parse JSON out of what we were provided. |
WrongType | We got a type different to what we expected. |
| |
NotOneOfOptions !Value | We expected one of several possibilities, but got something that fits none. |
AdditionalPropFoundButBanned | We found a JSON object with a property that wasn't specified in its schema, and additional properties are forbidden. |
RequiredPropertyIsMissing | We found a JSON object which is missing a property its schema requires. |
OutOfBoundsArrayLength | We found a JSON array which falls outside of the minimum or maximum length constraints its corresponding schema demands. |
| |
ImplementationError !Text | This is a bug - please report it to us! |
Instances
data ValidatedJSON Source #
JSON, annotated with what schemata it was deemed valid against.
Instances
toValue :: ValidatedJSON -> Value Source #
Convert to an Aeson Value
, throwing away all schema information.
validAgainst :: ValidatedJSON -> SchemaInformation Source #
What schema did this validate against?
validate :: Schema -> ByteString -> Either ValidationError ValidatedJSON Source #
Attempt to construct validated JSON from a strict bytestring. This will attempt to decode using Aeson before validating.
If this fails, it will return the first failure condition; that is, the one caused by the first node in a depth-first, right-to-left, document-order traversal of the input JSON.
validateFromFile :: MonadIO m => Schema -> FilePath -> m (Either ValidationError ValidatedJSON) Source #
Helper for construction of validated JSON from a JSON file.
This will attempt to decode using Aeson before validating. This will return
errors on failure in the same way as validate
does.
This will clean up any file handle(s) if any exceptions are thrown.
validateFromHandle :: MonadIO m => Schema -> Handle -> m (Either ValidationError ValidatedJSON) Source #