module Components.ObjectHandlers.ServerObjectValidator (checkObjectsAttributes) where

import qualified Control.Exception as E
import Data.Maybe
import Data.Either
import Model.ServerObjectTypes
import Model.ServerExceptions
import Components.ObjectHandlers.ObjectsHandler


-- check that all nested objects are with valid properties

checkObjectsAttributes :: [RootObject] -> [(String,[String])] -> [(String,[String])] -> Bool
checkObjectsAttributes objs sss sos = foldr (\x y -> (hasValidAttributes x sss sos)&&y) True objs
hasValidAttributes :: NestedObject -> [(String,[String])] -> [(String,[String])] -> Bool
hasValidAttributes (NestedObject alias name sobject ss sfs) sss sos = (if ss==Nothing then True else isValidSubSelection sobject (fromJust ss) sss)&&(isValidSubFields sobject sfs sss sos)
isValidSubSelection :: ServerObject -> ScalarType -> [(String,[String])] -> Bool
isValidSubSelection obj (ScalarType alias name trans arg) sss = (isValidServerObjectScalarField obj name sss)  -- &&(isValidScalarTransformation obj name trans arg)

isValidSubFields :: ServerObject -> [Field] -> [(String,[String])] -> [(String,[String])] -> Bool
isValidSubFields _ [] _ _ = False  -- we should not get an empty query

isValidSubFields obj sfs sss sos = foldr (\x y -> (isValidSubField obj x sss sos)&&y) True sfs
isValidSubField :: ServerObject -> Field -> [(String,[String])]-> [(String,[String])] -> Bool
isValidSubField obj (Left sf) sss sos = (isValidServerObjectScalarField obj sname sss)  -- &&(isValidScalarTransformation obj sname trans arg)

  where
    sname = getScalarName sf
isValidSubField obj sf sss sos = (isValidServerObjectNestedObjectField obj ofname sos)&&(hasValidAttributes nestedObjectField sss sos)
  where
    nestedObjectField = fromRight (E.throw InvalidObjectException) sf
    ofname = getObjectName nestedObjectField