2018-12-12 15:58:39 +03:00
|
|
|
module Hasura.RQL.DML.Select.Internal
|
|
|
|
( mkSQLSelect
|
|
|
|
, mkAggSelect
|
|
|
|
, module Hasura.RQL.DML.Select.Types
|
|
|
|
)
|
|
|
|
where
|
2018-10-31 15:51:20 +03:00
|
|
|
|
2019-10-18 11:29:47 +03:00
|
|
|
import Control.Lens hiding (op)
|
2020-04-03 11:24:51 +03:00
|
|
|
import qualified Data.List as L
|
2018-12-12 15:58:39 +03:00
|
|
|
import Instances.TH.Lift ()
|
2018-10-31 15:51:20 +03:00
|
|
|
|
2018-12-12 15:58:39 +03:00
|
|
|
import qualified Data.HashMap.Strict as HM
|
|
|
|
import qualified Data.List.NonEmpty as NE
|
|
|
|
import qualified Data.Text as T
|
2018-10-31 15:51:20 +03:00
|
|
|
|
|
|
|
import Hasura.Prelude
|
|
|
|
import Hasura.RQL.DML.Internal
|
2018-12-12 15:58:39 +03:00
|
|
|
import Hasura.RQL.DML.Select.Types
|
2018-10-31 15:51:20 +03:00
|
|
|
import Hasura.RQL.GBoolExp
|
|
|
|
import Hasura.RQL.Types
|
2018-12-12 15:58:39 +03:00
|
|
|
import Hasura.SQL.Rewrite (prefixNumToAliases)
|
2018-10-31 15:51:20 +03:00
|
|
|
import Hasura.SQL.Types
|
|
|
|
|
2018-12-12 15:58:39 +03:00
|
|
|
import qualified Hasura.SQL.DML as S
|
2018-10-31 15:51:20 +03:00
|
|
|
|
|
|
|
-- Conversion of SelectQ happens in 2 Stages.
|
|
|
|
-- Stage 1 : Convert input query into an annotated AST
|
|
|
|
-- Stage 2 : Convert annotated AST to SQL Select
|
|
|
|
|
2019-10-18 11:29:47 +03:00
|
|
|
functionToIden :: QualifiedFunction -> Iden
|
|
|
|
functionToIden = Iden . qualObjectToText
|
2018-11-16 15:40:23 +03:00
|
|
|
|
2019-10-18 11:29:47 +03:00
|
|
|
selFromToFromItem :: Iden -> SelectFrom -> S.FromItem
|
|
|
|
selFromToFromItem pfx = \case
|
|
|
|
FromTable tn -> S.FISimple tn Nothing
|
|
|
|
FromIden i -> S.FIIden i
|
2020-02-13 20:38:23 +03:00
|
|
|
FromFunction qf args defListM ->
|
2019-10-18 11:29:47 +03:00
|
|
|
S.FIFunc $ S.FunctionExp qf (fromTableRowArgs pfx args) $
|
2020-02-13 20:38:23 +03:00
|
|
|
Just $ S.mkFunctionAlias (functionToIden qf) defListM
|
2019-10-18 11:29:47 +03:00
|
|
|
|
2020-02-13 20:38:23 +03:00
|
|
|
-- This function shouldn't be present ideally
|
|
|
|
-- You should be able to retrieve this information
|
|
|
|
-- from the FromItem generated with selFromToFromItem
|
|
|
|
-- however given from S.FromItem is modelled, it is not
|
|
|
|
-- possible currently
|
2019-10-18 11:29:47 +03:00
|
|
|
selFromToQual :: SelectFrom -> S.Qual
|
|
|
|
selFromToQual = \case
|
|
|
|
FromTable tn -> S.QualTable tn
|
2020-02-04 18:34:17 +03:00
|
|
|
FromIden i -> S.QualIden i Nothing
|
2020-02-13 20:38:23 +03:00
|
|
|
FromFunction qf _ _ -> S.QualIden (functionToIden qf) Nothing
|
2018-11-16 15:40:23 +03:00
|
|
|
|
2018-11-12 10:28:46 +03:00
|
|
|
aggFldToExp :: AggFlds -> S.SQLExp
|
|
|
|
aggFldToExp aggFlds = jsonRow
|
2018-10-31 15:51:20 +03:00
|
|
|
where
|
|
|
|
jsonRow = S.applyJsonBuildObj (concatMap aggToFlds aggFlds)
|
|
|
|
withAls fldName sqlExp = [S.SELit fldName, sqlExp]
|
2018-12-12 15:58:39 +03:00
|
|
|
aggToFlds (FieldName t, fld) = withAls t $ case fld of
|
2018-11-14 15:59:59 +03:00
|
|
|
AFCount cty -> S.SECount cty
|
|
|
|
AFOp aggOp -> aggOpToObj aggOp
|
|
|
|
AFExp e -> S.SELit e
|
|
|
|
|
|
|
|
aggOpToObj (AggOp op flds) =
|
2018-10-31 15:51:20 +03:00
|
|
|
S.applyJsonBuildObj $ concatMap (colFldsToExtr op) flds
|
|
|
|
|
2018-12-12 15:58:39 +03:00
|
|
|
colFldsToExtr op (FieldName t, PCFCol col) =
|
2018-10-31 15:51:20 +03:00
|
|
|
[ S.SELit t
|
2018-11-12 10:28:46 +03:00
|
|
|
, S.SEFnApp op [S.SEIden $ toIden col] Nothing
|
2018-10-31 15:51:20 +03:00
|
|
|
]
|
2018-12-12 15:58:39 +03:00
|
|
|
colFldsToExtr _ (FieldName t, PCFExp e) =
|
2018-10-31 15:51:20 +03:00
|
|
|
[ S.SELit t , S.SELit e]
|
|
|
|
|
2018-12-12 15:58:39 +03:00
|
|
|
arrNodeToSelect :: BaseNode -> [S.Extractor] -> S.BoolExp -> S.Select
|
|
|
|
arrNodeToSelect bn extrs joinCond =
|
2018-10-31 15:51:20 +03:00
|
|
|
S.mkSelect
|
2018-12-12 15:58:39 +03:00
|
|
|
{ S.selExtr = extrs
|
|
|
|
, S.selFrom = Just $ S.FromExp [selFrom]
|
|
|
|
}
|
|
|
|
where
|
|
|
|
selFrom = S.mkSelFromItem (baseNodeToSel joinCond bn) $ S.Alias $
|
|
|
|
_bnPrefix bn
|
|
|
|
|
2019-04-26 11:19:59 +03:00
|
|
|
asSingleRowExtr :: S.Alias -> S.SQLExp
|
|
|
|
asSingleRowExtr col =
|
|
|
|
S.SEFnApp "coalesce" [jsonAgg, S.SELit "null"] Nothing
|
2018-10-31 15:51:20 +03:00
|
|
|
where
|
|
|
|
jsonAgg = S.SEOpApp (S.SQLOp "->")
|
|
|
|
[ S.SEFnApp "json_agg" [S.SEIden $ toIden col] Nothing
|
|
|
|
, S.SEUnsafe "0"
|
|
|
|
]
|
|
|
|
|
2019-08-01 08:09:52 +03:00
|
|
|
withJsonAggExtr
|
|
|
|
:: Bool -> Maybe Int -> Maybe S.OrderByExp -> S.Alias -> S.SQLExp
|
|
|
|
withJsonAggExtr subQueryReq permLimitM ordBy alias =
|
|
|
|
-- if select has aggregations then use subquery to apply permission limit
|
|
|
|
if subQueryReq then maybe simpleJsonAgg withPermLimit permLimitM
|
|
|
|
else simpleJsonAgg
|
2018-10-31 15:51:20 +03:00
|
|
|
where
|
2019-08-01 08:09:52 +03:00
|
|
|
simpleJsonAgg = mkSimpleJsonAgg rowIdenExp ordBy
|
2019-04-26 11:19:59 +03:00
|
|
|
rowIdenExp = S.SEIden $ S.getAlias alias
|
|
|
|
subSelAls = Iden "sub_query"
|
|
|
|
unnestTable = Iden "unnest_table"
|
|
|
|
|
|
|
|
mkSimpleJsonAgg rowExp ob =
|
|
|
|
let jsonAggExp = S.SEFnApp "json_agg" [rowExp] ob
|
|
|
|
in S.SEFnApp "coalesce" [jsonAggExp, S.SELit "[]"] Nothing
|
|
|
|
|
|
|
|
withPermLimit limit =
|
|
|
|
let subSelect = mkSubSelect limit
|
|
|
|
rowIden = S.mkQIdenExp subSelAls alias
|
|
|
|
extr = S.Extractor (mkSimpleJsonAgg rowIden newOrdBy) Nothing
|
|
|
|
fromExp = S.FromExp $ pure $
|
|
|
|
S.mkSelFromItem subSelect $ S.Alias subSelAls
|
|
|
|
in S.SESelect $ S.mkSelect { S.selExtr = pure extr
|
|
|
|
, S.selFrom = Just fromExp
|
|
|
|
}
|
|
|
|
|
|
|
|
mkSubSelect limit =
|
|
|
|
let jsonRowExtr = flip S.Extractor (Just alias) $
|
|
|
|
S.mkQIdenExp unnestTable alias
|
|
|
|
obExtrs = flip map newOBAliases $ \a ->
|
|
|
|
S.Extractor (S.mkQIdenExp unnestTable a) $ Just $ S.Alias a
|
|
|
|
in S.mkSelect { S.selExtr = jsonRowExtr : obExtrs
|
|
|
|
, S.selFrom = Just $ S.FromExp $ pure unnestFromItem
|
|
|
|
, S.selLimit = Just $ S.LimitExp $ S.intToSQLExp limit
|
|
|
|
, S.selOrderBy = newOrdBy
|
|
|
|
}
|
|
|
|
|
|
|
|
unnestFromItem =
|
|
|
|
let arrayAggItems = flip map (rowIdenExp : obCols) $
|
|
|
|
\s -> S.SEFnApp "array_agg" [s] Nothing
|
|
|
|
in S.FIUnnest arrayAggItems (S.Alias unnestTable) $
|
|
|
|
rowIdenExp : map S.SEIden newOBAliases
|
|
|
|
|
|
|
|
newOrdBy = bool (Just $ S.OrderByExp newOBItems) Nothing $ null newOBItems
|
|
|
|
|
|
|
|
(newOBItems, obCols, newOBAliases) = maybe ([], [], []) transformOrdBy ordBy
|
|
|
|
transformOrdBy (S.OrderByExp l) = unzip3 $
|
|
|
|
flip map (zip l [1..]) $ \(obItem, i::Int) ->
|
|
|
|
let iden = Iden $ "ob_col_" <> T.pack (show i)
|
|
|
|
in ( obItem{S.oColumn = S.SEIden iden}
|
|
|
|
, S.oColumn obItem
|
|
|
|
, iden
|
|
|
|
)
|
|
|
|
|
|
|
|
asJsonAggExtr
|
2020-02-13 20:38:23 +03:00
|
|
|
:: JsonAggSelect -> S.Alias -> Bool -> Maybe Int -> Maybe S.OrderByExp -> S.Extractor
|
|
|
|
asJsonAggExtr jsonAggSelect als subQueryReq permLimit ordByExpM =
|
|
|
|
flip S.Extractor (Just als) $ case jsonAggSelect of
|
|
|
|
JASMultipleRows -> withJsonAggExtr subQueryReq permLimit ordByExpM als
|
|
|
|
JASSingleObject -> asSingleRowExtr als
|
2018-10-31 15:51:20 +03:00
|
|
|
|
|
|
|
-- array relationships are not grouped, so have to be prefixed by
|
|
|
|
-- parent's alias
|
2018-12-12 15:58:39 +03:00
|
|
|
mkUniqArrRelAls :: FieldName -> [FieldName] -> Iden
|
|
|
|
mkUniqArrRelAls parAls flds =
|
2018-10-31 15:51:20 +03:00
|
|
|
Iden $
|
2018-12-12 15:58:39 +03:00
|
|
|
getFieldNameTxt parAls <> "."
|
|
|
|
<> T.intercalate "." (map getFieldNameTxt flds)
|
2018-10-31 15:51:20 +03:00
|
|
|
|
2018-12-12 15:58:39 +03:00
|
|
|
mkArrRelTableAls :: Iden -> FieldName -> [FieldName] -> Iden
|
|
|
|
mkArrRelTableAls pfx parAls flds =
|
2018-10-31 15:51:20 +03:00
|
|
|
pfx <> Iden ".ar." <> uniqArrRelAls
|
|
|
|
where
|
2018-12-12 15:58:39 +03:00
|
|
|
uniqArrRelAls = mkUniqArrRelAls parAls flds
|
2018-10-31 15:51:20 +03:00
|
|
|
|
|
|
|
mkObjRelTableAls :: Iden -> RelName -> Iden
|
|
|
|
mkObjRelTableAls pfx relName =
|
|
|
|
pfx <> Iden ".or." <> toIden relName
|
|
|
|
|
2019-10-18 11:29:47 +03:00
|
|
|
mkComputedFieldTableAls :: Iden -> FieldName -> Iden
|
|
|
|
mkComputedFieldTableAls pfx fldAls =
|
|
|
|
pfx <> Iden ".cf." <> toIden fldAls
|
|
|
|
|
2018-10-31 15:51:20 +03:00
|
|
|
mkBaseTableAls :: Iden -> Iden
|
|
|
|
mkBaseTableAls pfx =
|
|
|
|
pfx <> Iden ".base"
|
|
|
|
|
|
|
|
mkBaseTableColAls :: Iden -> PGCol -> Iden
|
2020-02-13 20:38:23 +03:00
|
|
|
mkBaseTableColAls pfx pgColumn =
|
|
|
|
pfx <> Iden ".pg." <> toIden pgColumn
|
2018-10-31 15:51:20 +03:00
|
|
|
|
2019-10-05 07:00:53 +03:00
|
|
|
mkOrderByFieldName :: RelName -> FieldName
|
|
|
|
mkOrderByFieldName relName =
|
|
|
|
FieldName $ relNameToTxt relName <> "." <> "order_by"
|
2018-12-12 15:58:39 +03:00
|
|
|
|
2019-10-18 11:29:47 +03:00
|
|
|
fromTableRowArgs
|
|
|
|
:: Iden -> FunctionArgsExpTableRow S.SQLExp -> S.FunctionArgs
|
|
|
|
fromTableRowArgs pfx = toFunctionArgs . fmap toSQLExp
|
|
|
|
where
|
|
|
|
toFunctionArgs (FunctionArgsExp positional named) =
|
|
|
|
S.FunctionArgs positional named
|
2020-02-13 20:38:23 +03:00
|
|
|
toSQLExp (AETableRow Nothing) = S.SERowIden $ mkBaseTableAls pfx
|
|
|
|
toSQLExp (AETableRow (Just acc)) = S.mkQIdenExp (mkBaseTableAls pfx) acc
|
2020-04-27 18:07:03 +03:00
|
|
|
toSQLExp (AESession s) = s
|
2020-02-13 20:38:23 +03:00
|
|
|
toSQLExp (AEInput s) = s
|
2019-10-18 11:29:47 +03:00
|
|
|
|
2018-10-31 15:51:20 +03:00
|
|
|
-- posttgres ignores anything beyond 63 chars for an iden
|
|
|
|
-- in this case, we'll need to use json_build_object function
|
|
|
|
-- json_build_object is slower than row_to_json hence it is only
|
|
|
|
-- used when needed
|
|
|
|
buildJsonObject
|
2019-03-01 14:45:04 +03:00
|
|
|
:: Iden -> FieldName -> ArrRelCtx -> Bool
|
2018-10-31 15:51:20 +03:00
|
|
|
-> [(FieldName, AnnFld)] -> (S.Alias, S.SQLExp)
|
2019-03-01 14:45:04 +03:00
|
|
|
buildJsonObject pfx parAls arrRelCtx strfyNum flds =
|
2018-10-31 15:51:20 +03:00
|
|
|
if any ( (> 63) . T.length . getFieldNameTxt . fst ) flds
|
|
|
|
then withJsonBuildObj parAls jsonBuildObjExps
|
|
|
|
else withRowToJSON parAls rowToJsonExtrs
|
|
|
|
where
|
|
|
|
jsonBuildObjExps = concatMap (toSQLFld withAlsExp) flds
|
|
|
|
rowToJsonExtrs = map (toSQLFld withAlsExtr) flds
|
|
|
|
|
|
|
|
withAlsExp fldName sqlExp =
|
|
|
|
[S.SELit $ getFieldNameTxt fldName, sqlExp]
|
2018-12-13 10:26:15 +03:00
|
|
|
|
2018-10-31 15:51:20 +03:00
|
|
|
withAlsExtr fldName sqlExp =
|
|
|
|
S.Extractor sqlExp $ Just $ S.toAlias fldName
|
|
|
|
|
2018-12-13 10:26:15 +03:00
|
|
|
toSQLFld :: (FieldName -> S.SQLExp -> f)
|
|
|
|
-> (FieldName, AnnFld) -> f
|
2018-10-31 15:51:20 +03:00
|
|
|
toSQLFld f (fldAls, fld) = f fldAls $ case fld of
|
2019-11-07 08:14:36 +03:00
|
|
|
FCol c -> toSQLCol c
|
2018-10-31 15:51:20 +03:00
|
|
|
FExp e -> S.SELit e
|
2018-12-12 15:58:39 +03:00
|
|
|
FObj objSel ->
|
|
|
|
let qual = mkObjRelTableAls pfx $ aarName objSel
|
2018-10-31 15:51:20 +03:00
|
|
|
in S.mkQIdenExp qual fldAls
|
2018-12-12 15:58:39 +03:00
|
|
|
FArr arrSel ->
|
2019-08-01 08:09:52 +03:00
|
|
|
let arrPfx = _aniPrefix $ mkArrNodeInfo pfx parAls arrRelCtx $
|
2019-10-18 11:29:47 +03:00
|
|
|
ANIField (fldAls, arrSel)
|
2018-12-12 15:58:39 +03:00
|
|
|
in S.mkQIdenExp arrPfx fldAls
|
2019-10-18 11:29:47 +03:00
|
|
|
FComputedField (CFSScalar computedFieldScalar) ->
|
|
|
|
fromScalarComputedField computedFieldScalar
|
2020-02-13 20:38:23 +03:00
|
|
|
FComputedField (CFSTable _ _) ->
|
2019-10-18 11:29:47 +03:00
|
|
|
let ccPfx = mkComputedFieldTableAls pfx fldAls
|
|
|
|
in S.mkQIdenExp ccPfx fldAls
|
2020-05-27 18:02:58 +03:00
|
|
|
FRemote _ -> S.SELit "null: remote field selected"
|
2018-10-31 15:51:20 +03:00
|
|
|
|
2019-11-07 08:14:36 +03:00
|
|
|
toSQLCol :: AnnColField -> S.SQLExp
|
|
|
|
toSQLCol (AnnColField col asText colOpM) =
|
|
|
|
toJSONableExp strfyNum (pgiType col) asText $ withColOp colOpM $
|
2019-10-18 11:29:47 +03:00
|
|
|
S.mkQIdenExp (mkBaseTableAls pfx) $ pgiColumn col
|
|
|
|
|
|
|
|
fromScalarComputedField :: ComputedFieldScalarSel S.SQLExp -> S.SQLExp
|
|
|
|
fromScalarComputedField computedFieldScalar =
|
2019-11-07 08:14:36 +03:00
|
|
|
toJSONableExp strfyNum (PGColumnScalar ty) False $ withColOp colOpM $
|
2019-10-18 11:29:47 +03:00
|
|
|
S.SEFunction $ S.FunctionExp fn (fromTableRowArgs pfx args) Nothing
|
2019-03-25 16:45:35 +03:00
|
|
|
where
|
2019-10-18 11:29:47 +03:00
|
|
|
ComputedFieldScalarSel fn args ty colOpM = computedFieldScalar
|
|
|
|
|
|
|
|
withColOp :: Maybe ColOp -> S.SQLExp -> S.SQLExp
|
|
|
|
withColOp colOpM sqlExp = case colOpM of
|
|
|
|
Nothing -> sqlExp
|
|
|
|
Just (ColOp op cExp) -> S.mkSQLOpExp op sqlExp cExp
|
2019-03-25 16:45:35 +03:00
|
|
|
|
2018-10-31 15:51:20 +03:00
|
|
|
-- uses row_to_json to build a json object
|
|
|
|
withRowToJSON
|
|
|
|
:: FieldName -> [S.Extractor] -> (S.Alias, S.SQLExp)
|
|
|
|
withRowToJSON parAls extrs =
|
|
|
|
(S.toAlias parAls, jsonRow)
|
|
|
|
where
|
|
|
|
jsonRow = S.applyRowToJson extrs
|
|
|
|
|
|
|
|
-- uses json_build_object to build a json object
|
|
|
|
withJsonBuildObj
|
|
|
|
:: FieldName -> [S.SQLExp] -> (S.Alias, S.SQLExp)
|
|
|
|
withJsonBuildObj parAls exps =
|
|
|
|
(S.toAlias parAls, jsonRow)
|
|
|
|
where
|
|
|
|
jsonRow = S.applyJsonBuildObj exps
|
|
|
|
|
2018-12-12 15:58:39 +03:00
|
|
|
mkAggObFld :: AnnAggOrdBy -> FieldName
|
|
|
|
mkAggObFld = \case
|
|
|
|
AAOCount -> FieldName "count"
|
|
|
|
AAOOp op col -> FieldName $ op <> "." <> getPGColTxt col
|
|
|
|
|
|
|
|
mkAggObExtrAndFlds :: AnnAggOrdBy -> (S.Extractor, AggFlds)
|
|
|
|
mkAggObExtrAndFlds annAggOb = case annAggOb of
|
|
|
|
AAOCount ->
|
|
|
|
( S.Extractor S.countStar als
|
|
|
|
, [(FieldName "count", AFCount S.CTStar)]
|
|
|
|
)
|
2020-02-13 20:38:23 +03:00
|
|
|
AAOOp op pgColumn ->
|
|
|
|
( S.Extractor (S.SEFnApp op [S.SEIden $ toIden pgColumn] Nothing) als
|
|
|
|
, [(FieldName op, AFOp $ AggOp op [(fromPGCol pgColumn, PCFCol pgColumn)])]
|
2018-12-12 15:58:39 +03:00
|
|
|
)
|
|
|
|
where
|
|
|
|
als = Just $ S.toAlias $ mkAggObFld annAggOb
|
|
|
|
|
2018-10-31 15:51:20 +03:00
|
|
|
processAnnOrderByItem
|
|
|
|
:: Iden
|
2018-12-12 15:58:39 +03:00
|
|
|
-> FieldName
|
|
|
|
-> ArrRelCtx
|
2019-03-01 14:45:04 +03:00
|
|
|
-> Bool
|
2018-10-31 15:51:20 +03:00
|
|
|
-> AnnOrderByItem
|
|
|
|
-- the extractors which will select the needed columns
|
|
|
|
-> ( (S.Alias, S.SQLExp)
|
|
|
|
-- the sql order by item that is attached to the final select
|
|
|
|
, S.OrderByItem
|
2018-12-12 15:58:39 +03:00
|
|
|
-- extra nodes for order by
|
|
|
|
, OrderByNode
|
2018-10-31 15:51:20 +03:00
|
|
|
)
|
2019-03-01 14:45:04 +03:00
|
|
|
processAnnOrderByItem pfx parAls arrRelCtx strfyNum obItemG =
|
2018-10-31 15:51:20 +03:00
|
|
|
( (obColAls, obColExp)
|
|
|
|
, sqlOrdByItem
|
|
|
|
, relNodeM
|
|
|
|
)
|
|
|
|
where
|
2019-03-01 14:45:04 +03:00
|
|
|
OrderByItemG obTyM annObCol obNullsM = obItemG
|
|
|
|
((obColAls, obColExp), relNodeM) =
|
|
|
|
processAnnOrderByCol pfx parAls arrRelCtx strfyNum annObCol
|
2018-10-31 15:51:20 +03:00
|
|
|
|
|
|
|
sqlOrdByItem =
|
2018-12-13 10:26:15 +03:00
|
|
|
S.OrderByItem (S.SEIden $ toIden obColAls)
|
|
|
|
(unOrderType <$> obTyM) (unNullsOrder <$> obNullsM)
|
2018-10-31 15:51:20 +03:00
|
|
|
|
|
|
|
processAnnOrderByCol
|
|
|
|
:: Iden
|
2018-12-12 15:58:39 +03:00
|
|
|
-> FieldName
|
|
|
|
-> ArrRelCtx
|
2019-03-01 14:45:04 +03:00
|
|
|
-> Bool
|
2018-10-31 15:51:20 +03:00
|
|
|
-> AnnObCol
|
|
|
|
-- the extractors which will select the needed columns
|
|
|
|
-> ( (S.Alias, S.SQLExp)
|
2018-12-12 15:58:39 +03:00
|
|
|
-- extra nodes for order by
|
|
|
|
, OrderByNode
|
2018-10-31 15:51:20 +03:00
|
|
|
)
|
2019-03-01 14:45:04 +03:00
|
|
|
processAnnOrderByCol pfx parAls arrRelCtx strfyNum = \case
|
2020-02-13 20:38:23 +03:00
|
|
|
AOCPG pgColumn ->
|
2018-10-31 15:51:20 +03:00
|
|
|
let
|
2020-02-13 20:38:23 +03:00
|
|
|
qualCol = S.mkQIdenExp (mkBaseTableAls pfx) (toIden pgColumn)
|
|
|
|
obColAls = mkBaseTableColAls pfx pgColumn
|
2018-10-31 15:51:20 +03:00
|
|
|
in ( (S.Alias obColAls, qualCol)
|
2018-12-12 15:58:39 +03:00
|
|
|
, OBNNothing
|
2018-10-31 15:51:20 +03:00
|
|
|
)
|
|
|
|
-- "pfx.or.relname"."pfx.ob.or.relname.rest" AS "pfx.ob.or.relname.rest"
|
2018-12-12 15:58:39 +03:00
|
|
|
AOCObj (RelInfo rn _ colMapping relTab _) relFltr rest ->
|
2018-10-31 15:51:20 +03:00
|
|
|
let relPfx = mkObjRelTableAls pfx rn
|
2019-10-05 07:00:53 +03:00
|
|
|
ordByFldName = mkOrderByFieldName rn
|
2018-12-12 15:58:39 +03:00
|
|
|
((nesAls, nesCol), ordByNode) =
|
2019-03-01 14:45:04 +03:00
|
|
|
processAnnOrderByCol relPfx ordByFldName emptyArrRelCtx strfyNum rest
|
2018-12-12 15:58:39 +03:00
|
|
|
(objNodeM, arrNodeM) = case ordByNode of
|
|
|
|
OBNNothing -> (Nothing, Nothing)
|
|
|
|
OBNObjNode name node -> (Just (name, node), Nothing)
|
|
|
|
OBNArrNode als node -> (Nothing, Just (als, node))
|
2018-10-31 15:51:20 +03:00
|
|
|
qualCol = S.mkQIdenExp relPfx nesAls
|
|
|
|
relBaseNode =
|
2018-11-23 04:53:56 +03:00
|
|
|
BaseNode relPfx Nothing (S.FISimple relTab Nothing)
|
2018-11-16 15:40:23 +03:00
|
|
|
(toSQLBoolExp (S.QualTable relTab) relFltr)
|
2018-10-31 15:51:20 +03:00
|
|
|
Nothing Nothing Nothing
|
|
|
|
(HM.singleton nesAls nesCol)
|
2018-12-12 15:58:39 +03:00
|
|
|
(maybe HM.empty (uncurry HM.singleton) objNodeM)
|
|
|
|
(maybe HM.empty (uncurry HM.singleton) arrNodeM)
|
2019-10-18 11:29:47 +03:00
|
|
|
HM.empty
|
2018-12-12 15:58:39 +03:00
|
|
|
relNode = ObjNode colMapping relBaseNode
|
2018-10-31 15:51:20 +03:00
|
|
|
in ( (nesAls, qualCol)
|
2018-12-12 15:58:39 +03:00
|
|
|
, OBNObjNode rn relNode
|
|
|
|
)
|
|
|
|
AOCAgg (RelInfo rn _ colMapping relTab _ ) relFltr annAggOb ->
|
2019-08-01 08:09:52 +03:00
|
|
|
let ArrNodeInfo arrAls arrPfx _ =
|
|
|
|
mkArrNodeInfo pfx parAls arrRelCtx $ ANIAggOrdBy rn
|
2018-12-12 15:58:39 +03:00
|
|
|
fldName = mkAggObFld annAggOb
|
|
|
|
qOrdBy = S.mkQIdenExp arrPfx $ toIden fldName
|
2019-10-18 11:29:47 +03:00
|
|
|
tabFrom = FromTable relTab
|
2018-12-12 15:58:39 +03:00
|
|
|
tabPerm = TablePerm relFltr Nothing
|
|
|
|
(extr, arrFlds) = mkAggObExtrAndFlds annAggOb
|
|
|
|
selFld = TAFAgg arrFlds
|
2019-10-18 11:29:47 +03:00
|
|
|
bn = mkBaseNode False (Prefixes arrPfx pfx) fldName selFld tabFrom
|
2019-08-01 08:09:52 +03:00
|
|
|
tabPerm noTableArgs strfyNum
|
2018-12-12 15:58:39 +03:00
|
|
|
aggNode = ArrNode [extr] colMapping $ mergeBaseNodes bn $
|
|
|
|
mkEmptyBaseNode arrPfx tabFrom
|
|
|
|
obAls = arrPfx <> Iden "." <> toIden fldName
|
|
|
|
in ( (S.Alias obAls, qOrdBy)
|
|
|
|
, OBNArrNode arrAls aggNode
|
2018-10-31 15:51:20 +03:00
|
|
|
)
|
|
|
|
|
2018-11-23 04:53:56 +03:00
|
|
|
processDistinctOnCol
|
|
|
|
:: Iden
|
|
|
|
-> NE.NonEmpty PGCol
|
|
|
|
-> ( S.DistinctExpr
|
|
|
|
-- additional column extractors
|
|
|
|
, [(S.Alias, S.SQLExp)]
|
|
|
|
)
|
|
|
|
processDistinctOnCol pfx neCols = (distOnExp, colExtrs)
|
|
|
|
where
|
|
|
|
cols = toList neCols
|
|
|
|
distOnExp = S.DistinctOn $ map (S.SEIden . toIden . mkQColAls) cols
|
|
|
|
mkQCol c = S.mkQIdenExp (mkBaseTableAls pfx) $ toIden c
|
|
|
|
mkQColAls = S.Alias . mkBaseTableColAls pfx
|
|
|
|
colExtrs = flip map cols $ mkQColAls &&& mkQCol
|
|
|
|
|
|
|
|
|
2019-10-18 11:29:47 +03:00
|
|
|
mkEmptyBaseNode :: Iden -> SelectFrom -> BaseNode
|
|
|
|
mkEmptyBaseNode pfx selectFrom =
|
2018-12-12 15:58:39 +03:00
|
|
|
BaseNode pfx Nothing fromItem (S.BELit True) Nothing Nothing
|
2019-10-18 11:29:47 +03:00
|
|
|
Nothing selOne HM.empty HM.empty HM.empty
|
2018-10-31 15:51:20 +03:00
|
|
|
where
|
|
|
|
selOne = HM.singleton (S.Alias $ pfx <> Iden "__one") (S.SEUnsafe "1")
|
2019-10-18 11:29:47 +03:00
|
|
|
fromItem = selFromToFromItem pfx selectFrom
|
2018-10-31 15:51:20 +03:00
|
|
|
|
2019-10-18 11:29:47 +03:00
|
|
|
aggSelToArrNode :: Prefixes -> FieldName -> ArrRelAgg -> ArrNode
|
|
|
|
aggSelToArrNode pfxs als aggSel =
|
2018-12-12 15:58:39 +03:00
|
|
|
ArrNode [extr] colMapping mergedBN
|
2018-10-31 15:51:20 +03:00
|
|
|
where
|
2018-12-12 15:58:39 +03:00
|
|
|
AnnRelG _ colMapping annSel = aggSel
|
2019-03-01 14:45:04 +03:00
|
|
|
AnnSelG aggFlds tabFrm tabPerm tabArgs strfyNum = annSel
|
2018-10-31 15:51:20 +03:00
|
|
|
fldAls = S.Alias $ toIden als
|
|
|
|
|
|
|
|
extr = flip S.Extractor (Just fldAls) $ S.applyJsonBuildObj $
|
|
|
|
concatMap selFldToExtr aggFlds
|
|
|
|
|
2019-04-26 11:19:59 +03:00
|
|
|
permLimit = _tpLimit tabPerm
|
2018-10-31 15:51:20 +03:00
|
|
|
ordBy = _bnOrderBy mergedBN
|
|
|
|
|
|
|
|
allBNs = map mkAggBaseNode aggFlds
|
2019-10-18 11:29:47 +03:00
|
|
|
emptyBN = mkEmptyBaseNode (_pfThis pfxs) tabFrm
|
2018-10-31 15:51:20 +03:00
|
|
|
mergedBN = foldr mergeBaseNodes emptyBN allBNs
|
|
|
|
|
2018-12-12 15:58:39 +03:00
|
|
|
mkAggBaseNode (fn, selFld) =
|
2019-10-18 11:29:47 +03:00
|
|
|
mkBaseNode subQueryReq pfxs fn selFld tabFrm tabPerm tabArgs strfyNum
|
2018-10-31 15:51:20 +03:00
|
|
|
|
2018-12-12 15:58:39 +03:00
|
|
|
selFldToExtr (FieldName t, fld) = (:) (S.SELit t) $ pure $ case fld of
|
2018-11-12 10:28:46 +03:00
|
|
|
TAFAgg flds -> aggFldToExp flds
|
2019-08-01 08:09:52 +03:00
|
|
|
TAFNodes _ ->
|
|
|
|
withJsonAggExtr subQueryReq permLimit ordBy $ S.Alias $ Iden t
|
2019-04-26 11:19:59 +03:00
|
|
|
TAFExp e ->
|
2018-10-31 15:51:20 +03:00
|
|
|
-- bool_or to force aggregation
|
|
|
|
S.SEFnApp "coalesce"
|
|
|
|
[ S.SELit e , S.SEUnsafe "bool_or('true')::text"] Nothing
|
|
|
|
|
2019-08-01 08:09:52 +03:00
|
|
|
subQueryReq = hasAggFld aggFlds
|
|
|
|
|
|
|
|
hasAggFld :: Foldable t => t (a, TableAggFldG v) -> Bool
|
|
|
|
hasAggFld = any (isTabAggFld . snd)
|
|
|
|
where
|
|
|
|
isTabAggFld (TAFAgg _) = True
|
|
|
|
isTabAggFld _ = False
|
|
|
|
|
|
|
|
mkArrNodeInfo
|
2018-12-12 15:58:39 +03:00
|
|
|
:: Iden
|
|
|
|
-> FieldName
|
|
|
|
-> ArrRelCtx
|
|
|
|
-> ArrNodeItem
|
2019-08-01 08:09:52 +03:00
|
|
|
-> ArrNodeInfo
|
|
|
|
mkArrNodeInfo pfx parAls (ArrRelCtx arrFlds obRels) = \case
|
2018-12-12 15:58:39 +03:00
|
|
|
ANIField aggFld@(fld, annArrSel) ->
|
|
|
|
let (rn, tabArgs) = fetchRNAndTArgs annArrSel
|
2020-04-03 11:24:51 +03:00
|
|
|
similarFlds = getSimilarAggFlds rn tabArgs $ L.delete aggFld
|
2019-08-01 08:09:52 +03:00
|
|
|
similarFldNames = map fst similarFlds
|
2018-12-12 15:58:39 +03:00
|
|
|
similarOrdByFound = rn `elem` obRels && tabArgs == noTableArgs
|
2019-10-05 07:00:53 +03:00
|
|
|
ordByFldName = mkOrderByFieldName rn
|
2018-12-12 15:58:39 +03:00
|
|
|
extraOrdByFlds = bool [] [ordByFldName] similarOrdByFound
|
2020-04-03 11:24:51 +03:00
|
|
|
sortedFlds = L.sort $ fld : (similarFldNames <> extraOrdByFlds)
|
2019-08-01 08:09:52 +03:00
|
|
|
alias = S.Alias $ mkUniqArrRelAls parAls sortedFlds
|
|
|
|
prefix = mkArrRelTableAls pfx parAls sortedFlds
|
|
|
|
in ArrNodeInfo alias prefix $
|
|
|
|
subQueryRequired similarFlds similarOrdByFound
|
2018-12-12 15:58:39 +03:00
|
|
|
ANIAggOrdBy rn ->
|
2019-08-01 08:09:52 +03:00
|
|
|
let similarFlds = map fst $ getSimilarAggFlds rn noTableArgs id
|
2019-10-05 07:00:53 +03:00
|
|
|
ordByFldName = mkOrderByFieldName rn
|
2020-04-03 11:24:51 +03:00
|
|
|
sortedFlds = L.sort $ ordByFldName:similarFlds
|
2019-08-01 08:09:52 +03:00
|
|
|
alias = S.Alias $ mkUniqArrRelAls parAls sortedFlds
|
|
|
|
prefix = mkArrRelTableAls pfx parAls sortedFlds
|
|
|
|
in ArrNodeInfo alias prefix False
|
2018-12-12 15:58:39 +03:00
|
|
|
where
|
2019-08-01 08:09:52 +03:00
|
|
|
getSimilarAggFlds rn tabArgs f =
|
2018-12-12 15:58:39 +03:00
|
|
|
flip filter (f arrFlds) $ \(_, annArrSel) ->
|
|
|
|
let (lrn, lTabArgs) = fetchRNAndTArgs annArrSel
|
|
|
|
in (lrn == rn) && (lTabArgs == tabArgs)
|
|
|
|
|
2019-08-01 08:09:52 +03:00
|
|
|
subQueryRequired similarFlds hasSimOrdBy =
|
|
|
|
hasSimOrdBy || any hasAgg similarFlds
|
|
|
|
|
|
|
|
hasAgg (_, ASSimple _) = False
|
|
|
|
hasAgg (_, ASAgg (AnnRelG _ _ annSel)) = hasAggFld $ _asnFields annSel
|
|
|
|
|
2018-12-12 15:58:39 +03:00
|
|
|
fetchRNAndTArgs (ASSimple (AnnRelG rn _ annSel)) =
|
|
|
|
(rn, _asnArgs annSel)
|
|
|
|
fetchRNAndTArgs (ASAgg (AnnRelG rn _ annSel)) =
|
|
|
|
(rn, _asnArgs annSel)
|
|
|
|
|
|
|
|
fetchOrdByAggRels
|
|
|
|
:: Maybe (NE.NonEmpty AnnOrderByItem)
|
|
|
|
-> [RelName]
|
|
|
|
fetchOrdByAggRels orderByM = fromMaybe [] relNamesM
|
|
|
|
where
|
|
|
|
relNamesM =
|
|
|
|
mapMaybe (fetchAggOrdByRels . obiColumn) . toList <$> orderByM
|
|
|
|
|
|
|
|
fetchAggOrdByRels (AOCAgg ri _ _) = Just $ riName ri
|
|
|
|
fetchAggOrdByRels _ = Nothing
|
|
|
|
|
|
|
|
mkOrdByItems
|
|
|
|
:: Iden -> FieldName
|
|
|
|
-> Maybe (NE.NonEmpty AnnOrderByItem)
|
2019-03-01 14:45:04 +03:00
|
|
|
-> Bool
|
2018-12-12 15:58:39 +03:00
|
|
|
-> ArrRelCtx
|
|
|
|
-- extractors
|
|
|
|
-> ( [(S.Alias, S.SQLExp)]
|
|
|
|
-- object relation nodes
|
|
|
|
, HM.HashMap RelName ObjNode
|
|
|
|
-- array relation aggregate nodes
|
|
|
|
, HM.HashMap S.Alias ArrNode
|
|
|
|
-- final order by expression
|
|
|
|
, Maybe S.OrderByExp
|
|
|
|
)
|
2019-03-01 14:45:04 +03:00
|
|
|
mkOrdByItems pfx fldAls orderByM strfyNum arrRelCtx =
|
2018-12-12 15:58:39 +03:00
|
|
|
(obExtrs, ordByObjsMap, ordByArrsMap, ordByExpM)
|
|
|
|
where
|
2019-03-01 14:45:04 +03:00
|
|
|
procAnnOrdBy' = processAnnOrderByItem pfx fldAls arrRelCtx strfyNum
|
2018-12-12 15:58:39 +03:00
|
|
|
procOrdByM =
|
|
|
|
unzip3 . map procAnnOrdBy' . toList <$> orderByM
|
|
|
|
|
2019-10-18 11:29:47 +03:00
|
|
|
obExtrs = maybe [] (^. _1) procOrdByM
|
|
|
|
ordByExpM = S.OrderByExp . (^. _2) <$> procOrdByM
|
2018-12-12 15:58:39 +03:00
|
|
|
|
2019-10-18 11:29:47 +03:00
|
|
|
ordByObjs = mapMaybe getOrdByRelNode $ maybe [] (^. _3) procOrdByM
|
2018-12-12 15:58:39 +03:00
|
|
|
ordByObjsMap = HM.fromListWith mergeObjNodes ordByObjs
|
|
|
|
|
2019-10-18 11:29:47 +03:00
|
|
|
ordByAggArrs = mapMaybe getOrdByAggNode $ maybe [] (^. _3) procOrdByM
|
2018-12-12 15:58:39 +03:00
|
|
|
ordByArrsMap = HM.fromListWith mergeArrNodes ordByAggArrs
|
|
|
|
|
|
|
|
getOrdByRelNode (OBNObjNode name node) = Just (name, node)
|
|
|
|
getOrdByRelNode _ = Nothing
|
|
|
|
|
|
|
|
getOrdByAggNode (OBNArrNode als node) = Just (als, node)
|
|
|
|
getOrdByAggNode _ = Nothing
|
|
|
|
|
2018-10-31 15:51:20 +03:00
|
|
|
mkBaseNode
|
2019-08-01 08:09:52 +03:00
|
|
|
:: Bool
|
2019-10-18 11:29:47 +03:00
|
|
|
-> Prefixes
|
2019-08-01 08:09:52 +03:00
|
|
|
-> FieldName
|
|
|
|
-> TableAggFld
|
2019-10-18 11:29:47 +03:00
|
|
|
-> SelectFrom
|
2019-08-01 08:09:52 +03:00
|
|
|
-> TablePerm
|
|
|
|
-> TableArgs
|
|
|
|
-> Bool
|
|
|
|
-> BaseNode
|
2019-10-18 11:29:47 +03:00
|
|
|
mkBaseNode subQueryReq pfxs fldAls annSelFlds selectFrom
|
2019-08-01 08:09:52 +03:00
|
|
|
tablePerm tableArgs strfyNum =
|
2019-10-18 11:29:47 +03:00
|
|
|
BaseNode thisPfx distExprM fromItem finalWhere ordByExpM finalLimit offsetM
|
|
|
|
allExtrs allObjsWithOb allArrsWithOb computedFields
|
2018-10-31 15:51:20 +03:00
|
|
|
where
|
2019-10-18 11:29:47 +03:00
|
|
|
Prefixes thisPfx baseTablepfx = pfxs
|
2019-08-01 08:09:52 +03:00
|
|
|
TablePerm permFilter permLimit = tablePerm
|
|
|
|
TableArgs whereM orderByM inpLimitM offsetM distM = tableArgs
|
|
|
|
|
|
|
|
-- if sub query is used, then only use input limit
|
|
|
|
-- because permission limit is being applied in subquery
|
|
|
|
-- else compare input and permission limits
|
|
|
|
finalLimit =
|
|
|
|
if subQueryReq then inpLimitM
|
|
|
|
else withPermLimit
|
|
|
|
|
|
|
|
withPermLimit =
|
|
|
|
case (inpLimitM, permLimit) of
|
|
|
|
(inpLim, Nothing) -> inpLim
|
|
|
|
(Nothing, permLim) -> permLim
|
|
|
|
(Just inp, Just perm) -> Just $ if inp < perm then inp else perm
|
|
|
|
|
|
|
|
|
2018-12-12 15:58:39 +03:00
|
|
|
aggOrdByRelNames = fetchOrdByAggRels orderByM
|
|
|
|
|
2019-10-18 11:29:47 +03:00
|
|
|
(allExtrs, allObjsWithOb, allArrsWithOb, computedFields, ordByExpM) =
|
2018-12-12 15:58:39 +03:00
|
|
|
case annSelFlds of
|
|
|
|
TAFNodes flds ->
|
|
|
|
let arrFlds = mapMaybe getAnnArr flds
|
|
|
|
arrRelCtx = mkArrRelCtx arrFlds
|
2019-10-18 11:29:47 +03:00
|
|
|
selExtr = buildJsonObject thisPfx fldAls arrRelCtx strfyNum flds
|
2018-12-12 15:58:39 +03:00
|
|
|
-- all object relationships
|
|
|
|
objNodes = HM.fromListWith mergeObjNodes $
|
|
|
|
map mkObjItem (mapMaybe getAnnObj flds)
|
|
|
|
-- all array items (array relationships + aggregates)
|
|
|
|
arrNodes = HM.fromListWith mergeArrNodes $
|
|
|
|
map (mkArrItem arrRelCtx) arrFlds
|
2019-10-18 11:29:47 +03:00
|
|
|
-- all computed fields with table returns
|
|
|
|
computedFieldNodes = HM.fromList $ map mkComputedFieldTable $
|
2020-02-13 20:38:23 +03:00
|
|
|
mapMaybe getComputedFieldTable flds
|
2018-12-12 15:58:39 +03:00
|
|
|
|
|
|
|
(obExtrs, ordByObjs, ordByArrs, obeM)
|
|
|
|
= mkOrdByItems' arrRelCtx
|
|
|
|
allObjs = HM.unionWith mergeObjNodes objNodes ordByObjs
|
|
|
|
allArrs = HM.unionWith mergeArrNodes arrNodes ordByArrs
|
|
|
|
|
|
|
|
in ( HM.fromList $ selExtr:obExtrs <> distExtrs
|
|
|
|
, allObjs
|
|
|
|
, allArrs
|
2019-10-18 11:29:47 +03:00
|
|
|
, computedFieldNodes
|
2018-12-12 15:58:39 +03:00
|
|
|
, obeM
|
|
|
|
)
|
|
|
|
TAFAgg tabAggs ->
|
|
|
|
let extrs = concatMap (fetchExtrFromAggFld . snd) tabAggs
|
|
|
|
(obExtrs, ordByObjs, ordByArrs, obeM)
|
|
|
|
= mkOrdByItems' emptyArrRelCtx
|
|
|
|
in ( HM.fromList $ extrs <> obExtrs <> distExtrs
|
|
|
|
, ordByObjs
|
|
|
|
, ordByArrs
|
2019-10-18 11:29:47 +03:00
|
|
|
, HM.empty
|
2018-12-12 15:58:39 +03:00
|
|
|
, obeM
|
|
|
|
)
|
|
|
|
TAFExp _ ->
|
|
|
|
let (obExtrs, ordByObjs, ordByArrs, obeM)
|
|
|
|
= mkOrdByItems' emptyArrRelCtx
|
2019-10-18 11:29:47 +03:00
|
|
|
in (HM.fromList obExtrs, ordByObjs, ordByArrs, HM.empty, obeM)
|
2018-10-31 15:51:20 +03:00
|
|
|
|
2018-11-14 15:59:59 +03:00
|
|
|
fetchExtrFromAggFld (AFCount cty) = countTyToExps cty
|
|
|
|
fetchExtrFromAggFld (AFOp aggOp) = aggOpToExps aggOp
|
|
|
|
fetchExtrFromAggFld (AFExp _) = []
|
|
|
|
|
|
|
|
countTyToExps S.CTStar = []
|
|
|
|
countTyToExps (S.CTSimple cols) = colsToExps cols
|
|
|
|
countTyToExps (S.CTDistinct cols) = colsToExps cols
|
|
|
|
|
|
|
|
colsToExps = mapMaybe (mkColExp . PCFCol)
|
2018-10-31 15:51:20 +03:00
|
|
|
|
2018-11-14 15:59:59 +03:00
|
|
|
aggOpToExps = mapMaybe (mkColExp . snd) . _aoFlds
|
2018-10-31 15:51:20 +03:00
|
|
|
|
|
|
|
mkColExp (PCFCol c) =
|
2019-10-18 11:29:47 +03:00
|
|
|
let qualCol = S.mkQIdenExp (mkBaseTableAls thisPfx) (toIden c)
|
2018-11-12 10:28:46 +03:00
|
|
|
colAls = toIden c
|
2018-10-31 15:51:20 +03:00
|
|
|
in Just (S.Alias colAls, qualCol)
|
|
|
|
mkColExp _ = Nothing
|
|
|
|
|
2019-08-01 08:09:52 +03:00
|
|
|
finalWhere = toSQLBoolExp tableQual $
|
|
|
|
maybe permFilter (andAnnBoolExps permFilter) whereM
|
2019-10-18 11:29:47 +03:00
|
|
|
fromItem = selFromToFromItem baseTablepfx selectFrom
|
|
|
|
tableQual = selFromToQual selectFrom
|
2018-10-31 15:51:20 +03:00
|
|
|
|
2018-12-12 15:58:39 +03:00
|
|
|
mkArrRelCtx arrSels = ArrRelCtx arrSels aggOrdByRelNames
|
|
|
|
|
2019-10-18 11:29:47 +03:00
|
|
|
mkOrdByItems' = mkOrdByItems thisPfx fldAls orderByM strfyNum
|
2018-10-31 15:51:20 +03:00
|
|
|
|
2019-10-18 11:29:47 +03:00
|
|
|
distItemsM = processDistinctOnCol thisPfx <$> distM
|
2018-11-23 04:53:56 +03:00
|
|
|
distExprM = fst <$> distItemsM
|
2020-02-13 20:38:23 +03:00
|
|
|
distExtrs = maybe [] snd distItemsM
|
2018-11-23 04:53:56 +03:00
|
|
|
|
2018-12-12 15:58:39 +03:00
|
|
|
-- process an object relationship
|
|
|
|
mkObjItem (fld, objSel) =
|
|
|
|
let relName = aarName objSel
|
2019-10-18 11:29:47 +03:00
|
|
|
objNodePfx = mkObjRelTableAls thisPfx $ aarName objSel
|
|
|
|
objNode = mkObjNode (Prefixes objNodePfx thisPfx) (fld, objSel)
|
2018-12-12 15:58:39 +03:00
|
|
|
in (relName, objNode)
|
2018-10-31 15:51:20 +03:00
|
|
|
|
2018-12-12 15:58:39 +03:00
|
|
|
-- process an array/array-aggregate item
|
|
|
|
mkArrItem arrRelCtx (fld, arrSel) =
|
2019-08-01 08:09:52 +03:00
|
|
|
let ArrNodeInfo arrAls arrPfx subQReq =
|
2019-10-18 11:29:47 +03:00
|
|
|
mkArrNodeInfo thisPfx fldAls arrRelCtx $ ANIField (fld, arrSel)
|
|
|
|
arrNode = mkArrNode subQReq (Prefixes arrPfx thisPfx) (fld, arrSel)
|
2018-12-12 15:58:39 +03:00
|
|
|
in (arrAls, arrNode)
|
2018-10-31 15:51:20 +03:00
|
|
|
|
2019-10-18 11:29:47 +03:00
|
|
|
-- process a computed field, which returns a table
|
2020-02-13 20:38:23 +03:00
|
|
|
mkComputedFieldTable (fld, jsonAggSelect, sel) =
|
2019-10-18 11:29:47 +03:00
|
|
|
let prefixes = Prefixes (mkComputedFieldTableAls thisPfx fld) thisPfx
|
|
|
|
baseNode = annSelToBaseNode False prefixes fld sel
|
2020-02-13 20:38:23 +03:00
|
|
|
in (fld, CFTableNode jsonAggSelect baseNode)
|
2019-10-18 11:29:47 +03:00
|
|
|
|
2018-12-12 15:58:39 +03:00
|
|
|
getAnnObj (f, annFld) = case annFld of
|
|
|
|
FObj ob -> Just (f, ob)
|
|
|
|
_ -> Nothing
|
|
|
|
|
|
|
|
getAnnArr (f, annFld) = case annFld of
|
|
|
|
FArr ar -> Just (f, ar)
|
|
|
|
_ -> Nothing
|
2018-10-31 15:51:20 +03:00
|
|
|
|
2019-10-18 11:29:47 +03:00
|
|
|
getComputedFieldTable (f, annFld) = case annFld of
|
2020-02-13 20:38:23 +03:00
|
|
|
FComputedField (CFSTable jas sel) -> Just (f, jas, sel)
|
|
|
|
_ -> Nothing
|
2019-10-18 11:29:47 +03:00
|
|
|
|
|
|
|
annSelToBaseNode :: Bool -> Prefixes -> FieldName -> AnnSimpleSel -> BaseNode
|
|
|
|
annSelToBaseNode subQueryReq pfxs fldAls annSel =
|
|
|
|
mkBaseNode subQueryReq pfxs fldAls (TAFNodes selFlds) tabFrm tabPerm tabArgs strfyNum
|
2018-10-31 15:51:20 +03:00
|
|
|
where
|
2019-03-01 14:45:04 +03:00
|
|
|
AnnSelG selFlds tabFrm tabPerm tabArgs strfyNum = annSel
|
2018-10-31 15:51:20 +03:00
|
|
|
|
2019-10-18 11:29:47 +03:00
|
|
|
mkObjNode :: Prefixes -> (FieldName, ObjSel) -> ObjNode
|
|
|
|
mkObjNode pfxs (fldName, AnnRelG _ rMapn rAnnSel) =
|
|
|
|
ObjNode rMapn $ annSelToBaseNode False pfxs fldName rAnnSel
|
2018-10-31 15:51:20 +03:00
|
|
|
|
2019-10-18 11:29:47 +03:00
|
|
|
mkArrNode :: Bool -> Prefixes -> (FieldName, ArrSel) -> ArrNode
|
|
|
|
mkArrNode subQueryReq pfxs (fldName, annArrSel) = case annArrSel of
|
2018-12-12 15:58:39 +03:00
|
|
|
ASSimple annArrRel ->
|
2019-10-18 11:29:47 +03:00
|
|
|
let bn = annSelToBaseNode subQueryReq pfxs fldName $ aarAnnSel annArrRel
|
2019-04-26 11:19:59 +03:00
|
|
|
permLimit = getPermLimit $ aarAnnSel annArrRel
|
2020-02-13 20:38:23 +03:00
|
|
|
extr = asJsonAggExtr JASMultipleRows (S.toAlias fldName) subQueryReq permLimit $
|
2018-12-12 15:58:39 +03:00
|
|
|
_bnOrderBy bn
|
|
|
|
in ArrNode [extr] (aarMapping annArrRel) bn
|
|
|
|
|
2019-10-18 11:29:47 +03:00
|
|
|
ASAgg annAggSel -> aggSelToArrNode pfxs fldName annAggSel
|
2018-10-31 15:51:20 +03:00
|
|
|
|
|
|
|
injectJoinCond :: S.BoolExp -- ^ Join condition
|
|
|
|
-> S.BoolExp -- ^ Where condition
|
|
|
|
-> S.WhereFrag -- ^ New where frag
|
|
|
|
injectJoinCond joinCond whereCond =
|
|
|
|
S.WhereFrag $ S.simplifyBoolExp $ S.BEBin S.AndOp joinCond whereCond
|
|
|
|
|
2019-12-13 00:46:33 +03:00
|
|
|
mkJoinCond :: S.Alias -> HashMap PGCol PGCol -> S.BoolExp
|
2019-10-18 11:29:47 +03:00
|
|
|
mkJoinCond baseTablepfx colMapn =
|
2019-12-13 00:46:33 +03:00
|
|
|
foldl' (S.BEBin S.AndOp) (S.BELit True) $ flip map (HM.toList colMapn) $ \(lCol, rCol) ->
|
2019-10-18 11:29:47 +03:00
|
|
|
S.BECompare S.SEQ (S.mkQIdenExp baseTablepfx lCol) (S.mkSIdenExp rCol)
|
2018-10-31 15:51:20 +03:00
|
|
|
|
|
|
|
baseNodeToSel :: S.BoolExp -> BaseNode -> S.Select
|
2018-11-23 04:53:56 +03:00
|
|
|
baseNodeToSel joinCond baseNode =
|
2018-10-31 15:51:20 +03:00
|
|
|
S.mkSelect
|
|
|
|
{ S.selExtr = [S.Extractor e $ Just a | (a, e) <- HM.toList extrs]
|
|
|
|
, S.selFrom = Just $ S.FromExp [joinedFrom]
|
|
|
|
, S.selOrderBy = ordByM
|
|
|
|
, S.selLimit = S.LimitExp . S.intToSQLExp <$> limitM
|
|
|
|
, S.selOffset = S.OffsetExp <$> offsetM
|
2018-11-23 04:53:56 +03:00
|
|
|
, S.selDistinct = dExp
|
2018-10-31 15:51:20 +03:00
|
|
|
}
|
|
|
|
where
|
2018-11-23 04:53:56 +03:00
|
|
|
BaseNode pfx dExp fromItem whr ordByM limitM
|
2019-10-18 11:29:47 +03:00
|
|
|
offsetM extrs objRels arrRels computedFields
|
2018-11-23 04:53:56 +03:00
|
|
|
= baseNode
|
2018-10-31 15:51:20 +03:00
|
|
|
-- this is the table which is aliased as "pfx.base"
|
|
|
|
baseSel = S.mkSelect
|
2020-01-16 07:53:28 +03:00
|
|
|
{ S.selExtr = [S.Extractor (S.SEStar Nothing) Nothing]
|
2018-10-31 15:51:20 +03:00
|
|
|
, S.selFrom = Just $ S.FromExp [fromItem]
|
|
|
|
, S.selWhere = Just $ injectJoinCond joinCond whr
|
|
|
|
}
|
|
|
|
baseSelAls = S.Alias $ mkBaseTableAls pfx
|
2020-05-13 11:09:44 +03:00
|
|
|
baseFromItem = S.mkSelFromItem baseSel baseSelAls
|
2018-10-31 15:51:20 +03:00
|
|
|
|
|
|
|
-- function to create a joined from item from two from items
|
|
|
|
leftOuterJoin current new =
|
|
|
|
S.FIJoin $ S.JoinExpr current S.LeftOuter new $
|
|
|
|
S.JoinOn $ S.BELit True
|
|
|
|
|
|
|
|
-- this is the from eexp for the final select
|
|
|
|
joinedFrom :: S.FromItem
|
|
|
|
joinedFrom = foldl' leftOuterJoin baseFromItem $
|
2018-12-12 15:58:39 +03:00
|
|
|
map objNodeToFromItem (HM.elems objRels) <>
|
2019-10-18 11:29:47 +03:00
|
|
|
map arrNodeToFromItem (HM.elems arrRels) <>
|
|
|
|
map computedFieldNodeToFromItem (HM.toList computedFields)
|
2018-10-31 15:51:20 +03:00
|
|
|
|
2018-12-12 15:58:39 +03:00
|
|
|
objNodeToFromItem :: ObjNode -> S.FromItem
|
|
|
|
objNodeToFromItem (ObjNode relMapn relBaseNode) =
|
2018-10-31 15:51:20 +03:00
|
|
|
let als = S.Alias $ _bnPrefix relBaseNode
|
|
|
|
sel = baseNodeToSel (mkJoinCond baseSelAls relMapn) relBaseNode
|
|
|
|
in S.mkLateralFromItem sel als
|
|
|
|
|
2018-12-12 15:58:39 +03:00
|
|
|
arrNodeToFromItem :: ArrNode -> S.FromItem
|
|
|
|
arrNodeToFromItem (ArrNode es colMapn bn) =
|
|
|
|
let sel = arrNodeToSelect bn es (mkJoinCond baseSelAls colMapn)
|
|
|
|
als = S.Alias $ _bnPrefix bn
|
2018-10-31 15:51:20 +03:00
|
|
|
in S.mkLateralFromItem sel als
|
|
|
|
|
2020-02-13 20:38:23 +03:00
|
|
|
computedFieldNodeToFromItem :: (FieldName, CFTableNode) -> S.FromItem
|
|
|
|
computedFieldNodeToFromItem (fld, CFTableNode jsonAggSelect bn) =
|
2019-10-18 11:29:47 +03:00
|
|
|
let internalSel = baseNodeToSel (S.BELit True) bn
|
|
|
|
als = S.Alias $ _bnPrefix bn
|
2020-02-13 20:38:23 +03:00
|
|
|
extr = asJsonAggExtr jsonAggSelect (S.toAlias fld) False Nothing $
|
2019-10-18 11:29:47 +03:00
|
|
|
_bnOrderBy bn
|
|
|
|
internalSelFrom = S.mkSelFromItem internalSel als
|
|
|
|
sel = S.mkSelect
|
|
|
|
{ S.selExtr = pure extr
|
|
|
|
, S.selFrom = Just $ S.FromExp [internalSelFrom]
|
|
|
|
}
|
|
|
|
in S.mkLateralFromItem sel als
|
|
|
|
|
2018-12-12 15:58:39 +03:00
|
|
|
mkAggSelect :: AnnAggSel -> S.Select
|
|
|
|
mkAggSelect annAggSel =
|
|
|
|
prefixNumToAliases $ arrNodeToSelect bn extr $ S.BELit True
|
|
|
|
where
|
2019-12-13 00:46:33 +03:00
|
|
|
aggSel = AnnRelG rootRelName HM.empty annAggSel
|
2019-10-18 11:29:47 +03:00
|
|
|
rootIden = Iden "root"
|
|
|
|
rootPrefix = Prefixes rootIden rootIden
|
2018-12-12 15:58:39 +03:00
|
|
|
ArrNode extr _ bn =
|
2019-10-18 11:29:47 +03:00
|
|
|
aggSelToArrNode rootPrefix (FieldName "root") aggSel
|
2018-12-12 15:58:39 +03:00
|
|
|
|
2020-02-13 20:38:23 +03:00
|
|
|
mkSQLSelect :: JsonAggSelect -> AnnSimpleSel -> S.Select
|
|
|
|
mkSQLSelect jsonAggSelect annSel =
|
2018-12-12 15:58:39 +03:00
|
|
|
prefixNumToAliases $ arrNodeToSelect baseNode extrs $ S.BELit True
|
|
|
|
where
|
2019-04-26 11:19:59 +03:00
|
|
|
permLimit = getPermLimit annSel
|
2020-02-13 20:38:23 +03:00
|
|
|
extrs = pure $ asJsonAggExtr jsonAggSelect rootFldAls False permLimit
|
2019-04-26 11:19:59 +03:00
|
|
|
$ _bnOrderBy baseNode
|
2019-10-18 11:29:47 +03:00
|
|
|
rootFldIden = toIden rootFldName
|
|
|
|
rootPrefix = Prefixes rootFldIden rootFldIden
|
|
|
|
baseNode = annSelToBaseNode False rootPrefix rootFldName annSel
|
2018-12-12 15:58:39 +03:00
|
|
|
rootFldName = FieldName "root"
|
|
|
|
rootFldAls = S.Alias $ toIden rootFldName
|