module Data.Validator.Draft4.Object
( module Data.Validator.Draft4.Object
, module Data.Validator.Draft4.Object.Properties
) where
import Import
import Prelude hiding (all, concat,
foldl)
import Data.Aeson.Types (Parser)
import qualified Data.HashMap.Strict as H
import Data.Set (Set)
import qualified Data.Set as S
import qualified Data.Text as T
import Data.Validator.Draft4.Object.Properties
import Data.Validator.Failure (Fail(..))
import Data.Validator.Utils
maxProperties :: Int -> HashMap Text Value -> Maybe (Fail ())
maxProperties n x
| n < 0 = Nothing
| H.size x > n = Just (Failure () (toJSON n) mempty (Object x))
| otherwise = Nothing
minProperties :: Int -> HashMap Text Value -> Maybe (Fail ())
minProperties n x
| n < 0 = Nothing
| H.size x < n = Just (Failure () (toJSON n) mempty (Object x))
| otherwise = Nothing
newtype Required
= Required { _unRequired :: Set Text }
deriving (Eq, Show, ToJSON)
instance FromJSON Required where
parseJSON v = checkUnique =<< checkSize =<< parseJSON v
where
checkSize :: [Text] -> Parser [Text]
checkSize a
| null a = fail "Required validator must not be empty."
| otherwise = pure a
checkUnique :: [Text] -> Parser Required
checkUnique a =
let b = S.fromList a
in if length a == S.size b
then pure (Required b)
else fail "All elements of the Required validator must be unique."
instance Arbitrary Required where
arbitrary = do
x <- arbitraryText
xs <- (fmap.fmap) T.pack arbitrary
pure . Required . S.fromList $ x:xs
required :: Required -> HashMap Text Value -> Maybe (Fail ())
required (Required ts) x
| S.null ts = Nothing
| H.null (H.difference hm x) = Nothing
| otherwise = Just (Failure () (toJSON ts)
mempty (Object x))
where
hm :: HashMap Text Bool
hm = foldl (\b a -> H.insert a True b) mempty ts
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 DependencyInvalid err
= SchemaDependencyInvalid err
| PropertyDependencyInvalid
deriving (Eq, Show)
dependencies
:: forall err schema.
(schema -> Value -> [Fail err])
-> HashMap Text (Dependency schema)
-> HashMap Text Value
-> [Fail (DependencyInvalid err)]
dependencies f hm x = concat . fmap (uncurry g) . H.toList $ hm
where
g :: Text -> Dependency schema -> [Fail (DependencyInvalid err)]
g k (SchemaDependency schema)
| H.member k x =
fmap SchemaDependencyInvalid <$> f schema (Object x)
| otherwise = mempty
g k (PropertyDependency ts)
| H.member k x && not allPresent =
pure $ Failure PropertyDependencyInvalid
(toJSON (H.singleton k ts))
mempty
(Object x)
| otherwise = mempty
where
allPresent :: Bool
allPresent = all (`H.member` x) ts