module JSONSchema.Validator.Draft4.Object
( module JSONSchema.Validator.Draft4.Object
, module JSONSchema.Validator.Draft4.Object.Properties
) where
import Import
import qualified Data.HashMap.Strict as HM
import qualified Data.List.NonEmpty as NE
import Data.Set (Set)
import qualified Data.Set as Set
import qualified Data.Text as T
import JSONSchema.Validator.Draft4.Object.Properties
import JSONSchema.Validator.Utils
newtype MaxProperties
= MaxProperties { _unMaxProperties :: Int }
deriving (Eq, Show)
instance FromJSON MaxProperties where
parseJSON = withObject "MaxProperties" $ \o ->
MaxProperties <$> o .: "maxProperties"
data MaxPropertiesInvalid
= MaxPropertiesInvalid MaxProperties (HashMap Text Value)
deriving (Eq, Show)
maxPropertiesVal
:: MaxProperties
-> HashMap Text Value
-> Maybe MaxPropertiesInvalid
maxPropertiesVal a@(MaxProperties n) x
| n < 0 = Nothing
| HM.size x > n = Just (MaxPropertiesInvalid a x)
| otherwise = Nothing
newtype MinProperties
= MinProperties { _unMinProperties :: Int }
deriving (Eq, Show)
instance FromJSON MinProperties where
parseJSON = withObject "MinProperties" $ \o ->
MinProperties <$> o .: "minProperties"
data MinPropertiesInvalid
= MinPropertiesInvalid MinProperties (HashMap Text Value)
deriving (Eq, Show)
minPropertiesVal
:: MinProperties
-> HashMap Text Value
-> Maybe MinPropertiesInvalid
minPropertiesVal a@(MinProperties n) x
| n < 0 = Nothing
| HM.size x < n = Just (MinPropertiesInvalid a x)
| otherwise = Nothing
newtype Required
= Required { _unRequired :: Set Text }
deriving (Eq, Show)
instance FromJSON Required where
parseJSON = withObject "Required" $ \o ->
Required <$> o .: "required"
instance Arbitrary Required where
arbitrary = do
x <- arbitraryText
xs <- (fmap.fmap) T.pack arbitrary
pure . Required . Set.fromList $ x:xs
data RequiredInvalid
= RequiredInvalid Required (Set Text) (HashMap Text Value)
deriving (Eq, Show)
requiredVal :: Required -> HashMap Text Value -> Maybe RequiredInvalid
requiredVal r@(Required ts) x
| Set.null ts = Nothing
| Set.null leftovers = Nothing
| otherwise = Just (RequiredInvalid r leftovers x)
where
leftovers :: Set Text
leftovers =
Set.difference
ts
(Set.fromList (HM.keys x))
newtype DependenciesValidator schema
= DependenciesValidator
{ _unDependenciesValidator :: HashMap Text (Dependency schema) }
deriving (Eq, Show)
instance FromJSON schema => FromJSON (DependenciesValidator schema) where
parseJSON = withObject "DependenciesValidator" $ \o ->
DependenciesValidator <$> o .: "dependencies"
data Dependency schema
= SchemaDependency schema
| PropertyDependency (Set Text)
deriving (Eq, Show)
instance FromJSON schema => FromJSON (Dependency schema) where
parseJSON v = fmap SchemaDependency (parseJSON v)
<|> fmap PropertyDependency (parseJSON v)
instance ToJSON schema => ToJSON (Dependency schema) where
toJSON (SchemaDependency schema) = toJSON schema
toJSON (PropertyDependency ts) = toJSON ts
instance Arbitrary schema => Arbitrary (Dependency schema) where
arbitrary = oneof [ SchemaDependency <$> arbitrary
, PropertyDependency <$> arbitrarySetOfText
]
data DependencyMemberInvalid err
= SchemaDepInvalid (NonEmpty err)
| PropertyDepInvalid (Set Text) (HashMap Text Value)
deriving (Eq, Show)
newtype DependenciesInvalid err
= DependenciesInvalid (HashMap Text (DependencyMemberInvalid err))
deriving (Eq, Show)
dependenciesVal
:: forall err schema.
(schema -> Value -> [err])
-> DependenciesValidator schema
-> HashMap Text Value
-> Maybe (DependenciesInvalid err)
dependenciesVal f (DependenciesValidator hm) x =
let res = HM.mapMaybeWithKey g hm
in if HM.null res
then Nothing
else Just (DependenciesInvalid res)
where
g :: Text -> Dependency schema -> Maybe (DependencyMemberInvalid err)
g k (SchemaDependency schema)
| HM.member k x = SchemaDepInvalid
<$> NE.nonEmpty (f schema (Object x))
| otherwise = Nothing
g k (PropertyDependency ts)
| HM.member k x && not allPresent = Just (PropertyDepInvalid ts x)
| otherwise = Nothing
where
allPresent :: Bool
allPresent = all (`HM.member` x) ts