@@ -314,41 +314,45 @@ pgFmtFullSelName aggAlias fieldName = case fieldName of
314314-- TODO: At this stage there shouldn't be a Maybe since ApiRequest should ensure that an INSERT/UPDATE has a body
315315fromJsonBodyF :: Maybe LBS. ByteString -> [CoercibleField ] -> Bool -> Bool -> Bool -> SQL. Snippet
316316fromJsonBodyF body fields includeSelect includeLimitOne includeDefaults =
317- (if includeSelect then " SELECT " <> namedCols <> " " else mempty ) <>
318- " FROM (SELECT " <> jsonPlaceHolder <> " AS json_data) pgrst_payload, " <>
319- (if includeDefaults
320- then if isJsonObject
321- then " LATERAL (SELECT " <> defsJsonb <> " || pgrst_payload.json_data AS val) pgrst_json_defs, "
322- else " LATERAL (SELECT jsonb_agg(" <> defsJsonb <> " || elem) AS val from jsonb_array_elements(pgrst_payload.json_data) elem) pgrst_json_defs, "
323- else mempty ) <>
324- " LATERAL (SELECT " <> parsedCols <> " FROM " <>
325- (if null fields -- when json keys are empty, e.g. when payload is `{}` or `[{}, {}]`
326- then SQL. sql $
327- if isJsonObject
328- then " (values(1)) _ " -- only 1 row for an empty json object '{}'
329- else jsonArrayElementsF <> " (" <> finalBodyF <> " ) _ " -- extract rows of a json array of empty objects `[{}, {}]`
330- else jsonToRecordsetF <> " (" <> SQL. sql finalBodyF <> " ) AS _(" <> typedCols <> " ) " <> if includeLimitOne then " LIMIT 1" else mempty
331- ) <>
332- " ) pgrst_body "
317+ selectClause <> fromClause <> defaultsClause <> lateralClause <> " pgrst_body "
333318 where
319+ selectClause = if includeSelect then " SELECT " <> namedCols <> " " else mempty
320+ fromClause = " FROM (SELECT " <> jsonPlaceHolder <> " AS json_data) pgrst_payload, "
321+ defaultsClause
322+ | includeDefaults && isJsonObject = " LATERAL (SELECT " <> defsJsonb <> " || pgrst_payload.json_data AS val) pgrst_json_defs, "
323+ | includeDefaults && not isJsonObject = " LATERAL (SELECT jsonb_agg(" <> defsJsonb <> " || elem) AS val from jsonb_array_elements(pgrst_payload.json_data) elem) pgrst_json_defs, "
324+ | otherwise = mempty
325+ lateralClause = " LATERAL (SELECT " <> parsedCols <> " FROM " <> lateralFieldsSource <> " )"
326+
334327 namedCols = intercalateSnippet " , " $ fromQi . QualifiedIdentifier " pgrst_body" . cfName <$> fields
335328 parsedCols = intercalateSnippet " , " $ pgFmtCoerceNamed <$> fields
336329 typedCols = intercalateSnippet " , " $ pgFmtIdent . cfName <> const " " <> SQL. sql . encodeUtf8 . cfIRType <$> fields
330+
331+ lateralFieldsSource = if null fields then emptyFieldsSource else nonEmptyFieldsSource
332+ where
333+ limitClause = if includeLimitOne then " LIMIT 1" else mempty
334+ nonEmptyFieldsSource = jsonToRecordsetF <> " (" <> finalBodyF <> " ) AS _(" <> typedCols <> " ) " <> limitClause
335+ -- when json keys are empty, e.g. when payload is `{}` or `[{}, {}]`
336+ emptyFieldsSource = if isJsonObject
337+ then " (values(1)) _ " -- only 1 row for an empty json object '{}'
338+ else jsonArrayElementsF <> " (" <> finalBodyF <> " ) _ " -- extract rows of a json array of empty objects `[{}, {}]`
339+
337340 defsJsonb = SQL. sql $ " jsonb_build_object(" <> BS. intercalate " ," fieldsWDefaults <> " )"
338- fieldsWDefaults = mapMaybe (\ case
339- CoercibleField {cfName= nam, cfDefault= Just def} -> Just $ encodeUtf8 (pgFmtLit nam <> " , " <> def)
340- CoercibleField {cfDefault= Nothing } -> Nothing
341- ) fields
341+ fieldsWDefaults = mapMaybe extractFieldDefault fields
342+ where
343+ extractFieldDefault CoercibleField {cfName= nam, cfDefault= Just def} = Just $ encodeUtf8 (pgFmtLit nam <> " , " <> def)
344+ extractFieldDefault CoercibleField {cfDefault= Nothing } = Nothing
345+
342346 (finalBodyF, jsonArrayElementsF, jsonToRecordsetF) =
343347 if includeDefaults
344348 then (" pgrst_json_defs.val" , " jsonb_array_elements" , if isJsonObject then " jsonb_to_record" else " jsonb_to_recordset" )
345349 else (" pgrst_payload.json_data" , " json_array_elements" , if isJsonObject then " json_to_record" else " json_to_recordset" )
350+
346351 jsonPlaceHolder = SQL. encoderAndParam (HE. nullable $ if includeDefaults then HE. jsonbLazyBytes else HE. jsonLazyBytes) body
347352 isJsonObject = -- light validation as pg's json_to_record(set) already validates that the body is valid JSON. We just need to know whether the body looks like an object or not.
348- let
349- insignificantWhitespace = [32 ,9 ,10 ,13 ] -- " \t\n\r" [32,9,10,13] https://datatracker.ietf.org/doc/html/rfc8259#section-2
350- in
351353 LBS. take 1 (LBS. dropWhile (`elem` insignificantWhitespace) (fromMaybe mempty body)) == " {"
354+ where
355+ insignificantWhitespace = [32 ,9 ,10 ,13 ] -- " \t\n\r" [32,9,10,13] https://datatracker.ietf.org/doc/html/rfc8259#section-2
352356
353357pgFmtOrderTerm :: QualifiedIdentifier -> CoercibleOrderTerm -> SQL. Snippet
354358pgFmtOrderTerm qi ot =
0 commit comments