module Components.QueryComposers.SQLQueryComposer (makeSqlQueries) where import Model.ServerObjectTypes (RootObject,NestedObject,SubFields) import Model.ServerExceptions (QueryException(CreatingSqlQueryObjectsException,CreatingSqlQueryObjectFieldsException,InvalidObjectException,InvalidScalarException,RelationshipConfigurationException)) import Components.ObjectHandlers.ObjectsHandler (translateServerObjectToDBName,getSubSelectionArgument,getSubSelectionField,withSubSelection,getDBObjectRelationships,getServerObject,getInlinefragmentObject,getInlinefragmentFields,isServerObjectTable,getSubFields,getScalarName,isServerObjectTable) import Data.Either (fromLeft,fromRight,isRight,isLeft) import Data.Map.Strict (fromList,Map,(!),insertWith) import Control.Exception (throw) makeSqlQueries :: [RootObject] -> [(String,String)] -> [(String,String,[String])] -> [(String,[String],[String])] -> ([[[String]]],[[String]]) makeSqlQueries [] _ _ _ = ([],[]) makeSqlQueries rojs sodn sor soa = unzip $ map unzip $ map (makeSqlQuerySet sodn sor soa) rojs makeSqlQuerySet :: [(String,String)] -> [(String,String,[String])] -> [(String,[String],[String])] -> RootObject -> [([String],String)] makeSqlQuerySet sodn sor soa obj = if (length dbNames)==1 then (addSqlQueryFields (getSubFields obj) (fromList [(firstTable,1)]) ("select "++firstTable++(show 1)++".id,") (" from"++(makeSqlTablePhrase obj firstTable 1)) (" order by "++firstTable++(show 1)++".id asc") (((firstTable,1):[])) [] sodn sor soa (firstTable:[])) else (foldr (\x y -> x++y) [] [(addSqlQueryFields (getSubFields obj) (fromList [(x,1)]) ("select "++x++(show 1)++".id,") (" from"++(makeSqlTablePhrase obj x 1)) (" order by "++x++(show 1)++".id asc") ((x,1):[]) [] sodn sor soa (x:[])) | x<-dbNames]) where dbNames = translateServerObjectToDBName (getServerObject obj) sodn soa firstTable = head dbNames -- making table phrase when there is only one sql table makeSqlTablePhrase :: NestedObject -> String -> Int -> String makeSqlTablePhrase obj name number = if (withSubSelection obj)==True then " (select * from "++name++" where "++(getSubSelectionField obj)++"="++(getSubSelectionArgument obj)++") as "++name++(show number) else " "++name++" as "++name++(show number) addSqlQueryFields :: SubFields -> Map String Int -> String -> String -> String -> [(String,Int)] -> [SubFields] -> [(String,String)] -> [(String,String,[String])] -> [(String,[String],[String])] -> [String] -> [([String],String)] addSqlQueryFields [] counts select from order [] [] _ _ _ tbls = [(tbls,(removeLastChar select)++from++order++";")] addSqlQueryFields [] counts select from order [] _ _ _ _ _ = throw CreatingSqlQueryObjectFieldsException addSqlQueryFields [] counts select from order _ [] _ _ _ tbls = [(tbls,(removeLastChar select)++from++order++";")] addSqlQueryFields [] counts select from order (_:b) (h:t) sodn sor soa tbls = addSqlQueryFields h counts select from order b t sodn sor soa tbls addSqlQueryFields (h:t) counts select from order [] _ _ _ _ _ = throw CreatingSqlQueryObjectsException -- fields without objects addSqlQueryFields (h:t) counts select from order ((ltable,ltableNo):names) fields sodn sor soa tbls | (isLeft h)==True = addSqlQueryFields t counts (select++(ltable++(show ltableNo))++"."++(getScalarName $ fromLeft (throw InvalidScalarException) h)++",") from order ((ltable,ltableNo):names) fields sodn sor soa tbls -- since only difference is table name, I should remove repeated computations by changing only name... | (isLeft fobj)&&(length tables)>1 = foldr (\x y -> x++y) [] [(addSqlQueryFields (getSubFields nobj) (calcNewCounts ltable x counts sor) (select++x++(show $ (!) (calcNewCounts ltable x counts sor) x)++".id,") (from++(makeTransitions (calcNewCounts ltable x counts sor) (getDBObjectRelationships ltable x sor) nobj)) (order++","++x++(show $ (!) (calcNewCounts ltable x counts sor) x)++".id asc") ((x,((calcNewCounts ltable x counts sor) ! x)):(ltable,ltableNo):names) (t:fields) sodn sor) soa (x:tbls) | x<-tables] | (isLeft fobj)&&(length tables)>0 = addSqlQueryFields (getSubFields nobj) firstTableNewCounts (select++firstSubfieldTable++(show $ (!) firstTableNewCounts firstSubfieldTable)++".id,") (from++(makeTransitions firstTableNewCounts (getDBObjectRelationships ltable firstSubfieldTable sor) nobj)) (order++","++firstSubfieldTable++(show $ (!) firstTableNewCounts firstSubfieldTable)++".id asc") ((firstSubfieldTable,firstTableNewCounts ! firstSubfieldTable):(ltable,ltableNo):names) (t:fields) sodn sor soa (firstSubfieldTable:tbls) | (isRight fobj)&&(isServerObjectTable ltable (getInlinefragmentObject ifobj) sodn soa) = addSqlQueryFields ((getInlinefragmentFields ifobj)++t) counts select from order ((ltable,ltableNo):names) fields sodn sor soa tbls | otherwise = addSqlQueryFields t counts select from order ((ltable,ltableNo):names) fields sodn sor soa tbls where fobj = fromRight (throw InvalidObjectException) h nobj = fromLeft (throw InvalidObjectException) fobj ifobj = fromRight (throw InvalidObjectException) fobj tables = translateServerObjectToDBName (getServerObject nobj) sodn soa firstSubfieldTable = head tables firstTableNewCounts = calcNewCounts ltable firstSubfieldTable counts sor calcNewCounts :: String -> String -> Map String Int -> [(String,String,[String])] -> Map String Int calcNewCounts from to pcnt sor = foldr (\x y -> insertWith (+) x 1 y) pcnt (getNewTables $ getDBObjectRelationships from to sor) removeLastChar :: String -> String removeLastChar [] = [] removeLastChar str = init str -- get the tables where we need to increment the tables counter getNewTables :: [String] -> [String] getNewTables lnk = getNewTablesHelper (tail $ tail lnk) 0 getNewTablesHelper :: [String] -> Int -> [String] getNewTablesHelper [] _ = [] getNewTablesHelper (h:t) idx | (idx==0) = h:getNewTablesHelper (tail t) 3 | ((mod idx 3)==0) = h:getNewTablesHelper t (idx+1) | otherwise = getNewTablesHelper t (idx+1) makeTransitions :: Map String Int -> [String] -> NestedObject -> String makeTransitions counts (h1:h2:h3:h4:h5:h6:h7:t) nobj = " inner join "++h5++" as "++h5++(show $ (!) counts h5)++" on "++(makeEqColumns (h1++(show $ (!) counts h1)) h2 (h5++(show $ (!) counts h5)) h6)++(completeTransition counts (h3:h4:h5:h6:h7:t) nobj) makeTransitions counts (h1:h2:h3:h4:t) nobj = " inner join "++(if (withSubSelection nobj)==True then ("(select * from "++h3++" where "++(getSubSelectionField nobj)++"="++(getSubSelectionArgument nobj)++")") else h3)++" as "++h3++(show $ (!) counts h3)++" on "++(makeEqColumns (h1++(show $ (!) counts h1)) h2 (h3++(show $ (!) counts h3)) h4) makeTransitions _ _ _ = throw RelationshipConfigurationException completeTransition :: Map String Int -> [String] -> NestedObject -> String completeTransition counts (h1:h2:h3:h4:h5:[]) nobj = " inner join "++(if (withSubSelection nobj)==True then ("(select * from "++h1++" where "++(getSubSelectionField nobj)++"="++(getSubSelectionArgument nobj)++")") else h1)++" as "++h1++(show $ (!) counts h1)++" on "++(makeEqColumns (h3++(show $ (!) counts h3)) h5 (h1++(show $ (!) counts h1)) h2) completeTransition counts (h1:h2:h3:h4:h5:h6:h7:h8:t) nobj = " inner join "++h6++" as "++h6++(show $ (!) counts h6)++" on "++(makeEqColumns (h3++(show $ (!) counts h3)) h5 (h6++(show $ (!) counts h6)) h7)++(completeTransition counts (h1:h2:h6:h7:h8:t) nobj) completeTransition counts _ _ = throw RelationshipConfigurationException makeEqColumns :: String -> String -> String -> String -> String makeEqColumns tb1 col1 tb2 col2 = if ((elem ' ' col1)==False&&(elem ' ' col2)==False) then (tb1++"."++col1++"="++tb2++"."++col2) else makeEqColumnsHelper "" tb1 col1 tb2 col2 makeEqColumnsHelper :: String -> String -> String -> String -> String -> String makeEqColumnsHelper rlt tb1 col1 tb2 col2 | (elem ' ' col1)&&(elem ' ' col2)&&((length rlt)>0) = makeEqColumnsHelper (rlt++" and "++tb1++"."++fst++"="++tb2++"."++snd) tb1 rmd1 tb2 rmd2 | (elem ' ' col1)&&(elem ' ' col2) = makeEqColumnsHelper (tb1++"."++fst++"="++tb2++"."++snd) tb1 rmd1 tb2 rmd2 | (elem ' ' col1) = throw RelationshipConfigurationException | (elem ' ' col2) = throw RelationshipConfigurationException | ((length rlt)>0) = rlt++" and "++(tb1++"."++col1++"="++tb2++"."++col2) | otherwise = (tb1++"."++col1++"="++tb2++"."++col2) where (fst, rmd1) = getFirstColumn col1 (snd, rmd2) = getFirstColumn col2 getFirstColumn :: String -> (String,String) getFirstColumn str = getFirstColumnHelper "" str getFirstColumnHelper :: String -> String -> (String,String) getFirstColumnHelper _ [] = ([],[]) getFirstColumnHelper acc (h:t) | (h==' ') = (acc,t) | otherwise = getFirstColumnHelper (acc++[h]) t