@@ -42,6 +42,7 @@ import NeatInterpolation (trimming)
4242import PostgREST.Config (AppConfig (.. ))
4343import PostgREST.Config.Database (TimezoneNames ,
4444 toIsolationLevel )
45+ import PostgREST.Config.PgVersion (PgVersion , pgVersion170 )
4546import PostgREST.SchemaCache.Identifiers (FieldName ,
4647 QualifiedIdentifier (.. ),
4748 RelIdentifier (.. ),
@@ -139,13 +140,13 @@ data KeyDep
139140type SqlQuery = ByteString
140141
141142
142- querySchemaCache :: AppConfig -> SQL. Transaction SchemaCache
143- querySchemaCache conf@ AppConfig {.. } = do
143+ querySchemaCache :: PgVersion -> AppConfig -> SQL. Transaction SchemaCache
144+ querySchemaCache pgVer conf@ AppConfig {.. } = do
144145 SQL. sql " set local schema ''" -- This voids the search path. The following queries need this for getting the fully qualified name(schema.name) of every db object
145- tabs <- SQL. statement conf $ allTables prepared
146+ tabs <- SQL. statement conf $ allTables pgVer prepared
146147 keyDeps <- SQL. statement conf $ allViewsKeyDependencies prepared
147148 m2oRels <- SQL. statement mempty $ allM2OandO2ORels prepared
148- funcs <- SQL. statement conf $ allFunctions prepared
149+ funcs <- SQL. statement conf $ allFunctions pgVer prepared
149150 cRels <- SQL. statement mempty $ allComputedRels prepared
150151 reps <- SQL. statement conf $ dataRepresentations prepared
151152 mHdlers <- SQL. statement conf $ mediaHandlers prepared
@@ -353,47 +354,61 @@ dataRepresentations = SQL.Statement sql mempty decodeRepresentations
353354 OR (dst_t.typtype = 'd' AND c.castsource IN ('json'::regtype::oid , 'text'::regtype::oid)))
354355 |]
355356
356- allFunctions :: Bool -> SQL. Statement AppConfig RoutineMap
357- allFunctions = SQL. Statement funcsSqlQuery params decodeFuncs
357+ allFunctions :: PgVersion -> Bool -> SQL. Statement AppConfig RoutineMap
358+ allFunctions pgVer = SQL. Statement ( funcsSqlQuery pgVer) params decodeFuncs
358359 where
359360 params =
360361 (map escapeIdent . toList . configDbSchemas >$< arrayParam HE. text) <>
361362 (configDbHoistedTxSettings >$< arrayParam HE. text)
362363
363- baseTypesCte :: Text
364- baseTypesCte = [trimming |
365- -- Recursively get the base types of domains
366- base_types AS (
367- WITH RECURSIVE
368- recurse AS (
369- SELECT
370- oid,
371- typbasetype,
372- typnamespace AS base_namespace,
373- COALESCE(NULLIF(typbasetype, 0), oid) AS base_type
374- FROM pg_type
375- UNION
376- SELECT
377- t.oid,
378- b.typbasetype,
379- b.typnamespace AS base_namespace,
380- COALESCE(NULLIF(b.typbasetype, 0), b.oid) AS base_type
381- FROM recurse t
382- JOIN pg_type b ON t.typbasetype = b.oid
383- )
384- SELECT
385- oid,
386- base_namespace,
387- base_type
388- FROM recurse
389- WHERE typbasetype = 0
390- )
391- |]
364+ baseTypesCte :: PgVersion -> Text
365+ baseTypesCte pgVer
366+ | pgVer >= pgVersion170 = [trimming |
367+ -- Get base types using pg_basetype() (PG 17+)
368+ base_types AS (
369+ SELECT
370+ t.oid,
371+ bt.typnamespace AS base_namespace,
372+ bt.oid AS base_type
373+ FROM pg_type t
374+ JOIN pg_type bt ON bt.oid = pg_basetype(t.oid)
375+ )
376+ |]
377+ | otherwise = [trimming |
378+ -- Recursively get the base types of domains (PG < 17)
379+ base_types AS (
380+ WITH RECURSIVE
381+ recurse AS (
382+ SELECT
383+ oid,
384+ typbasetype,
385+ typnamespace AS base_namespace,
386+ COALESCE(NULLIF(typbasetype, 0), oid) AS base_type
387+ FROM pg_type
388+ UNION
389+ SELECT
390+ t.oid,
391+ b.typbasetype,
392+ b.typnamespace AS base_namespace,
393+ COALESCE(NULLIF(b.typbasetype, 0), b.oid) AS base_type
394+ FROM recurse t
395+ JOIN pg_type b ON t.typbasetype = b.oid
396+ )
397+ SELECT
398+ oid,
399+ base_namespace,
400+ base_type
401+ FROM recurse
402+ WHERE typbasetype = 0
403+ )
404+ |]
392405
393- funcsSqlQuery :: SqlQuery
394- funcsSqlQuery = encodeUtf8 [trimming |
406+ funcsSqlQuery :: PgVersion -> SqlQuery
407+ funcsSqlQuery pgVer =
408+ let baseCte = baseTypesCte pgVer
409+ in encodeUtf8 [trimming |
395410 WITH
396- $baseTypesCte ,
411+ $baseCte ,
397412 arguments AS (
398413 SELECT
399414 oid,
@@ -566,22 +581,23 @@ addViewPrimaryKeys tabs keyDeps =
566581 takeFirstPK = mapMaybe (head . snd )
567582 indexedDeps = HM. fromListWith (++) $ fmap ((keyDepType &&& keyDepView) &&& pure ) keyDeps
568583
569- allTables :: Bool -> SQL. Statement AppConfig TablesMap
570- allTables = SQL. Statement tablesSqlQuery params decodeTables
584+ allTables :: PgVersion -> Bool -> SQL. Statement AppConfig TablesMap
585+ allTables pgVer = SQL. Statement ( tablesSqlQuery pgVer) params decodeTables
571586 where
572587 params = map escapeIdent . toList . configDbSchemas >$< arrayParam HE. text
573588
574589-- | Gets tables with their PK cols
575- tablesSqlQuery :: SqlQuery
576- tablesSqlQuery =
590+ tablesSqlQuery :: PgVersion -> SqlQuery
591+ tablesSqlQuery pgVer =
577592 -- the tbl_constraints/key_col_usage CTEs are based on the standard "information_schema.table_constraints"/"information_schema.key_column_usage" views,
578593 -- we cannot use those directly as they include the following privilege filter:
579594 -- (pg_has_role(ss.relowner, 'USAGE'::text) OR has_column_privilege(ss.roid, a.attnum, 'SELECT, INSERT, UPDATE, REFERENCES'::text));
580595 -- on the "columns" CTE, left joining on pg_depend and pg_class is used to obtain the sequence name as a column default in case there are GENERATED .. AS IDENTITY,
581596 -- generated columns are only available from pg >= 10 but the query is agnostic to versions. dep.deptype = 'i' is done because there are other 'a' dependencies on PKs
582- encodeUtf8 [trimming |
597+ let baseCte = baseTypesCte pgVer
598+ in encodeUtf8 [trimming |
583599 WITH
584- $baseTypesCte ,
600+ $baseCte ,
585601 columns AS (
586602 SELECT
587603 c.oid AS relid,
0 commit comments