module JSONSchema.Draft4
(
SchemaWithURI(..)
, Schema(..)
, SC.emptySchema
, fetchHTTPAndValidate
, HTTPValidationFailure(..)
, FE.HTTPFailure(..)
, SchemaInvalid(..)
, fetchFilesystemAndValidate
, FilesystemValidationFailure(..)
, FE.FilesystemFailure(..)
, Invalid(..)
, ValidatorFailure(..)
, URISchemaMap(..)
, referencesViaHTTP
, referencesViaFilesystem
, metaSchema
, metaSchemaBytes
, schemaValidity
, referencesValidity
, checkSchema
, draft4FetchInfo
) where
import Import
import qualified Data.ByteString as BS
import Data.FileEmbed (embedFile,
makeRelativeToProject)
import qualified Data.HashMap.Strict as HM
import qualified Data.List.NonEmpty as NE
import Data.Maybe (fromMaybe)
import JSONSchema.Draft4.Failure (Invalid(..),
SchemaInvalid(..),
ValidatorFailure(..))
import JSONSchema.Draft4.Schema (Schema)
import qualified JSONSchema.Draft4.Schema as SC
import qualified JSONSchema.Draft4.Spec as Spec
import JSONSchema.Fetch (SchemaWithURI(..),
URISchemaMap(..))
import qualified JSONSchema.Fetch as FE
data HTTPValidationFailure
= HVRequest FE.HTTPFailure
| HVSchema SchemaInvalid
| HVData Invalid
deriving Show
fetchHTTPAndValidate
:: SchemaWithURI Schema
-> Value
-> IO (Either HTTPValidationFailure ())
fetchHTTPAndValidate sw v = do
res <- referencesViaHTTP sw
pure (g =<< f =<< first HVRequest res)
where
f :: FE.URISchemaMap Schema
-> Either HTTPValidationFailure (Value -> [ValidatorFailure])
f references = first HVSchema (checkSchema references sw)
g :: (Value -> [ValidatorFailure]) -> Either HTTPValidationFailure ()
g val = case NE.nonEmpty (val v) of
Nothing -> Right ()
Just failures -> Left (HVData Invalid
{ _invalidSchema = _swSchema sw
, _invalidInstance = v
, _invalidFailures = failures
})
data FilesystemValidationFailure
= FVRead FE.FilesystemFailure
| FVSchema SchemaInvalid
| FVData Invalid
deriving (Show, Eq)
fetchFilesystemAndValidate
:: SchemaWithURI Schema
-> Value
-> IO (Either FilesystemValidationFailure ())
fetchFilesystemAndValidate sw v = do
res <- referencesViaFilesystem sw
pure (g =<< f =<< first FVRead res)
where
f :: FE.URISchemaMap Schema
-> Either FilesystemValidationFailure (Value -> [ValidatorFailure])
f references = first FVSchema (checkSchema references sw)
g :: (Value -> [ValidatorFailure]) -> Either FilesystemValidationFailure ()
g val = case NE.nonEmpty (val v) of
Nothing -> Right ()
Just invalid -> Left (FVData Invalid
{ _invalidSchema = _swSchema sw
, _invalidInstance = v
, _invalidFailures = invalid
})
draft4FetchInfo :: FE.FetchInfo Schema
draft4FetchInfo = FE.FetchInfo Spec.embedded SC._schemaId SC._schemaRef
referencesViaHTTP
:: SchemaWithURI Schema
-> IO (Either FE.HTTPFailure (FE.URISchemaMap Schema))
referencesViaHTTP = FE.referencesViaHTTP' draft4FetchInfo
referencesViaFilesystem
:: SchemaWithURI Schema
-> IO (Either FE.FilesystemFailure (FE.URISchemaMap Schema))
referencesViaFilesystem = FE.referencesViaFilesystem' draft4FetchInfo
checkSchema
:: FE.URISchemaMap Schema
-> SchemaWithURI Schema
-> Either SchemaInvalid (Value -> [ValidatorFailure])
checkSchema sm sw =
case NE.nonEmpty failures of
Just fs -> Left (SchemaInvalid fs)
Nothing -> Right (Spec.specValidate sm sw)
where
failures :: [(Maybe Text, NonEmpty ValidatorFailure)]
failures =
let refFailures = first Just <$> referencesValidity sm
in case NE.nonEmpty (schemaValidity (_swSchema sw)) of
Nothing -> refFailures
Just errs -> (Nothing,errs) : refFailures
metaSchema :: Schema
metaSchema =
fromMaybe (panic "Schema decode failed (this should never happen)")
. decodeStrict
$ metaSchemaBytes
metaSchemaBytes :: BS.ByteString
metaSchemaBytes =
$(makeRelativeToProject "src/draft4.json" >>= embedFile)
schemaValidity :: Schema -> [ValidatorFailure]
schemaValidity =
Spec.specValidate schemaMap (SchemaWithURI metaSchema Nothing) . toJSON
where
schemaMap :: URISchemaMap Schema
schemaMap =
URISchemaMap (HM.singleton "http://json-schema.org/draft-04/schema"
metaSchema)
referencesValidity
:: FE.URISchemaMap Schema
-> [(Text, NonEmpty ValidatorFailure)]
referencesValidity = HM.foldlWithKey' f mempty . FE._unURISchemaMap
where
f :: [(Text, NonEmpty ValidatorFailure)]
-> Text
-> Schema
-> [(Text, NonEmpty ValidatorFailure)]
f acc k v = case NE.nonEmpty (schemaValidity v) of
Nothing -> acc
Just errs -> (k,errs) : acc