module Components.DataProcessors.PersistentDataProcessor where import Data.Maybe import Data.Either import Data.Text (Text) import Text.JSON (encodeStrict,toJSObject,JSValue,showJSONs,toJSObject,showJSON) import qualified Control.Exception as E import Model.ServerExceptions import Model.ServerObjectTypes import Components.ObjectHandlers.ObjectsHandler (getSubFields) -- with root objects we want one json representation of separate graphql results... processReturnedValues :: [RootObject] -> [[[[Text]]]] -> String processReturnedValues robjs rlts = encodeStrict $ toJSObject [("data", toJSObject [processReturnedValue x y | x<-robjs, y<-groupSingleQueryResults rlts])] -- with separated sql query results, we want a list of data rows that are separated by only graphql query... groupSingleQueryResults :: [[[[Text]]]] -> [[[Text]]] groupSingleQueryResults rlts = [foldr (\y z -> y++z) [] x | x<-rlts] -- with qraphql query object and sql return data, we want json representation on graphql query results... processReturnedValue :: RootObject -> [[Text]] -> (String, JSValue) processReturnedValue (NestedObject alias name _ _ sfs) rlts = (if (alias==Nothing) then name else (fromJust alias), showJSONs $ processSubFields sfs rlts) -- with SubFields and data rows, we want json representation on qraphql query data processSubFields :: [Field] -> [[Text]] -> [JSValue] processSubFields _ [] = [] processSubFields sfs rlts = ((showJSON $ toJSObject $ composeGraphQlRow sfs $ fetchGraphQlRow rlts):(processSubFields sfs $ removeDataRow rlts)) composeGraphQlRow :: [Field] -> [[Text]] -> [(String,JSValue)] composeGraphQlRow [] [[]] = [] -- done composeGraphQlRow [] _ = E.throw EOFDataProcessingException composeGraphQlRow _ [[]] = E.throw EOFDataProcessingException composeGraphQlRow (a:b) ((h:t):j) | (isLeft a)==True = (((getScalarFieldLabel $ fromLeft (E.throw InvalidScalarException) a), (showJSON h)):(composeGraphQlRow b (removeNDataColumns 1 ((h:t):j)))) | otherwise = (((getNestedObjectFieldLabel $ fromRight (E.throw InvalidObjectException) a), showJSONs (processSubFields (getSubFields $ fromRight (E.throw InvalidObjectException) a) (pullNDataColumns nestedObjectFieldCount ((h:t):j)))):(composeGraphQlRow b (removeNDataColumns nestedObjectFieldCount ((h:t):j)))) where nestedObjectFieldCount = (countNestedObjectQueriedFields $ fromRight (E.throw InvalidObjectException) a) fetchGraphQlRow :: [[Text]] -> [[Text]] fetchGraphQlRow rlts = [t | (h:t)<-rlts, (h)==(head $ head rlts)] removeDataRow :: [[Text]] -> [[Text]] removeDataRow rlts = [x | x<-rlts, (head x)/=(head $ head rlts)] getScalarFieldLabel :: ScalarType -> String getScalarFieldLabel (ScalarType alias name trans arg) = if (alias/=Nothing) then (fromJust alias) else name getNestedObjectFieldLabel :: NestedObject -> String getNestedObjectFieldLabel (NestedObject alias name sobj ss sfs) = if (alias/=Nothing) then (fromJust alias) else name pullNDataColumns :: Int -> [[Text]] -> [[Text]] pullNDataColumns _ [] = [] pullNDataColumns cnt rslt | (cnt<0) = E.throw InvalidArgumentException | otherwise = [if (length x) Int countNestedObjectQueriedFields (NestedObject alias name sobj ss sfs) = 1+(countNestedObjectQueriedSubFields sfs) countNestedObjectQueriedSubFields :: [Field] -> Int countNestedObjectQueriedSubFields [] = 0 countNestedObjectQueriedSubFields (h:t) | (isLeft h)==True = 1+(countNestedObjectQueriedSubFields t) | otherwise = (countNestedObjectQueriedFields (fromRight (E.throw InvalidObjectException) h))+(countNestedObjectQueriedSubFields t) -- remove nested object columns from data row that is including nested object id removeNDataColumns :: Int -> [[Text]] -> [[Text]] removeNDataColumns 0 rslt = rslt removeNDataColumns (-1) _ = E.throw EOFDataProcessingException removeNDataColumns _ [[]] = [[]] removeNDataColumns _ ([]:t) = E.throw EOFDataProcessingException removeNDataColumns cnt rslt = removeNDataColumns (cnt-1) [t | (h:t)<-rslt]