2023-04-05 23:14:35 +03:00
|
|
|
{-# LANGUAGE QuasiQuotes #-}
|
2021-04-22 00:44:37 +03:00
|
|
|
{-# LANGUAGE UndecidableInstances #-}
|
2021-09-24 01:56:37 +03:00
|
|
|
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
2021-03-18 20:39:35 +03:00
|
|
|
|
2022-02-08 12:24:34 +03:00
|
|
|
-- | Postgres Instances Metadata
|
|
|
|
--
|
|
|
|
-- Defines a 'Hasura.RQL.Types.Metadata.Backend.BackendMetadata' type class instance for Postgres.
|
2021-03-18 20:39:35 +03:00
|
|
|
module Hasura.Backends.Postgres.Instances.Metadata () where
|
|
|
|
|
2023-04-26 18:42:13 +03:00
|
|
|
import Data.HashMap.Strict qualified as HashMap
|
2023-04-27 10:41:55 +03:00
|
|
|
import Data.HashMap.Strict.InsOrd qualified as InsOrdHashMap
|
2023-04-05 23:14:35 +03:00
|
|
|
import Data.String.Interpolate (i)
|
2021-09-24 01:56:37 +03:00
|
|
|
import Data.Text.Extended
|
2023-04-04 17:01:17 +03:00
|
|
|
import Database.PG.Query.PTI qualified as PTI
|
2023-04-05 23:14:35 +03:00
|
|
|
import Database.PG.Query.Pool (fromPGTxErr)
|
|
|
|
import Database.PG.Query.Transaction (Query)
|
|
|
|
import Database.PG.Query.Transaction qualified as Query
|
2023-04-04 17:01:17 +03:00
|
|
|
import Database.PostgreSQL.LibPQ qualified as PQ
|
2022-09-21 14:34:39 +03:00
|
|
|
import Hasura.Backends.Postgres.DDL qualified as Postgres
|
2023-04-05 23:14:35 +03:00
|
|
|
import Hasura.Backends.Postgres.Execute.Types (runPgSourceReadTx)
|
2023-04-13 19:10:38 +03:00
|
|
|
import Hasura.Backends.Postgres.Instances.NativeQueries as Postgres (validateNativeQuery)
|
2023-04-05 23:14:35 +03:00
|
|
|
import Hasura.Backends.Postgres.SQL.Types (QualifiedObject (..), QualifiedTable)
|
2023-04-04 17:01:17 +03:00
|
|
|
import Hasura.Backends.Postgres.SQL.Types qualified as Postgres
|
2021-09-24 01:56:37 +03:00
|
|
|
import Hasura.Backends.Postgres.Types.CitusExtraTableMetadata
|
|
|
|
import Hasura.Base.Error
|
|
|
|
import Hasura.Prelude
|
2023-04-26 09:48:12 +03:00
|
|
|
import Hasura.RQL.DDL.Relationship (defaultBuildArrayRelationshipInfo, defaultBuildObjectRelationshipInfo)
|
2021-09-24 01:56:37 +03:00
|
|
|
import Hasura.RQL.Types.Backend (Backend)
|
2023-04-24 21:35:48 +03:00
|
|
|
import Hasura.RQL.Types.BackendType
|
2021-09-24 01:56:37 +03:00
|
|
|
import Hasura.RQL.Types.Metadata.Backend
|
2021-12-01 07:53:34 +03:00
|
|
|
import Hasura.RQL.Types.Relationships.Local
|
2023-04-05 23:14:35 +03:00
|
|
|
import Hasura.RQL.Types.SchemaCache (askSourceConfig)
|
2021-09-24 01:56:37 +03:00
|
|
|
import Hasura.RQL.Types.Table
|
2021-03-18 20:39:35 +03:00
|
|
|
|
2021-05-21 05:46:58 +03:00
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- PostgresMetadata
|
|
|
|
|
|
|
|
-- | We differentiate the handling of metadata between Citus and Vanilla
|
|
|
|
-- Postgres because Citus imposes limitations on the types of joins that it
|
|
|
|
-- permits, which then limits the types of relations that we can track.
|
|
|
|
class PostgresMetadata (pgKind :: PostgresKind) where
|
|
|
|
-- TODO: find a better name
|
2021-09-24 01:56:37 +03:00
|
|
|
validateRel ::
|
|
|
|
MonadError QErr m =>
|
|
|
|
TableCache ('Postgres pgKind) ->
|
|
|
|
QualifiedTable ->
|
|
|
|
Either (ObjRelDef ('Postgres pgKind)) (ArrRelDef ('Postgres pgKind)) ->
|
|
|
|
m ()
|
2021-05-21 05:46:58 +03:00
|
|
|
|
2023-04-05 23:14:35 +03:00
|
|
|
-- | A query for getting the list of all tables on a given data source. This
|
|
|
|
-- is primarily used by the console to display tables for tracking etc.
|
|
|
|
listAllTablesSql :: Query
|
|
|
|
|
2023-04-04 17:01:17 +03:00
|
|
|
-- | A mapping from pg scalar types with clear oid equivalent to oid.
|
|
|
|
--
|
|
|
|
-- This is a insert order hash map so that when we invert it
|
|
|
|
-- duplicate oids will point to a more "general" type.
|
2023-04-27 10:41:55 +03:00
|
|
|
pgTypeOidMapping :: InsOrdHashMap.InsOrdHashMap Postgres.PGScalarType PQ.Oid
|
2023-04-04 17:01:17 +03:00
|
|
|
pgTypeOidMapping =
|
2023-04-27 10:41:55 +03:00
|
|
|
InsOrdHashMap.fromList $
|
2023-04-04 17:01:17 +03:00
|
|
|
[ (Postgres.PGSmallInt, PTI.int2),
|
|
|
|
(Postgres.PGSerial, PTI.int4),
|
|
|
|
(Postgres.PGInteger, PTI.int4),
|
|
|
|
(Postgres.PGBigSerial, PTI.int8),
|
|
|
|
(Postgres.PGBigInt, PTI.int8),
|
|
|
|
(Postgres.PGFloat, PTI.float4),
|
|
|
|
(Postgres.PGDouble, PTI.float8),
|
|
|
|
(Postgres.PGMoney, PTI.numeric),
|
|
|
|
(Postgres.PGNumeric, PTI.numeric),
|
|
|
|
(Postgres.PGBoolean, PTI.bool),
|
|
|
|
(Postgres.PGChar, PTI.bpchar),
|
|
|
|
(Postgres.PGVarchar, PTI.varchar),
|
|
|
|
(Postgres.PGText, PTI.text),
|
|
|
|
(Postgres.PGDate, PTI.date),
|
|
|
|
(Postgres.PGTimeStamp, PTI.timestamp),
|
|
|
|
(Postgres.PGTimeStampTZ, PTI.timestamptz),
|
|
|
|
(Postgres.PGTimeTZ, PTI.timetz),
|
|
|
|
(Postgres.PGJSON, PTI.json),
|
|
|
|
(Postgres.PGJSONB, PTI.jsonb),
|
|
|
|
(Postgres.PGUUID, PTI.uuid),
|
|
|
|
(Postgres.PGArray Postgres.PGSmallInt, PTI.int2_array),
|
|
|
|
(Postgres.PGArray Postgres.PGSerial, PTI.int4_array),
|
|
|
|
(Postgres.PGArray Postgres.PGInteger, PTI.int4_array),
|
|
|
|
(Postgres.PGArray Postgres.PGBigSerial, PTI.int8_array),
|
|
|
|
(Postgres.PGArray Postgres.PGBigInt, PTI.int8_array),
|
|
|
|
(Postgres.PGArray Postgres.PGFloat, PTI.float4_array),
|
|
|
|
(Postgres.PGArray Postgres.PGDouble, PTI.float8_array),
|
|
|
|
(Postgres.PGArray Postgres.PGMoney, PTI.numeric_array),
|
|
|
|
(Postgres.PGArray Postgres.PGNumeric, PTI.numeric_array),
|
|
|
|
(Postgres.PGArray Postgres.PGBoolean, PTI.bool_array),
|
|
|
|
(Postgres.PGArray Postgres.PGChar, PTI.char_array),
|
|
|
|
(Postgres.PGArray Postgres.PGVarchar, PTI.varchar_array),
|
|
|
|
(Postgres.PGArray Postgres.PGText, PTI.text_array),
|
|
|
|
(Postgres.PGArray Postgres.PGDate, PTI.date_array),
|
|
|
|
(Postgres.PGArray Postgres.PGTimeStamp, PTI.timestamp_array),
|
|
|
|
(Postgres.PGArray Postgres.PGTimeStampTZ, PTI.timestamptz_array),
|
|
|
|
(Postgres.PGArray Postgres.PGTimeTZ, PTI.timetz_array),
|
|
|
|
(Postgres.PGArray Postgres.PGJSON, PTI.json_array),
|
|
|
|
(Postgres.PGArray Postgres.PGJSON, PTI.jsonb_array),
|
|
|
|
(Postgres.PGArray Postgres.PGUUID, PTI.uuid_array)
|
|
|
|
]
|
|
|
|
|
2021-05-21 05:46:58 +03:00
|
|
|
instance PostgresMetadata 'Vanilla where
|
|
|
|
validateRel _ _ _ = pure ()
|
|
|
|
|
2023-04-05 23:14:35 +03:00
|
|
|
listAllTablesSql =
|
|
|
|
Query.fromText
|
|
|
|
[i|
|
|
|
|
WITH partitions as (
|
|
|
|
SELECT array(
|
|
|
|
SELECT
|
|
|
|
child.relname AS partition
|
|
|
|
FROM pg_inherits
|
|
|
|
JOIN pg_class child ON pg_inherits.inhrelid = child.oid
|
|
|
|
JOIN pg_namespace nmsp_child ON nmsp_child.oid = child.relnamespace
|
|
|
|
) as names
|
|
|
|
)
|
2023-05-04 14:38:31 +03:00
|
|
|
SELECT info_schema.table_schema, info_schema.table_name
|
2023-04-05 23:14:35 +03:00
|
|
|
FROM information_schema.tables as info_schema, partitions
|
|
|
|
WHERE
|
|
|
|
info_schema.table_schema NOT IN ('information_schema', 'pg_catalog', 'hdb_catalog', '_timescaledb_internal')
|
|
|
|
AND NOT (info_schema.table_name = ANY (partitions.names))
|
2023-05-04 14:38:31 +03:00
|
|
|
ORDER BY info_schema.table_schema, info_schema.table_name
|
2023-04-05 23:14:35 +03:00
|
|
|
|]
|
|
|
|
|
2021-05-21 05:46:58 +03:00
|
|
|
instance PostgresMetadata 'Citus where
|
2021-09-24 01:56:37 +03:00
|
|
|
validateRel ::
|
|
|
|
forall m.
|
|
|
|
MonadError QErr m =>
|
|
|
|
TableCache ('Postgres 'Citus) ->
|
|
|
|
QualifiedTable ->
|
|
|
|
Either (ObjRelDef ('Postgres 'Citus)) (ArrRelDef ('Postgres 'Citus)) ->
|
|
|
|
m ()
|
2021-05-21 05:46:58 +03:00
|
|
|
validateRel tableCache sourceTable relInfo = do
|
|
|
|
sourceTableInfo <- lookupTableInfo sourceTable
|
|
|
|
case relInfo of
|
|
|
|
Left (RelDef _ obj _) ->
|
|
|
|
case obj of
|
2021-09-24 01:56:37 +03:00
|
|
|
RUFKeyOn (SameTable _) -> pure ()
|
2021-05-21 05:46:58 +03:00
|
|
|
RUFKeyOn (RemoteTable targetTable _) -> checkObjectRelationship sourceTableInfo targetTable
|
2023-05-04 17:31:14 +03:00
|
|
|
RUManual RelManualTableConfig {} -> pure ()
|
|
|
|
RUManual RelManualNativeQueryConfig {} -> pure ()
|
2021-05-21 05:46:58 +03:00
|
|
|
Right (RelDef _ obj _) ->
|
|
|
|
case obj of
|
|
|
|
RUFKeyOn (ArrRelUsingFKeyOn targetTable _col) -> checkArrayRelationship sourceTableInfo targetTable
|
2023-05-04 17:31:14 +03:00
|
|
|
RUManual RelManualTableConfig {} -> pure ()
|
|
|
|
RUManual RelManualNativeQueryConfig {} -> pure ()
|
2021-05-21 05:46:58 +03:00
|
|
|
where
|
2021-09-24 01:56:37 +03:00
|
|
|
lookupTableInfo tableName =
|
2023-04-26 18:42:13 +03:00
|
|
|
HashMap.lookup tableName tableCache
|
2021-09-24 01:56:37 +03:00
|
|
|
`onNothing` throw400 NotFound ("no such table " <>> tableName)
|
2021-05-21 05:46:58 +03:00
|
|
|
|
|
|
|
checkObjectRelationship sourceTableInfo targetTable = do
|
|
|
|
targetTableInfo <- lookupTableInfo targetTable
|
|
|
|
let notSupported = throwNotSupportedError sourceTableInfo targetTableInfo "object"
|
2021-09-24 01:56:37 +03:00
|
|
|
case ( _tciExtraTableMetadata $ _tiCoreInfo sourceTableInfo,
|
|
|
|
_tciExtraTableMetadata $ _tiCoreInfo targetTableInfo
|
2021-05-21 05:46:58 +03:00
|
|
|
) of
|
2021-09-24 01:56:37 +03:00
|
|
|
(Distributed {}, Local) -> notSupported
|
|
|
|
(Distributed {}, Reference) -> pure ()
|
|
|
|
(Distributed {}, Distributed {}) -> pure ()
|
|
|
|
(_, Distributed {}) -> notSupported
|
|
|
|
(_, _) -> pure ()
|
2021-05-21 05:46:58 +03:00
|
|
|
|
|
|
|
checkArrayRelationship sourceTableInfo targetTable = do
|
|
|
|
targetTableInfo <- lookupTableInfo targetTable
|
|
|
|
let notSupported = throwNotSupportedError sourceTableInfo targetTableInfo "array"
|
2021-09-24 01:56:37 +03:00
|
|
|
case ( _tciExtraTableMetadata $ _tiCoreInfo sourceTableInfo,
|
|
|
|
_tciExtraTableMetadata $ _tiCoreInfo targetTableInfo
|
2021-05-21 05:46:58 +03:00
|
|
|
) of
|
2021-09-24 01:56:37 +03:00
|
|
|
(Distributed {}, Distributed {}) -> pure ()
|
|
|
|
(Distributed {}, _) -> notSupported
|
|
|
|
(_, Distributed {}) -> notSupported
|
|
|
|
(_, _) -> pure ()
|
2021-05-21 05:46:58 +03:00
|
|
|
|
|
|
|
showDistributionType :: ExtraTableMetadata -> Text
|
|
|
|
showDistributionType = \case
|
2021-09-24 01:56:37 +03:00
|
|
|
Local -> "local"
|
2021-05-21 05:46:58 +03:00
|
|
|
Distributed _ -> "distributed"
|
2021-09-24 01:56:37 +03:00
|
|
|
Reference -> "reference"
|
2021-05-21 05:46:58 +03:00
|
|
|
|
|
|
|
throwNotSupportedError :: TableInfo ('Postgres 'Citus) -> TableInfo ('Postgres 'Citus) -> Text -> m ()
|
|
|
|
throwNotSupportedError sourceTableInfo targetTableInfo t =
|
|
|
|
let tciSrc = _tiCoreInfo sourceTableInfo
|
|
|
|
tciTgt = _tiCoreInfo targetTableInfo
|
2021-09-24 01:56:37 +03:00
|
|
|
in throw400
|
|
|
|
NotSupported
|
|
|
|
( showDistributionType (_tciExtraTableMetadata tciSrc)
|
|
|
|
<> " tables ("
|
|
|
|
<> toTxt (_tciName tciSrc)
|
|
|
|
<> ") cannot have an "
|
|
|
|
<> t
|
|
|
|
<> " relationship against a "
|
|
|
|
<> showDistributionType (_tciExtraTableMetadata $ _tiCoreInfo targetTableInfo)
|
|
|
|
<> " table ("
|
|
|
|
<> toTxt (_tciName tciTgt)
|
|
|
|
<> ")"
|
|
|
|
)
|
2021-05-21 05:46:58 +03:00
|
|
|
|
2023-04-05 23:14:35 +03:00
|
|
|
listAllTablesSql =
|
|
|
|
Query.fromText
|
|
|
|
[i|
|
|
|
|
WITH partitions as (
|
|
|
|
SELECT array(
|
|
|
|
SELECT
|
|
|
|
child.relname AS partition
|
|
|
|
FROM pg_inherits
|
|
|
|
JOIN pg_class child ON pg_inherits.inhrelid = child.oid
|
|
|
|
JOIN pg_namespace nmsp_child ON nmsp_child.oid = child.relnamespace
|
|
|
|
) as names
|
|
|
|
)
|
2023-05-04 14:38:31 +03:00
|
|
|
SELECT info_schema.table_schema, info_schema.table_name
|
2023-04-05 23:14:35 +03:00
|
|
|
FROM information_schema.tables as info_schema, partitions
|
|
|
|
WHERE
|
|
|
|
info_schema.table_schema NOT IN ('pg_catalog', 'citus', 'information_schema', 'columnar', 'columnar_internal', 'guest', 'INFORMATION_SCHEMA', 'sys', 'db_owner', 'db_securityadmin', 'db_accessadmin', 'db_backupoperator', 'db_ddladmin', 'db_datawriter', 'db_datareader', 'db_denydatawriter', 'db_denydatareader', 'hdb_catalog', '_timescaledb_internal')
|
|
|
|
AND NOT (info_schema.table_name = ANY (partitions.names))
|
|
|
|
AND info_schema.table_name NOT IN ('citus_tables')
|
2023-05-04 14:38:31 +03:00
|
|
|
ORDER BY info_schema.table_schema, info_schema.table_name
|
2023-04-05 23:14:35 +03:00
|
|
|
|]
|
|
|
|
|
2022-08-19 17:19:54 +03:00
|
|
|
instance PostgresMetadata 'Cockroach where
|
|
|
|
validateRel _ _ _ = pure ()
|
2023-04-05 23:14:35 +03:00
|
|
|
|
2023-04-04 17:01:17 +03:00
|
|
|
pgTypeOidMapping =
|
2023-04-27 10:41:55 +03:00
|
|
|
InsOrdHashMap.fromList
|
2023-04-04 17:01:17 +03:00
|
|
|
[ (Postgres.PGInteger, PTI.int8),
|
|
|
|
(Postgres.PGSerial, PTI.int8),
|
|
|
|
(Postgres.PGJSON, PTI.jsonb)
|
|
|
|
]
|
2023-04-27 10:41:55 +03:00
|
|
|
`InsOrdHashMap.union` pgTypeOidMapping @'Vanilla
|
2022-08-19 17:19:54 +03:00
|
|
|
|
2023-04-05 23:14:35 +03:00
|
|
|
listAllTablesSql =
|
|
|
|
Query.fromText
|
|
|
|
[i|
|
|
|
|
WITH partitions as (
|
|
|
|
SELECT array(
|
|
|
|
SELECT
|
|
|
|
child.relname AS partition
|
|
|
|
FROM pg_inherits
|
|
|
|
JOIN pg_class child ON pg_inherits.inhrelid = child.oid
|
|
|
|
JOIN pg_namespace nmsp_child ON nmsp_child.oid = child.relnamespace
|
|
|
|
) as names
|
|
|
|
)
|
2023-05-04 14:38:31 +03:00
|
|
|
SELECT info_schema.table_schema, info_schema.table_name
|
2023-04-05 23:14:35 +03:00
|
|
|
FROM information_schema.tables as info_schema, partitions
|
|
|
|
WHERE
|
|
|
|
info_schema.table_schema NOT IN ('pg_catalog', 'crdb_internal', 'information_schema', 'columnar', 'guest', 'INFORMATION_SCHEMA', 'sys', 'db_owner', 'db_securityadmin', 'db_accessadmin', 'db_backupoperator', 'db_ddladmin', 'db_datawriter', 'db_datareader', 'db_denydatawriter', 'db_denydatareader', 'hdb_catalog', '_timescaledb_internal', 'pg_extension')
|
2023-05-04 14:38:31 +03:00
|
|
|
AND NOT (info_schema.table_name = ANY (partitions.names))
|
|
|
|
ORDER BY info_schema.table_schema, info_schema.table_name
|
2023-04-05 23:14:35 +03:00
|
|
|
|]
|
|
|
|
|
2021-05-21 05:46:58 +03:00
|
|
|
----------------------------------------------------------------
|
|
|
|
-- BackendMetadata instance
|
|
|
|
|
2021-04-22 00:44:37 +03:00
|
|
|
instance
|
2021-09-24 01:56:37 +03:00
|
|
|
( Backend ('Postgres pgKind),
|
|
|
|
PostgresMetadata pgKind,
|
2022-09-21 14:34:39 +03:00
|
|
|
Postgres.FetchTableMetadata pgKind,
|
|
|
|
Postgres.FetchFunctionMetadata pgKind,
|
|
|
|
Postgres.ToMetadataFetchQuery pgKind
|
2021-09-24 01:56:37 +03:00
|
|
|
) =>
|
|
|
|
BackendMetadata ('Postgres pgKind)
|
|
|
|
where
|
2022-09-21 14:34:39 +03:00
|
|
|
prepareCatalog = Postgres.prepareCatalog
|
|
|
|
buildComputedFieldInfo = Postgres.buildComputedFieldInfo
|
|
|
|
fetchAndValidateEnumValues = Postgres.fetchAndValidateEnumValues
|
|
|
|
resolveSourceConfig = Postgres.resolveSourceConfig
|
2023-04-13 04:29:15 +03:00
|
|
|
resolveDatabaseMetadata _ = Postgres.resolveDatabaseMetadata
|
2022-09-21 14:34:39 +03:00
|
|
|
parseBoolExpOperations = Postgres.parseBoolExpOperations
|
2023-04-26 09:48:12 +03:00
|
|
|
buildArrayRelationshipInfo _ = defaultBuildArrayRelationshipInfo
|
|
|
|
buildObjectRelationshipInfo _ = defaultBuildObjectRelationshipInfo
|
2022-09-21 14:34:39 +03:00
|
|
|
buildFunctionInfo = Postgres.buildFunctionInfo
|
|
|
|
updateColumnInEventTrigger = Postgres.updateColumnInEventTrigger
|
|
|
|
parseCollectableType = Postgres.parseCollectableType
|
|
|
|
postDropSourceHook = Postgres.postDropSourceHook
|
2021-09-24 01:56:37 +03:00
|
|
|
validateRelationship = validateRel @pgKind
|
2022-09-21 14:34:39 +03:00
|
|
|
buildComputedFieldBooleanExp = Postgres.buildComputedFieldBooleanExp
|
2023-04-13 19:10:38 +03:00
|
|
|
validateNativeQuery = Postgres.validateNativeQuery (pgTypeOidMapping @pgKind)
|
2023-03-08 08:59:40 +03:00
|
|
|
supportsBeingRemoteRelationshipTarget _ = True
|
2023-04-05 23:14:35 +03:00
|
|
|
|
2023-04-13 04:29:15 +03:00
|
|
|
listAllTables sourceName = do
|
2023-04-05 23:14:35 +03:00
|
|
|
sourceConfig <- askSourceConfig @('Postgres pgKind) sourceName
|
|
|
|
|
|
|
|
results <-
|
|
|
|
runPgSourceReadTx sourceConfig (Query.multiQE fromPGTxErr (listAllTablesSql @pgKind))
|
|
|
|
`onLeftM` \err -> throwError (prefixQErr "failed to fetch source tables: " err)
|
|
|
|
|
2023-05-04 14:38:31 +03:00
|
|
|
pure [QualifiedObject {..} | (qSchema, qName) <- results]
|