medea-1.2.0: A schema language for JSON.

Copyright(C) Juspay Technologies Pvt Ltd 2020
LicenseMIT
Maintainerkoz.ross@retro-freedom.nz
StabilityExperimental
PortabilityGHC only
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Medea

Contents

Description

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

Schema loading

data Schema Source #

A compiled Medea schema.

Instances
Eq Schema Source # 
Instance details

Defined in Data.Medea.Schema

Methods

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

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

Show Schema Source # 
Instance details

Defined in Data.Medea.Schema

data LoaderError Source #

Possible errors from loading Medea schemata.

Constructors

NotUtf8

The data provided wasn't UTF-8.

ParsingFailed !(ParseErrorBundle Text ParseError)

Parsing failed.

StartSchemaMissing

No schema labelled $start was provided.

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.

Fields

  • !Text

    Name of the schema we were expecting.

  • !Text

    Name of the schema that referenced it.

SchemaNameReserved !Text

A schema was named with a reserved identifier (other than start).

IsolatedSchemata !Text

An isolated schema was found.

MissingPropSchemaDefinition

A property schema refers to a non-existent schema.

Fields

  • !Text

    Name of the non-existent schema being referenced.

  • !Text

    Name of the referencing schema.

MinimumLengthGreaterThanMaximum !Text

A minimum length specification was more than its corresponding maximum length specification.

MultiplePropSchemaDefinition

A property was specified more than once.

Fields

  • !Text

    Name of the parent schema.

  • !Text

    Name of the property that was defined more than once.

MissingListSchemaDefinition

A list specification did not provide an element type.

Fields

  • !Text

    Name of the missing list element type schema.

  • !Text

    Name of the parent schema.

MissingTupleSchemaDefinition

A tuple specification does not provide a positional schema.

Fields

  • !Text

    Name of the missing tuple positional schema.

  • !Text

    Name of the parent schema.

PropertySpecWithoutObjectType !Text

Schema had a property specification, but no $object type.

ListSpecWithoutArrayType !Text

Schema had a list specification, but no $array type.

TupleSpecWithoutArrayType !Text

Schema had a tuple specification, but no $array type.

StringSpecWithoutStringType !Text

Schema had a string specification, but no $string type.

Instances
Eq LoaderError Source # 
Instance details

Defined in Data.Medea.Loader

Show LoaderError Source # 
Instance details

Defined in Data.Medea.Loader

data ParseError Source #

All possible errors from the Medea parser.

Constructors

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.

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

data JSONType Source #

The basic types of JSON value (as per ECMA-404).

Instances
Eq JSONType Source # 
Instance details

Defined in Data.Medea.JSONType

Ord JSONType Source # 
Instance details

Defined in Data.Medea.JSONType

Show JSONType Source # 
Instance details

Defined in Data.Medea.JSONType

Generic JSONType Source # 
Instance details

Defined in Data.Medea.JSONType

Associated Types

type Rep JSONType :: Type -> Type #

Methods

from :: JSONType -> Rep JSONType x #

to :: Rep JSONType x -> JSONType #

Hashable JSONType Source # 
Instance details

Defined in Data.Medea.JSONType

type Rep JSONType Source # 
Instance details

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.

Constructors

AnySchema

No requirements were placed on this chunk.

NullSchema

Validated as JSON null.

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
Eq SchemaInformation Source # 
Instance details

Defined in Data.Medea

Data SchemaInformation Source # 
Instance details

Defined in Data.Medea

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SchemaInformation -> c SchemaInformation #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SchemaInformation #

toConstr :: SchemaInformation -> Constr #

dataTypeOf :: SchemaInformation -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SchemaInformation) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SchemaInformation) #

gmapT :: (forall b. Data b => b -> b) -> SchemaInformation -> SchemaInformation #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SchemaInformation -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SchemaInformation -> r #

gmapQ :: (forall d. Data d => d -> u) -> SchemaInformation -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SchemaInformation -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SchemaInformation -> m SchemaInformation #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SchemaInformation -> m SchemaInformation #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SchemaInformation -> m SchemaInformation #

Show SchemaInformation Source # 
Instance details

Defined in Data.Medea

Generic SchemaInformation Source # 
Instance details

Defined in Data.Medea

Associated Types

type Rep SchemaInformation :: Type -> Type #

NFData SchemaInformation Source # 
Instance details

Defined in Data.Medea

Methods

rnf :: SchemaInformation -> () #

Hashable SchemaInformation Source # 
Instance details

Defined in Data.Medea

type Rep SchemaInformation Source # 
Instance details

Defined in Data.Medea

type Rep SchemaInformation = D1 (MetaData "SchemaInformation" "Data.Medea" "medea-1.2.0-inplace" False) (((C1 (MetaCons "AnySchema" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NullSchema" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "BooleanSchema" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NumberSchema" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "StringSchema" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ArraySchema" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "ObjectSchema" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "StartSchema" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "UserDefined" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Text))))))

data ValidationError Source #

All possible validation errors.

Constructors

EmptyError 
NotJSON

We could not parse JSON out of what we were provided.

WrongType

We got a type different to what we expected.

Fields

  • !Value

    The chunk of JSON.

  • !JSONType

    What we expected the type to be.

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.

Fields

  • !Text

    The property in question.

  • !Text

    The name of the specifying schema.

RequiredPropertyIsMissing

We found a JSON object which is missing a property its schema requires.

Fields

  • !Text

    The property in question.

  • !Text

    The name of the specifying schema.

OutOfBoundsArrayLength

We found a JSON array which falls outside of the minimum or maximum length constraints its corresponding schema demands.

Fields

  • !Text

    The name of the specifying schema.

  • !Value

    The JSON chunk corresponding to the invalid array.

ImplementationError !Text

This is a bug - please report it to us!

Instances
Eq ValidationError Source # 
Instance details

Defined in Data.Medea

Show ValidationError Source # 
Instance details

Defined in Data.Medea

Generic ValidationError Source # 
Instance details

Defined in Data.Medea

Associated Types

type Rep ValidationError :: Type -> Type #

Semigroup ValidationError Source # 
Instance details

Defined in Data.Medea

Monoid ValidationError Source # 
Instance details

Defined in Data.Medea

Hashable ValidationError Source # 
Instance details

Defined in Data.Medea

type Rep ValidationError Source # 
Instance details

Defined in Data.Medea

type Rep ValidationError = D1 (MetaData "ValidationError" "Data.Medea" "medea-1.2.0-inplace" False) (((C1 (MetaCons "EmptyError" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NotJSON" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "WrongType" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Value) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 JSONType)) :+: C1 (MetaCons "NotOneOfOptions" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Value)))) :+: ((C1 (MetaCons "AdditionalPropFoundButBanned" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Text)) :+: C1 (MetaCons "RequiredPropertyIsMissing" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Text))) :+: (C1 (MetaCons "OutOfBoundsArrayLength" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Value)) :+: C1 (MetaCons "ImplementationError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Text)))))

data ValidatedJSON Source #

JSON, annotated with what schemata it was deemed valid against.

Instances
Eq ValidatedJSON Source # 
Instance details

Defined in Data.Medea

Data ValidatedJSON Source # 
Instance details

Defined in Data.Medea

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ValidatedJSON -> c ValidatedJSON #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ValidatedJSON #

toConstr :: ValidatedJSON -> Constr #

dataTypeOf :: ValidatedJSON -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ValidatedJSON) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ValidatedJSON) #

gmapT :: (forall b. Data b => b -> b) -> ValidatedJSON -> ValidatedJSON #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ValidatedJSON -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ValidatedJSON -> r #

gmapQ :: (forall d. Data d => d -> u) -> ValidatedJSON -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ValidatedJSON -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ValidatedJSON -> m ValidatedJSON #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ValidatedJSON -> m ValidatedJSON #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ValidatedJSON -> m ValidatedJSON #

Show ValidatedJSON Source # 
Instance details

Defined in Data.Medea

NFData ValidatedJSON Source # 
Instance details

Defined in Data.Medea

Methods

rnf :: ValidatedJSON -> () #

Hashable ValidatedJSON Source # 
Instance details

Defined in Data.Medea

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 #

Helper for construction of validated JSON from a Handle. This will attempt to decode using Aeson before validating. This will return errors on failure in the same way as validate does.

This will close the Handle upon finding EOF, or if an exception is thrown.