diff --git a/src/PostgREST/ApiRequest/Types.hs b/src/PostgREST/ApiRequest/Types.hs index 9dbd369da1..e98133016a 100644 --- a/src/PostgREST/ApiRequest/Types.hs +++ b/src/PostgREST/ApiRequest/Types.hs @@ -144,7 +144,7 @@ type Cast = Text type Alias = Text type Hint = Text -data AggregateFunction = Sum | Avg | Max | Min | Count | ArrayAgg +data AggregateFunction = Sum | Avg | Max | Min | Count | ArrayAgg { aaFilters :: [FieldName] } deriving (Show, Eq) data EmbedParam diff --git a/src/PostgREST/Plan.hs b/src/PostgREST/Plan.hs index 397f7cf33c..e8f4dc377e 100644 --- a/src/PostgREST/Plan.hs +++ b/src/PostgREST/Plan.hs @@ -332,6 +332,7 @@ readPlan qi@QualifiedIdentifier{..} AppConfig{configDbMaxRows, configDbAggregate in mapLeft ApiRequestError $ treeRestrictRange configDbMaxRows (iAction apiRequest) =<< + addFiltersToArrayAgg ctx =<< hoistSpreadAggFunctions =<< validateAggFunctions configDbAggregates =<< addRelSelects =<< @@ -635,7 +636,7 @@ addArrayAggToManySpread (Node rp@ReadPlan{select} forest) = shouldAddArrayAgg = spreadRelIsNestedInToMany rp fieldToArrayAgg field | isJust $ csAggFunction field = field - | otherwise = field { csAggFunction = Just ArrayAgg, csAlias = newAlias (csAlias field) (cfName $ csField field) } + | otherwise = field { csAggFunction = Just $ ArrayAgg [], csAlias = newAlias (csAlias field) (cfName $ csField field) } newAlias alias fieldName = maybe (Just fieldName) pure alias addRelSelects :: ReadPlanTree -> Either ApiRequestError ReadPlanTree @@ -676,11 +677,58 @@ generateSpreadSelectFields rp@ReadPlan{select, relSelect} = relSelectToSpread :: RelSelectField -> [SpreadSelectField] relSelectToSpread (JsonEmbed{rsSelName}) = -- The regular embeds that are nested inside spread to-many relationships are also aggregated in an array - let (aggFun, alias) = if spreadRelIsNestedInToMany rp then (Just ArrayAgg, Just rsSelName) else (Nothing, Nothing) in + let (aggFun, alias) = if spreadRelIsNestedInToMany rp then (Just $ ArrayAgg [], Just rsSelName) else (Nothing, Nothing) in [SpreadSelectField { ssSelName = rsSelName, ssSelAggFunction = aggFun, ssSelAggCast = Nothing, ssSelAlias = alias }] relSelectToSpread (Spread{rsSpreadSel}) = rsSpreadSel +addFiltersToArrayAgg :: ResolverContext -> ReadPlanTree -> Either ApiRequestError ReadPlanTree +addFiltersToArrayAgg ctx rpt = Right $ applyAddArrayAggFilters ctx [] rpt + +applyAddArrayAggFilters :: ResolverContext -> [(Alias, [CoercibleSelectField])] -> ReadPlanTree -> ReadPlanTree +applyAddArrayAggFilters ctx pkSelectFields (Node rp@ReadPlan{select, relSelect, relAggAlias} forest) = + let newForest = applyAddArrayAggFilters ctx getFKSelectFields <$> forest + newSelects + | null pkSelectFields = select + | otherwise = select ++ fromMaybe mempty (lookup relAggAlias pkSelectFields) + newRelSelects + | null getFKAliases = relSelect + | otherwise = buildFKRelSelect <$> relSelect + in Node rp { select = newSelects, relSelect = newRelSelects } newForest + where + -- Verify if the current node has an array aggregate in the relSelect + spreadHasArrAgg Spread{rsSpreadSel} = any (\case Just (ArrayAgg _) -> True; _ -> False; . ssSelAggFunction) rsSpreadSel + spreadHasArrAgg _ = False + aggSpreads = mapMaybe (\r -> if spreadHasArrAgg r then Just (rsAggAlias r) else Nothing) relSelect + + -- If it has array aggregates, navigate the children nodes to get the unique FK that will be used as filters for said aggregates + allFKSelectFieldsAndAliases = mapMaybe findFKField forest + findFKField :: ReadPlanTree -> Maybe ((Alias, [Alias]), (Alias, [CoercibleSelectField])) + findFKField (Node ReadPlan{relAggAlias=childAggAlias, from=childTbl, relToParent=childToParent} _) = + if childAggAlias `elem` aggSpreads + then Just ((childAggAlias, fst fkFlds), (childAggAlias, snd fkFlds)) + else Nothing + where + fkAlias field = childAggAlias <> "_" <> field <> "_fk" + toSelectField fld = CoercibleSelectField (resolveOutputField ctx{qi=childTbl} (fld, mempty)) Nothing Nothing Nothing (Just $ fkAlias fld) + fkFlds = unzip $ map (\fk -> (fkAlias fk, toSelectField fk)) + (case childToParent of + Just Relationship{relCardinality = M2M j} -> fst <$> junColsTarget j + Just Relationship{relCardinality = O2M _ cols} -> snd <$> cols + _ -> mempty) + + (getFKAliases, getFKSelectFields) = unzip allFKSelectFieldsAndAliases + + -- Add the FKFields to every ArrayAgg of the respective Spread relSelect + buildFKRelSelect rs@Spread{rsAggAlias=rsAlias, rsSpreadSel=rsSel} = + case lookup rsAlias getFKAliases of + Just fkAliases -> rs{rsSpreadSel= addFilterToArrAgg fkAliases <$> rsSel} + _ -> rs + buildFKRelSelect rs = rs + addFilterToArrAgg fkAliases sel = case ssSelAggFunction sel of + Just (ArrayAgg _) -> sel{ssSelAggFunction = Just $ ArrayAgg fkAliases} + _ -> sel + -- When aggregates are present in a ReadPlan that will be spread, we "hoist" -- to the highest level possible so that their semantics make sense. For instance, -- imagine the user performs the following request: @@ -763,7 +811,7 @@ hoistIntoRelSelectFields _ r = r validateAggFunctions :: Bool -> ReadPlanTree -> Either ApiRequestError ReadPlanTree validateAggFunctions aggFunctionsAllowed (Node rp@ReadPlan {select} forest) - | not aggFunctionsAllowed && any (maybe False (/= ArrayAgg) . csAggFunction) select = Left AggregatesNotAllowed + | not aggFunctionsAllowed && any (maybe False (\case ArrayAgg _ -> False; _ -> True) . csAggFunction) select = Left AggregatesNotAllowed | otherwise = Node rp <$> traverse (validateAggFunctions aggFunctionsAllowed) forest addFilters :: ResolverContext -> ApiRequest -> ReadPlanTree -> Either ApiRequestError ReadPlanTree diff --git a/src/PostgREST/Query/SqlFragment.hs b/src/PostgREST/Query/SqlFragment.hs index c9d9b2cc26..76ad57067f 100644 --- a/src/PostgREST/Query/SqlFragment.hs +++ b/src/PostgREST/Query/SqlFragment.hs @@ -269,34 +269,39 @@ pgFmtCoerceNamed CoercibleField{cfName=fn} = pgFmtIdent fn pgFmtSelectItem :: QualifiedIdentifier -> CoercibleSelectField -> SQL.Snippet pgFmtSelectItem table CoercibleSelectField{csField=fld, csAggFunction=agg, csAggCast=aggCast, csCast=cast, csAlias=alias} = - pgFmtApplyAggregate agg aggCast Nothing (pgFmtApplyCast cast (pgFmtTableCoerce table fld)) <> pgFmtAs alias + pgFmtApplyAggregate agg aggCast (pgFmtApplyCast cast (pgFmtTableCoerce table fld)) <> pgFmtAs alias pgFmtSpreadSelectItem :: Alias -> MediaHandler -> SpreadSelectField -> SQL.Snippet pgFmtSpreadSelectItem aggAlias handler SpreadSelectField{ssSelName, ssSelAggFunction, ssSelAggCast, ssSelAlias} = - pgFmtApplyAggregate ssSelAggFunction ssSelAggCast (Just handler) fullSelName <> pgFmtAs ssSelAlias + pgFmtApplySpreadAggregate ssSelAggFunction ssSelAggCast aggAlias handler fullSelName <> pgFmtAs ssSelAlias where fullSelName = case ssSelName of "*" -> pgFmtIdent aggAlias <> ".*" _ -> pgFmtIdent aggAlias <> "." <> pgFmtIdent ssSelName -pgFmtApplyAggregate :: Maybe AggregateFunction -> Maybe Cast -> Maybe MediaHandler -> SQL.Snippet -> SQL.Snippet -pgFmtApplyAggregate Nothing _ _ snippet = snippet -pgFmtApplyAggregate (Just agg) aggCast handler snippet = +pgFmtApplyAggregate :: Maybe AggregateFunction -> Maybe Cast -> SQL.Snippet -> SQL.Snippet +pgFmtApplyAggregate Nothing _ snippet = snippet +pgFmtApplyAggregate (Just agg) aggCast snippet = pgFmtApplyCast aggCast aggregatedSnippet where convertAggFunction = SQL.sql . BS.map toUpper . BS.pack . show + aggregatedSnippet = convertAggFunction agg <> "(" <> snippet <> ")" + +pgFmtApplySpreadAggregate :: Maybe AggregateFunction -> Maybe Cast -> Alias -> MediaHandler -> SQL.Snippet -> SQL.Snippet +pgFmtApplySpreadAggregate (Just (ArrayAgg flt)) aggCast relAlias handler snippet = + pgFmtApplyCast aggCast aggregatedSnippet + where arrayAggStripNulls = case handler of - Just BuiltinAggArrayJsonStrip -> True - Just (BuiltinAggSingleJson strip) -> strip - _ -> False - fmtArrayAggFunction - | arrayAggStripNulls = "array_agg(" <> snippet <> ") FILTER (WHERE " <> snippet <> " IS NOT NULL)" - -- TODO: NULLIF(...,'{null}') does not take into consideration a case with a single element with a null value. - -- See https://github.com/PostgREST/postgrest/pull/3640#issuecomment-2334996466 - | otherwise = "NULLIF(array_agg(" <> snippet <> "),'{null}')" - aggregatedSnippet = case agg of - ArrayAgg -> "COALESCE(" <> fmtArrayAggFunction <> ",'{}')" - a -> convertAggFunction a <> "(" <> snippet <> ")" + BuiltinAggArrayJsonStrip -> True + BuiltinAggSingleJson strip -> strip + _ -> False + arrayAggFilter + | arrayAggStripNulls = Just $ snippet <> " IS NOT NULL" + | not (null flt) = Just $ intercalateSnippet " AND " $ (\f -> pgFmtIdent relAlias <> "." <> pgFmtIdent f <> " IS NOT NULL") <$> flt + | otherwise = Nothing + fmtArrayAggFunction = "array_agg(" <> snippet <> ")" <> maybe mempty (\f -> " FILTER (WHERE " <> f <> ")") arrayAggFilter + aggregatedSnippet = "COALESCE(" <> fmtArrayAggFunction <> ",'{}')" +pgFmtApplySpreadAggregate agg aggCast _ _ snippet = pgFmtApplyAggregate agg aggCast snippet pgFmtApplyCast :: Maybe Cast -> SQL.Snippet -> SQL.Snippet pgFmtApplyCast Nothing snippet = snippet diff --git a/test/spec/Feature/Query/SpreadQueriesSpec.hs b/test/spec/Feature/Query/SpreadQueriesSpec.hs index 27eeef9117..f02fa00379 100644 --- a/test/spec/Feature/Query/SpreadQueriesSpec.hs +++ b/test/spec/Feature/Query/SpreadQueriesSpec.hs @@ -135,6 +135,14 @@ spec = { matchStatus = 200 , matchHeaders = [matchContentTypeJson] } + it "should return a single null element array, not an empty one, when the row exists but the value happens to be null" $ + get "/managers?select=name,...organizations(organizations:name,referees:referee)&id=eq.1" `shouldRespondWith` + [json|[ + {"name":"Referee Manager","organizations":["Referee Org"],"referees":[null]} + ]|] + { matchStatus = 200 + , matchHeaders = [matchContentTypeJson] + } it "should work when selecting all columns, aggregating each one of them" $ get "/factories?select=factory:name,...processes(*)&id=lte.2&order=name" `shouldRespondWith` [json|[ @@ -309,6 +317,14 @@ spec = { matchStatus = 200 , matchHeaders = [matchContentTypeJson] } + it "should return a single null element array, not an empty one, when the row exists but the value happens to be null" $ + get "/operators?select=name,...processes(process:name,...process_costs(cost)))&id=eq.5&processes.id=eq.7" `shouldRespondWith` + [json|[ + {"name":"Alfred","process":["Process XX"],"cost":[null]} + ]|] + { matchStatus = 200 + , matchHeaders = [matchContentTypeJson] + } it "should work when selecting all columns, aggregating each one of them" $ get "/operators?select=operator:name,...processes(*)&id=lte.2" `shouldRespondWith` [json|[