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) import Control.Monad.Except (runExceptT) main :: IO () main = do -- try to load the schema graph file loaded <- runExceptT . loadSchemaFromFile $ "/path/to/schema.medea" case loaded of Left err -> print err -- or some other handling Right scm -> do -- try to validate validated <- runExceptT . 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
- | IdentifierTooLong
- | EmptyLengthSpec
- | ParserError !(ParseError Text Void)
- | 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
- buildSchema :: MonadError LoaderError m => ByteString -> m Schema
- loadSchemaFromFile :: (MonadIO m, MonadError LoaderError m) => FilePath -> m Schema
- loadSchemaFromHandle :: (MonadIO m, MonadError LoaderError m) => Handle -> m Schema
- data JSONType
- data SchemaInformation
- data ValidationError
- data ValidatedJSON
- toValue :: ValidatedJSON -> Value
- validAgainst :: ValidatedJSON -> SchemaInformation
- validate :: (MonadPlus m, MonadError ValidationError m) => Schema -> ByteString -> m ValidatedJSON
- validateFromFile :: (MonadPlus m, MonadError ValidationError m, MonadIO m) => Schema -> FilePath -> m ValidatedJSON
- validateFromHandle :: (MonadPlus m, MonadError ValidationError m, MonadIO m) => Schema -> Handle -> m ValidatedJSON
Schema loading
A compiled Medea schema.
data LoaderError Source #
Possible errors from loading Medea schemata.
NotUtf8 | The data provided wasn't UTF-8. |
IdentifierTooLong | An identifier was longer than allowed. |
EmptyLengthSpec | A length specification had no minimum/maximum specification. |
ParserError !(ParseError Text Void) | 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 # |
buildSchema :: MonadError LoaderError m => ByteString -> m Schema Source #
Attempt to produce a schema from UTF-8 data in memory.
loadSchemaFromFile :: (MonadIO m, MonadError LoaderError m) => FilePath -> m Schema Source #
Parse and process a Medea schema graph file.
loadSchemaFromHandle :: (MonadIO m, MonadError LoaderError m) => Handle -> m Schema Source #
Load data corresponding to a Medea schema graph file from a Handle
.
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.0.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 :: (MonadPlus m, MonadError ValidationError m) => Schema -> ByteString -> m ValidatedJSON Source #
Attempt to construct validated JSON from a bytestring. This will attempt to decode using Aeson before validating.
validateFromFile :: (MonadPlus m, MonadError ValidationError m, MonadIO m) => Schema -> FilePath -> m ValidatedJSON Source #
Helper for construction of validated JSON from a JSON file. This will attempt to decode using Aeson before validating.
validateFromHandle :: (MonadPlus m, MonadError ValidationError m, MonadIO m) => Schema -> Handle -> m ValidatedJSON Source #