{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE TupleSections #-}
module Data.Medea
(
Schema,
LoaderError (..),
ParseError (..),
buildSchema,
loadSchemaFromFile,
loadSchemaFromHandle,
JSONType (..),
SchemaInformation (..),
ValidationError (..),
ValidatedJSON,
toValue,
validAgainst,
validate,
validateFromFile,
validateFromHandle,
)
where
import Control.Applicative (Alternative (..))
import Control.Comonad.Cofree (Cofree (..))
import Control.DeepSeq (NFData (..))
import Control.Monad (unless)
import Control.Monad.Except (MonadError (..))
import Control.Monad.IO.Class (MonadIO (..))
import Control.Monad.RWS.Strict (RWST (..), evalRWST)
import Control.Monad.Reader (MonadReader, asks)
import Control.Monad.State.Strict (MonadState (..), gets)
import Data.Aeson (Array, Object, Value (..), decodeStrict)
import qualified Data.ByteString as BS
import Data.ByteString (ByteString)
import Data.Can (Can (..))
import Data.Coerce (coerce)
import Data.Data (Data)
import Data.Foldable (asum, traverse_)
import Data.Functor (($>))
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HM
import Data.Hashable (Hashable (..))
import qualified Data.Map.Strict as M
import Data.Medea.Analysis (ArrayType (..), CompiledSchema (..), TypeNode (..), arrayBounds)
import Data.Medea.JSONType (JSONType (..), typeOf)
import Data.Medea.Loader
( LoaderError (..),
buildSchema,
loadSchemaFromFile,
loadSchemaFromHandle,
)
import Data.Medea.Parser.Primitive (Identifier (..), ReservedIdentifier (..), identFromReserved)
import Data.Medea.Parser.Types (ParseError (..))
import Data.Medea.Schema (Schema (..))
import Data.Medea.ValidJSON (ValidJSONF (..))
import qualified Data.Set as S
import Data.Set.NonEmpty
( NESet,
dropWhileAntitone,
findMin,
member,
singleton,
)
import Data.Text (Text)
import qualified Data.Vector as V
import GHC.Generics (Generic)
import System.IO (Handle)
data SchemaInformation
=
AnySchema
|
NullSchema
|
BooleanSchema
|
NumberSchema
|
StringSchema
|
ArraySchema
|
ObjectSchema
|
StartSchema
|
UserDefined {-# UNPACK #-} !Text
deriving stock (Eq, Data, Show, Generic)
deriving anyclass (Hashable, NFData)
newtype ValidatedJSON = ValidatedJSON (Cofree ValidJSONF SchemaInformation)
deriving stock (Data)
deriving newtype (Eq, Show)
instance NFData ValidatedJSON where
{-# INLINE rnf #-}
rnf (ValidatedJSON (x :< f)) =
rnf x `seq` (rnf . fmap ValidatedJSON $ f)
instance Hashable ValidatedJSON where
{-# INLINE hashWithSalt #-}
hashWithSalt salt (ValidatedJSON (x :< f)) =
salt `hashWithSalt` x `hashWithSalt` fmap ValidatedJSON f
toValue :: ValidatedJSON -> Value
toValue (ValidatedJSON (_ :< f)) = case f of
AnythingF v -> v
NullF -> Null
BooleanF b -> Bool b
NumberF n -> Number n
StringF s -> String s
ArrayF v -> Array . fmap (toValue . coerce) $ v
ObjectF hm -> Object . fmap (toValue . coerce) $ hm
validAgainst :: ValidatedJSON -> SchemaInformation
validAgainst (ValidatedJSON (label :< _)) = label
data ValidationError
= EmptyError
|
NotJSON
|
WrongType
!Value
!JSONType
|
NotOneOfOptions !Value
|
AdditionalPropFoundButBanned
{-# UNPACK #-} !Text
{-# UNPACK #-} !Text
|
RequiredPropertyIsMissing
{-# UNPACK #-} !Text
{-# UNPACK #-} !Text
|
OutOfBoundsArrayLength
{-# UNPACK #-} !Text
!Value
|
ImplementationError
{-# UNPACK #-} !Text
deriving stock (Eq, Show, Generic)
deriving anyclass (Hashable)
instance Semigroup ValidationError where
EmptyError <> x = x
x <> _ = x
instance Monoid ValidationError where
mempty = EmptyError
validate :: Schema -> ByteString -> Either ValidationError ValidatedJSON
validate scm bs = case decodeStrict bs of
Nothing -> throwError NotJSON
Just v -> ValidatedJSON <$> go v
where
go v =
fmap fst . evalRWST (runValidationM . checkTypes $ v) scm $ (initialSet, Nothing)
initialSet = singleton . CustomNode . identFromReserved $ RStart
validateFromFile ::
(MonadIO m) =>
Schema ->
FilePath ->
m (Either ValidationError ValidatedJSON)
validateFromFile scm = fmap (validate scm) . liftIO . BS.readFile
validateFromHandle ::
(MonadIO m) =>
Schema ->
Handle ->
m (Either ValidationError ValidatedJSON)
validateFromHandle scm = fmap (validate scm) . liftIO . BS.hGetContents
newtype ValidationM a = ValidationM
{ runValidationM ::
RWST
Schema
()
(NESet TypeNode, Maybe Identifier)
(Either ValidationError)
a
}
deriving newtype
( Functor,
Applicative,
Monad,
MonadReader Schema,
MonadState (NESet TypeNode, Maybe Identifier),
MonadError ValidationError
)
instance Alternative ValidationM where
empty = ValidationM . RWST $ \_ _ -> Left EmptyError
ValidationM comp1 <|> ValidationM comp2 = ValidationM . RWST $ go
where
go r s = case runRWST comp1 r s of
Left err -> case runRWST comp2 r s of
Left _ -> Left err
Right res -> Right res
Right res -> Right res
failWith :: ValidationError -> ValidationM a
failWith err = ValidationM . RWST $ \_ _ -> Left err
checkTypes :: Value -> ValidationM (Cofree ValidJSONF SchemaInformation)
checkTypes v = checkAny v <|> checkPrim v <|> checkCustoms v
checkAny :: Value -> ValidationM (Cofree ValidJSONF SchemaInformation)
checkAny v = do
minNode <- gets (findMin . fst)
case minNode of
AnyNode -> pure (AnySchema :< AnythingF v)
_ -> failWith EmptyError
checkPrim :: Value -> ValidationM (Cofree ValidJSONF SchemaInformation)
checkPrim v = do
(nodes, par) <- get
unless (member (PrimitiveNode . typeOf $ v) nodes) (failWith . NotOneOfOptions $ v)
case v of
Null -> pure (NullSchema :< NullF)
Bool b -> pure (BooleanSchema :< BooleanF b)
Number n -> pure (NumberSchema :< NumberF n)
String s -> case par of
Nothing -> pure (StringSchema :< StringF s)
Just parIdent -> do
scm <- lookupSchema parIdent
let validVals = stringVals scm
if
| V.length validVals == 0 -> pure (StringSchema :< StringF s)
| s `V.elem` validVals -> pure (StringSchema :< StringF s)
| otherwise -> failWith . NotOneOfOptions $ v
Array arr -> case par of
Nothing -> put (anySet, Nothing) >> (ArraySchema :<) . ArrayF <$> traverse checkTypes arr
Just parIdent -> checkArray arr parIdent
Object obj -> case par of
Nothing ->
put (anySet, Nothing) >> (ObjectSchema :<) . ObjectF <$> traverse checkTypes obj
Just parIdent -> checkObject obj parIdent
checkArray :: Array -> Identifier -> ValidationM (Cofree ValidJSONF SchemaInformation)
checkArray arr parIdent = do
scm <- lookupSchema parIdent
let arrLen = fromIntegral . V.length $ arr
maybe (failWith outOfBounds) pure $ case arrayBounds scm of
Non -> Just ()
One lo -> unless (arrLen >= lo) Nothing
Eno hi -> unless (arrLen <= hi) Nothing
Two lo hi -> unless (arrLen >= lo && arrLen <= hi) Nothing
let valsAndTypes = pairValsWithTypes . arrayTypes $ scm
checkedArray <- traverse go valsAndTypes
pure (ArraySchema :< ArrayF checkedArray)
where
outOfBounds = OutOfBoundsArrayLength (textify parIdent) . Array $ arr
pairValsWithTypes = \case
Nothing -> (,AnyNode) <$> arr
Just (ListType node) -> (,node) <$> arr
Just (TupleType nodes) -> V.zip arr nodes
go (val, typeNode) = do
put (singleton typeNode, Nothing)
checkTypes val
checkObject :: Object -> Identifier -> ValidationM (Cofree ValidJSONF SchemaInformation)
checkObject obj parIdent = do
valsAndTypes <- pairPropertySchemaAndVal obj parIdent
checkedObj <- traverse go valsAndTypes
pure (ObjectSchema :< ObjectF checkedObj)
where
go (val, typeNode) = do
put (singleton typeNode, Nothing)
checkTypes val
pairPropertySchemaAndVal ::
HashMap Text Value -> Identifier -> ValidationM (HashMap Text (Value, TypeNode))
pairPropertySchemaAndVal obj parIdent = do
scm <- lookupSchema parIdent
mappedObj <- traverse (pairProperty scm) . HM.mapWithKey (,) $ obj
traverse_ isMatched . HM.mapWithKey (,) . props $ scm
pure mappedObj
where
pairProperty scm (propName, v) = case HM.lookup propName . props $ scm of
Just (typeNode, _) -> pure (v, typeNode)
Nothing ->
if additionalProps scm
then pure (v, additionalPropSchema scm)
else failWith . AdditionalPropFoundButBanned (textify parIdent) $ propName
isMatched (propName, (_, optional)) = case HM.lookup propName obj of
Nothing ->
unless optional . failWith . RequiredPropertyIsMissing (textify parIdent) $ propName
Just _ -> pure ()
checkCustoms :: Value -> ValidationM (Cofree ValidJSONF SchemaInformation)
checkCustoms v = do
customNodes <- gets (dropWhileAntitone (not . isCustom) . fst)
asum . fmap checkCustom . S.toList $ customNodes
where
checkCustom = \case
CustomNode ident -> do
neighbourhood <- typesAs <$> lookupSchema ident
put (neighbourhood, Just ident)
($> (UserDefined . textify $ ident)) <$> checkTypes v
_ -> failWith . ImplementationError $ "Unreachable code: these nodes must be custom."
lookupSchema ::
(MonadReader Schema m, MonadError ValidationError m) => Identifier -> m CompiledSchema
lookupSchema ident = do
x <- asks $ M.lookup ident . compiledSchemata
case x of
Just scm -> pure scm
Nothing -> throwError . ImplementationError $ "Unreachable state: We should be able to find this schema"
anySet :: NESet TypeNode
anySet = singleton AnyNode
textify :: Identifier -> Text
textify (Identifier t) = t
isCustom :: TypeNode -> Bool
isCustom (CustomNode _) = True
isCustom _ = False