mirror of
https://github.com/hasura/graphql-engine.git
synced 2024-12-17 04:24:35 +03:00
bacadc30da
## Remaining Work - [x] changelog entry - [x] more tests: `<backend>_delete_remote_relationship` is definitely untested - [x] negative tests: we probably want to assert that there are some APIs we DON'T support - [x] update the console to use the new API, if necessary - [x] ~~adding the corresponding documentation for the API for other backends (only `pg_` was added here)~~ - deferred to https://github.com/hasura/graphql-engine-mono/issues/3170 - [x] ~~deciding which backends should support this API~~ - deferred to https://github.com/hasura/graphql-engine-mono/issues/3170 - [x] ~~deciding what to do about potentially overlapping schematic representations~~ - ~~cf. https://github.com/hasura/graphql-engine-mono/pull/3157#issuecomment-995307624~~ - deferred to https://github.com/hasura/graphql-engine-mono/issues/3171 - [x] ~~add more descriptive versioning information to some of the types that are changing in this PR~~ - cf. https://github.com/hasura/graphql-engine-mono/pull/3157#discussion_r769830920 - deferred to https://github.com/hasura/graphql-engine-mono/issues/3172 ## Description This PR fixes several important issues wrt. the remote relationship API. - it fixes a regression introduced by [#3124](https://github.com/hasura/graphql-engine-mono/pull/3124), which prevented `<backend>_create_remote_relationship` from accepting the old argument format (break of backwards compatibility, broke the console) - it removes the command `create_remote_relationship` added to the v1/metadata API as a work-around as part of [#3124](https://github.com/hasura/graphql-engine-mono/pull/3124) - it reverts the subsequent fix in the console: [#3149](https://github.com/hasura/graphql-engine-mono/pull/3149) Furthermore, this PR also addresses two other issues: - THE DOCUMENTATION OF THE METADATA API WAS WRONG, and documented `create_remote_relationship` instead of `<backend>_create_remote_relationship`: this PR fixes this by adding `pg_` everywhere, but does not attempt to add the corresponding documentation for other backends, partly because: - `<backend>_delete_remote_relationship` WAS BROKEN ON NON-POSTGRES BACKENDS; it always expected an argument parameterized by Postgres. As of main, the `<backend>_(create|update|delete)_remote_relationship` commands are supported on Postgres, Citus, BigQuery, but **NOT MSSQL**. I do not know if this is intentional or not, if it even should be publicized or not, and as a result this PR doesn't change this. PR-URL: https://github.com/hasura/graphql-engine-mono/pull/3157 Co-authored-by: jkachmar <8461423+jkachmar@users.noreply.github.com> GitOrigin-RevId: 37e2f41522a9229a11c595574c3f4984317d652a
256 lines
11 KiB
Haskell
256 lines
11 KiB
Haskell
{-# LANGUAGE UndecidableInstances #-}
|
|
|
|
module Hasura.RQL.DDL.RemoteRelationship
|
|
( CreateFromSourceRelationship (..),
|
|
runCreateRemoteRelationship,
|
|
runDeleteRemoteRelationship,
|
|
runUpdateRemoteRelationship,
|
|
DeleteFromSourceRelationship (..),
|
|
dropRemoteRelationshipInMetadata,
|
|
PartiallyResolvedSource (..),
|
|
buildRemoteFieldInfo,
|
|
)
|
|
where
|
|
|
|
import Data.Aeson (FromJSON (..), ToJSON (..), (.!=), (.:), (.:?), (.=))
|
|
import Data.Aeson qualified as J
|
|
import Data.HashMap.Strict qualified as Map
|
|
import Data.HashMap.Strict.InsOrd qualified as OMap
|
|
import Data.HashSet qualified as S
|
|
import Data.Text.Extended ((<<>), (<>>))
|
|
import Hasura.Base.Error
|
|
( Code (NotFound, NotSupported, RemoteSchemaError),
|
|
QErr,
|
|
QErrM,
|
|
runAesonParser,
|
|
throw400,
|
|
)
|
|
import Hasura.EncJSON (EncJSON)
|
|
import Hasura.Prelude
|
|
import Hasura.RQL.DDL.RemoteRelationship.Validate
|
|
( errorToText,
|
|
validateSourceToSchemaRelationship,
|
|
)
|
|
import Hasura.RQL.Types
|
|
import Hasura.SQL.AnyBackend qualified as AB
|
|
|
|
--------------------------------------------------------------------------------
|
|
-- Create or update relationship
|
|
|
|
-- | Argument to the @_create_remote_relationship@ and
|
|
-- @_update_remote_relationship@ families of metadata commands.
|
|
--
|
|
-- For historical reason, this type is also used to represent a db-to-rs schema
|
|
-- in the metadata.
|
|
data CreateFromSourceRelationship (b :: BackendType) = CreateFromSourceRelationship
|
|
{ _crrSource :: SourceName,
|
|
_crrTable :: TableName b,
|
|
_crrName :: RelName,
|
|
_crrDefinition :: RemoteRelationshipDefinition
|
|
}
|
|
|
|
deriving stock instance (Eq (TableName b)) => Eq (CreateFromSourceRelationship b)
|
|
|
|
deriving stock instance (Show (TableName b)) => Show (CreateFromSourceRelationship b)
|
|
|
|
instance Backend b => FromJSON (CreateFromSourceRelationship b) where
|
|
parseJSON = J.withObject "CreateFromSourceRelationship" $ \o -> do
|
|
_crrSource <- o .:? "source" .!= defaultSource
|
|
_crrTable <- o .: "table"
|
|
_crrName <- o .: "name"
|
|
-- In the old format, the definition is inlined; in the new format, the
|
|
-- definition is in the "definition" object.
|
|
remoteSchema :: Maybe J.Value <- o .:? "remote_schema"
|
|
definition <- o .:? "definition"
|
|
_crrDefinition <- case (remoteSchema, definition) of
|
|
-- old format
|
|
(Just _, Nothing) -> parseJSON $ J.Object o
|
|
-- new format
|
|
(Nothing, Just def) -> parseJSON def
|
|
-- both or neither
|
|
_ -> fail "create_remote_relationship expects exactly one of: remote_schema, definition"
|
|
pure $ CreateFromSourceRelationship {..}
|
|
|
|
instance (Backend b) => ToJSON (CreateFromSourceRelationship b) where
|
|
toJSON (CreateFromSourceRelationship {..}) =
|
|
-- We need to introspect the definition, to know whether we need to inline
|
|
-- it, or if it needs to be in a distinct "definition" object.
|
|
J.object $ case _crrDefinition of
|
|
-- old format
|
|
RelationshipToSchema RRFOldDBToRemoteSchema _ ->
|
|
case J.toJSON _crrDefinition of
|
|
-- The result of this serialization will be an empty list if this
|
|
-- conversion fails (which it should _never_ do), in which case those
|
|
-- fields will be omitted from the serialized JSON. This could only
|
|
-- happen if the ToJSON instance of RemoteRelationshipDefinition were
|
|
-- changed to return something that isn't an object.
|
|
J.Object obj -> commonFields <> Map.toList obj
|
|
_ -> []
|
|
-- new format
|
|
_ -> ("definition" .= _crrDefinition) : commonFields
|
|
where
|
|
commonFields =
|
|
[ "source" .= _crrSource,
|
|
"table" .= _crrTable,
|
|
"name" .= _crrName
|
|
]
|
|
|
|
runCreateRemoteRelationship ::
|
|
forall b m.
|
|
(MonadError QErr m, CacheRWM m, MetadataM m, BackendMetadata b) =>
|
|
CreateFromSourceRelationship b ->
|
|
m EncJSON
|
|
runCreateRemoteRelationship CreateFromSourceRelationship {..} = do
|
|
void $ askTabInfo @b _crrSource _crrTable
|
|
let metadataObj =
|
|
MOSourceObjId _crrSource $
|
|
AB.mkAnyBackend $
|
|
SMOTableObj @b _crrTable $
|
|
MTORemoteRelationship _crrName
|
|
buildSchemaCacheFor metadataObj $
|
|
MetadataModifier $
|
|
tableMetadataSetter @b _crrSource _crrTable . tmRemoteRelationships
|
|
%~ OMap.insert _crrName (RemoteRelationship _crrName _crrDefinition)
|
|
pure successMsg
|
|
|
|
runUpdateRemoteRelationship ::
|
|
forall b m.
|
|
(MonadError QErr m, CacheRWM m, MetadataM m, BackendMetadata b) =>
|
|
CreateFromSourceRelationship b ->
|
|
m EncJSON
|
|
runUpdateRemoteRelationship CreateFromSourceRelationship {..} = do
|
|
fieldInfoMap <- askFieldInfoMap @b _crrSource _crrTable
|
|
let metadataObj =
|
|
MOSourceObjId _crrSource $
|
|
AB.mkAnyBackend $
|
|
SMOTableObj @b _crrTable $
|
|
MTORemoteRelationship _crrName
|
|
void $ askRemoteRel fieldInfoMap _crrName
|
|
buildSchemaCacheFor metadataObj $
|
|
MetadataModifier $
|
|
tableMetadataSetter @b _crrSource _crrTable . tmRemoteRelationships
|
|
%~ OMap.insert _crrName (RemoteRelationship _crrName _crrDefinition)
|
|
pure successMsg
|
|
|
|
--------------------------------------------------------------------------------
|
|
-- Drop relationship
|
|
|
|
-- | Argument to the @_drop_remote_relationship@ family of metadata commands.
|
|
data DeleteFromSourceRelationship (b :: BackendType) = DeleteFromSourceRelationship
|
|
{ _drrSource :: SourceName,
|
|
_drrTable :: TableName b,
|
|
_drrName :: RelName
|
|
}
|
|
|
|
instance Backend b => FromJSON (DeleteFromSourceRelationship b) where
|
|
parseJSON = J.withObject "DeleteFromSourceRelationship" $ \o ->
|
|
DeleteFromSourceRelationship
|
|
<$> o .:? "source" .!= defaultSource
|
|
<*> o .: "table"
|
|
<*> o .: "name"
|
|
|
|
runDeleteRemoteRelationship ::
|
|
forall b m.
|
|
(BackendMetadata b, MonadError QErr m, CacheRWM m, MetadataM m) =>
|
|
DeleteFromSourceRelationship b ->
|
|
m EncJSON
|
|
runDeleteRemoteRelationship (DeleteFromSourceRelationship source table relName) = do
|
|
fieldInfoMap <- askFieldInfoMap @b source table
|
|
void $ askRemoteRel fieldInfoMap relName
|
|
let metadataObj =
|
|
MOSourceObjId source $
|
|
AB.mkAnyBackend $
|
|
SMOTableObj @b table $
|
|
MTORemoteRelationship relName
|
|
buildSchemaCacheFor metadataObj $
|
|
MetadataModifier $
|
|
tableMetadataSetter @b source table %~ dropRemoteRelationshipInMetadata relName
|
|
pure successMsg
|
|
|
|
--------------------------------------------------------------------------------
|
|
-- Schema cache building (TODO: move this elsewere!)
|
|
|
|
-- | Internal intermediary step.
|
|
--
|
|
-- We build the output of sources in two steps:
|
|
-- 1. we first resolve sources, and collect the core info of their tables
|
|
-- 2. we then build the entire output from the collection of partially resolved sources
|
|
--
|
|
-- We need this split to be able to resolve cross-source relationships: to process one source's
|
|
-- remote relationship, we need to know about the target source's tables core info.
|
|
--
|
|
-- This data structure is used as an argument to @AnyBackend@ in the backend-agnostic intermediary
|
|
-- collection, and used here to build remote field info.
|
|
data PartiallyResolvedSource b = PartiallyResolvedSource
|
|
{ _prsSourceMetadata :: !(SourceMetadata b),
|
|
_resolvedSource :: !(ResolvedSource b),
|
|
_tableCoreInfoMap :: !(HashMap (TableName b) (TableCoreInfoG b (ColumnInfo b) (ColumnInfo b)))
|
|
}
|
|
|
|
-- TODO: this is not actually called by the remote relationship DDL API and is only used as part of
|
|
-- the schema cache process. Should this be moved elsewhere?
|
|
buildRemoteFieldInfo ::
|
|
forall m b.
|
|
(Backend b, QErrM m) =>
|
|
SourceName ->
|
|
TableName b ->
|
|
FieldInfoMap (FieldInfo b) ->
|
|
RemoteRelationship ->
|
|
HashMap SourceName (AB.AnyBackend PartiallyResolvedSource) ->
|
|
RemoteSchemaMap ->
|
|
m (RemoteFieldInfo b, [SchemaDependency])
|
|
buildRemoteFieldInfo sourceSource sourceTable fields RemoteRelationship {..} allSources remoteSchemaMap =
|
|
case _rrDefinition of
|
|
RelationshipToSource ToSourceRelationshipDef {..} -> do
|
|
targetTables <-
|
|
Map.lookup _tsrdSource allSources
|
|
`onNothing` throw400 NotFound ("source not found: " <>> _tsrdSource)
|
|
AB.dispatchAnyBackend @Backend targetTables \(partiallyResolvedSource :: PartiallyResolvedSource b') -> do
|
|
let PartiallyResolvedSource _ targetSourceInfo targetTablesInfo = partiallyResolvedSource
|
|
(targetTable :: TableName b') <- runAesonParser J.parseJSON _tsrdTable
|
|
targetColumns <-
|
|
fmap _tciFieldInfoMap $
|
|
onNothing (Map.lookup targetTable targetTablesInfo) $ throwTableDoesNotExist @b' targetTable
|
|
columnPairs <- for (Map.toList _tsrdFieldMapping) \(srcFieldName, tgtFieldName) -> do
|
|
srcField <- askFieldInfo fields srcFieldName
|
|
tgtField <- askFieldInfo targetColumns tgtFieldName
|
|
srcColumn <- case srcField of
|
|
FIColumn column -> pure column
|
|
_ -> throw400 NotSupported "relationships from non-columns are not supported yet"
|
|
pure (srcFieldName, srcColumn, tgtField)
|
|
mapping <- for columnPairs \(srcFieldName, srcColumn, tgtColumn) -> do
|
|
tgtScalar <- case pgiType tgtColumn of
|
|
ColumnScalar scalarType -> pure scalarType
|
|
ColumnEnumReference _ -> throw400 NotSupported "relationships to enum fields are not supported yet"
|
|
pure (srcFieldName, (srcColumn, tgtScalar, pgiColumn tgtColumn))
|
|
let sourceConfig = _rsConfig targetSourceInfo
|
|
sourceCustomization = _rsCustomization targetSourceInfo
|
|
rsri = RemoteSourceFieldInfo _rrName _tsrdRelationshipType _tsrdSource sourceConfig sourceCustomization targetTable $ Map.fromList mapping
|
|
tableDependencies =
|
|
[ SchemaDependency (SOSourceObj sourceSource $ AB.mkAnyBackend $ SOITable @b sourceTable) DRTable,
|
|
SchemaDependency (SOSourceObj _tsrdSource $ AB.mkAnyBackend $ SOITable @b' targetTable) DRTable
|
|
]
|
|
columnDependencies = flip concatMap columnPairs \(_, srcColumn, tgtColumn) ->
|
|
[ SchemaDependency (SOSourceObj sourceSource $ AB.mkAnyBackend $ SOITableObj @b sourceTable $ TOCol @b $ pgiColumn srcColumn) DRRemoteRelationship,
|
|
SchemaDependency (SOSourceObj _tsrdSource $ AB.mkAnyBackend $ SOITableObj @b' targetTable $ TOCol @b' $ pgiColumn tgtColumn) DRRemoteRelationship
|
|
]
|
|
pure (RFISource $ AB.mkAnyBackend @b' rsri, tableDependencies <> columnDependencies)
|
|
RelationshipToSchema _ remoteRelationship@ToSchemaRelationshipDef {..} -> do
|
|
RemoteSchemaCtx {..} <-
|
|
onNothing (Map.lookup _trrdRemoteSchema remoteSchemaMap) $
|
|
throw400 RemoteSchemaError $ "remote schema with name " <> _trrdRemoteSchema <<> " not found"
|
|
remoteField <-
|
|
validateSourceToSchemaRelationship remoteRelationship sourceTable _rrName sourceSource (_rscInfo, _rscIntroOriginal) fields
|
|
`onLeft` (throw400 RemoteSchemaError . errorToText)
|
|
let tableDep = SchemaDependency (SOSourceObj sourceSource $ AB.mkAnyBackend $ SOITable @b sourceTable) DRTable
|
|
remoteSchemaDep = SchemaDependency (SORemoteSchema _trrdRemoteSchema) DRRemoteSchema
|
|
fieldsDep =
|
|
S.toList (_rrfiHasuraFields remoteField) <&> \case
|
|
JoinColumn column _ ->
|
|
-- TODO: shouldn't this be DRColumn??
|
|
mkColDep @b DRRemoteRelationship sourceSource sourceTable column
|
|
JoinComputedField computedFieldInfo ->
|
|
mkComputedFieldDep @b DRRemoteRelationship sourceSource sourceTable $ _scfName computedFieldInfo
|
|
schemaDependencies = (tableDep : remoteSchemaDep : fieldsDep)
|
|
pure (RFISchema remoteField, schemaDependencies)
|