module Components.ObjectHandlers.ServerObjectTrimmer (mergeDuplicatedRootObjects) where
import Control.Exception (throw)
import Model.ServerObjectTypes (
RootObject,
NestedObject(..),
ScalarType,
Field,
InlinefragmentObject(..)
)
import Model.ServerExceptions (
QueryException(
DuplicateRootObjectsException,
FailedObjectEqualityException
)
)
import Components.ObjectHandlers.ObjectsHandler (
isSameNObjectReference,
isSameIFObjectReference,
isSameObjectSubSelection
)
mergeDuplicatedRootObjects :: [RootObject] -> [RootObject]
mergeDuplicatedRootObjects [] = []
mergeDuplicatedRootObjects robjs = mergeDuplicatedRootObjectsHelper robjs []
mergeDuplicatedRootObjectsHelper :: [RootObject] -> [RootObject] -> [RootObject]
mergeDuplicatedRootObjectsHelper [] rst = rst
mergeDuplicatedRootObjectsHelper (h:t) rst = mergeDuplicatedRootObjectsHelper differences (rst++[mergeDuplicates h duplicates])
where (duplicates, differences) = separateDuplicatesAndDifferences h t
separateDuplicatesAndDifferences :: RootObject -> [RootObject] -> ([RootObject],[RootObject])
separateDuplicatesAndDifferences robj [] = ([],[])
separateDuplicatesAndDifferences robj lst = separateDuplicatesAndDifferencesHelper robj lst [] []
separateDuplicatesAndDifferencesHelper :: RootObject -> [RootObject] -> [RootObject] -> [RootObject] -> ([RootObject],[RootObject])
separateDuplicatesAndDifferencesHelper robj [] dup diff = (dup,diff)
separateDuplicatesAndDifferencesHelper robj (h:t) dup diff
| (isSameNObjectReference robj h)&&(isSameObjectSubSelection robj h) = separateDuplicatesAndDifferencesHelper robj t (h:dup) diff
| (isSameNObjectReference robj h) = throw DuplicateRootObjectsException
| otherwise = separateDuplicatesAndDifferencesHelper robj t dup (h:diff)
mergeDuplicates :: RootObject -> [RootObject] -> RootObject
mergeDuplicates robj [] = robj
mergeDuplicates (NestedObject alias name sobj ss sf1) ((NestedObject _ _ _ _ sf2):t) = mergeDuplicates (NestedObject alias name sobj ss (compressSubFields (sf1++sf2))) t
compressSubFields :: [Field] -> [Field]
compressSubFields [] = []
compressSubFields lst = compressSubFieldsHelper lst []
compressSubFieldsHelper :: [Field] -> [Field] -> [Field]
compressSubFieldsHelper [] rst = rst
compressSubFieldsHelper ((Left h):t) rst = compressSubFieldsHelper t (combineScalarTypeWithPresent rst h)
compressSubFieldsHelper ((Right (Left h)):t) rst = compressSubFieldsHelper t (combineNestedObjectWithPresent rst h)
compressSubFieldsHelper ((Right (Right h)):t) rst = compressSubFieldsHelper t (combineInlinefragmentObjectWithPresent rst h)
combineScalarTypeWithPresent :: [Field] -> ScalarType -> [Field]
combineScalarTypeWithPresent fld st = combineScalarTypeWithPresentHelper fld st []
combineScalarTypeWithPresentHelper :: [Field] -> ScalarType -> [Field] -> [Field]
combineScalarTypeWithPresentHelper [] st acc = acc++[Left st]
combineScalarTypeWithPresentHelper ((Left h):t) st acc
| h==st = acc++((Left h):t)
combineScalarTypeWithPresentHelper (h:t) st acc = combineScalarTypeWithPresentHelper t st $ acc++[h]
combineNestedObjectWithPresent :: [Field] -> NestedObject -> [Field]
combineNestedObjectWithPresent fld no = combineNestedObjectWithPresentHelper fld no []
combineNestedObjectWithPresentHelper :: [Field] -> NestedObject -> [Field] -> [Field]
combineNestedObjectWithPresentHelper [] no acc = acc++[Right $ Left no]
combineNestedObjectWithPresentHelper ((Right (Left h)):t) no acc
| (isSameNObjectReference h no)&&(isSameObjectSubSelection h no) = ((Right $ Left $ mergeNObjects h no):t)++acc
| isSameNObjectReference h no = throw DuplicateRootObjectsException
| otherwise = combineNestedObjectWithPresentHelper t no ((Right $ Left h):acc)
combineNestedObjectWithPresentHelper (h:t) no acc = combineNestedObjectWithPresentHelper t no (h:acc)
combineInlinefragmentObjectWithPresent :: [Field] -> InlinefragmentObject -> [Field]
combineInlinefragmentObjectWithPresent [] ifo = [Right $ Right ifo]
combineInlinefragmentObjectWithPresent ((Right (Left h)):t) ifo = (Right $ Left h):combineInlinefragmentObjectWithPresent t ifo
combineInlinefragmentObjectWithPresent ((Right (Right h)):t) ifo
| isSameIFObjectReference h ifo = (Right $ Right $ mergeIFObjects h ifo):t
combineInlinefragmentObjectWithPresent (h:t) ifo = h:combineInlinefragmentObjectWithPresent t ifo
mergeNObjects :: NestedObject -> NestedObject -> NestedObject
mergeNObjects (NestedObject alias1 name1 sobj1 ss1 sfs1) (NestedObject alias2 name2 sobj2 ss2 sfs2) = if alias1==alias2&&name1==name2&&sobj1==sobj2&&ss1==ss2 then NestedObject alias1 name1 sobj1 ss1 (compressSubFields (sfs1++sfs2)) else throw FailedObjectEqualityException
mergeIFObjects :: InlinefragmentObject -> InlinefragmentObject -> InlinefragmentObject
mergeIFObjects (InlinefragmentObject sobj1 sfs1) (InlinefragmentObject sobj2 sfs2) = if sobj1==sobj2 then InlinefragmentObject sobj1 (compressSubFields (sfs1++sfs2)) else throw FailedObjectEqualityException