2020-05-27 18:02:58 +03:00
|
|
|
module Hasura.RQL.DDL.RemoteRelationship
|
2021-09-24 01:56:37 +03:00
|
|
|
( runCreateRemoteRelationship,
|
|
|
|
runDeleteRemoteRelationship,
|
|
|
|
runUpdateRemoteRelationship,
|
|
|
|
DeleteRemoteRelationship,
|
|
|
|
dropRemoteRelationshipInMetadata,
|
|
|
|
PartiallyResolvedSource (..),
|
|
|
|
buildRemoteFieldInfo,
|
|
|
|
)
|
|
|
|
where
|
2020-05-27 18:02:58 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
import Data.Aeson
|
|
|
|
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
|
|
|
|
import Hasura.EncJSON
|
|
|
|
import Hasura.Prelude
|
|
|
|
import Hasura.RQL.DDL.RemoteRelationship.Validate
|
|
|
|
import Hasura.RQL.Types
|
|
|
|
import Hasura.SQL.AnyBackend (mkAnyBackend)
|
|
|
|
import Hasura.SQL.AnyBackend qualified as AB
|
2020-10-27 16:53:49 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
runCreateRemoteRelationship ::
|
|
|
|
forall b m.
|
|
|
|
(MonadError QErr m, CacheRWM m, MetadataM m, BackendMetadata b) =>
|
|
|
|
RemoteRelationship b ->
|
|
|
|
m EncJSON
|
2021-07-23 02:06:10 +03:00
|
|
|
runCreateRemoteRelationship RemoteRelationship {..} = do
|
|
|
|
void $ askTabInfo @b _rtrSource _rtrTable
|
2021-09-24 01:56:37 +03:00
|
|
|
let metadataObj =
|
|
|
|
MOSourceObjId _rtrSource $
|
|
|
|
AB.mkAnyBackend $
|
|
|
|
SMOTableObj @b _rtrTable $
|
|
|
|
MTORemoteRelationship _rtrName
|
2021-07-23 02:06:10 +03:00
|
|
|
metadata = RemoteRelationshipMetadata _rtrName _rtrDefinition
|
2021-09-24 01:56:37 +03:00
|
|
|
buildSchemaCacheFor metadataObj $
|
|
|
|
MetadataModifier $
|
|
|
|
tableMetadataSetter @b _rtrSource _rtrTable . tmRemoteRelationships
|
|
|
|
%~ OMap.insert _rtrName metadata
|
2020-05-27 18:02:58 +03:00
|
|
|
pure successMsg
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
runUpdateRemoteRelationship ::
|
|
|
|
forall b m.
|
|
|
|
(MonadError QErr m, CacheRWM m, MetadataM m, BackendMetadata b) =>
|
|
|
|
RemoteRelationship b ->
|
|
|
|
m EncJSON
|
2021-07-23 02:06:10 +03:00
|
|
|
runUpdateRemoteRelationship RemoteRelationship {..} = do
|
|
|
|
fieldInfoMap <- askFieldInfoMap @b _rtrSource _rtrTable
|
|
|
|
void $ askRemoteRel fieldInfoMap _rtrName
|
2021-09-24 01:56:37 +03:00
|
|
|
let metadataObj =
|
|
|
|
MOSourceObjId _rtrSource $
|
|
|
|
AB.mkAnyBackend $
|
|
|
|
SMOTableObj @b _rtrTable $
|
|
|
|
MTORemoteRelationship _rtrName
|
2021-07-23 02:06:10 +03:00
|
|
|
metadata = RemoteRelationshipMetadata _rtrName _rtrDefinition
|
2021-09-24 01:56:37 +03:00
|
|
|
buildSchemaCacheFor metadataObj $
|
|
|
|
MetadataModifier $
|
|
|
|
tableMetadataSetter @b _rtrSource _rtrTable . tmRemoteRelationships
|
|
|
|
%~ OMap.insert _rtrName metadata
|
2020-05-27 18:02:58 +03:00
|
|
|
pure successMsg
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
data DeleteRemoteRelationship (b :: BackendType) = DeleteRemoteRelationship
|
|
|
|
{ _drrSource :: !SourceName,
|
|
|
|
_drrTable :: !(TableName b),
|
|
|
|
_drrName :: !RemoteRelationshipName
|
Clean metadata arguments
## Description
Thanks to #1664, the Metadata API types no longer require a `ToJSON` instance. This PR follows up with a cleanup of the types of the arguments to the metadata API:
- whenever possible, it moves those argument types to where they're used (RQL.DDL.*)
- it removes all unrequired instances (mostly `ToJSON`)
This PR does not attempt to do it for _all_ such argument types. For some of the metadata operations, the type used to describe the argument to the API and used to represent the value in the metadata are one and the same (like for `CreateEndpoint`). Sometimes, the two types are intertwined in complex ways (`RemoteRelationship` and `RemoteRelationshipDef`). In the spirit of only doing uncontroversial cleaning work, this PR only moves types that are not used outside of RQL.DDL.
Furthermore, this is a small step towards separating the different types all jumbled together in RQL.Types.
## Notes
This PR also improves several `FromJSON` instances to make use of `withObject`, and to use a human readable string instead of a type name in error messages whenever possible. For instance:
- before: `expected Object for Object, but encountered X`
after: `expected Object for add computed field, but encountered X`
- before: `Expecting an object for update query`
after: `expected Object for update query, but encountered X`
This PR also renames `CreateFunctionPermission` to `FunctionPermissionArgument`, to remove the quite surprising `type DropFunctionPermission = CreateFunctionPermission`.
This PR also deletes some dead code, mostly in RQL.DML.
This PR also moves a PG-specific source resolving function from DDL.Schema.Source to the only place where it is used: App.hs.
https://github.com/hasura/graphql-engine-mono/pull/1844
GitOrigin-RevId: a594521194bb7fe6a111b02a9e099896f9fed59c
2021-07-27 13:41:42 +03:00
|
|
|
}
|
|
|
|
|
|
|
|
instance Backend b => FromJSON (DeleteRemoteRelationship b) where
|
2021-09-20 22:49:33 +03:00
|
|
|
parseJSON = withObject "DeleteRemoteRelationship" $ \o ->
|
Clean metadata arguments
## Description
Thanks to #1664, the Metadata API types no longer require a `ToJSON` instance. This PR follows up with a cleanup of the types of the arguments to the metadata API:
- whenever possible, it moves those argument types to where they're used (RQL.DDL.*)
- it removes all unrequired instances (mostly `ToJSON`)
This PR does not attempt to do it for _all_ such argument types. For some of the metadata operations, the type used to describe the argument to the API and used to represent the value in the metadata are one and the same (like for `CreateEndpoint`). Sometimes, the two types are intertwined in complex ways (`RemoteRelationship` and `RemoteRelationshipDef`). In the spirit of only doing uncontroversial cleaning work, this PR only moves types that are not used outside of RQL.DDL.
Furthermore, this is a small step towards separating the different types all jumbled together in RQL.Types.
## Notes
This PR also improves several `FromJSON` instances to make use of `withObject`, and to use a human readable string instead of a type name in error messages whenever possible. For instance:
- before: `expected Object for Object, but encountered X`
after: `expected Object for add computed field, but encountered X`
- before: `Expecting an object for update query`
after: `expected Object for update query, but encountered X`
This PR also renames `CreateFunctionPermission` to `FunctionPermissionArgument`, to remove the quite surprising `type DropFunctionPermission = CreateFunctionPermission`.
This PR also deletes some dead code, mostly in RQL.DML.
This PR also moves a PG-specific source resolving function from DDL.Schema.Source to the only place where it is used: App.hs.
https://github.com/hasura/graphql-engine-mono/pull/1844
GitOrigin-RevId: a594521194bb7fe6a111b02a9e099896f9fed59c
2021-07-27 13:41:42 +03:00
|
|
|
DeleteRemoteRelationship
|
|
|
|
<$> o .:? "source" .!= defaultSource
|
|
|
|
<*> o .: "table"
|
|
|
|
<*> o .: "name"
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
runDeleteRemoteRelationship ::
|
|
|
|
forall b m.
|
|
|
|
(BackendMetadata b, MonadError QErr m, CacheRWM m, MetadataM m) =>
|
|
|
|
DeleteRemoteRelationship b ->
|
|
|
|
m EncJSON
|
Clean metadata arguments
## Description
Thanks to #1664, the Metadata API types no longer require a `ToJSON` instance. This PR follows up with a cleanup of the types of the arguments to the metadata API:
- whenever possible, it moves those argument types to where they're used (RQL.DDL.*)
- it removes all unrequired instances (mostly `ToJSON`)
This PR does not attempt to do it for _all_ such argument types. For some of the metadata operations, the type used to describe the argument to the API and used to represent the value in the metadata are one and the same (like for `CreateEndpoint`). Sometimes, the two types are intertwined in complex ways (`RemoteRelationship` and `RemoteRelationshipDef`). In the spirit of only doing uncontroversial cleaning work, this PR only moves types that are not used outside of RQL.DDL.
Furthermore, this is a small step towards separating the different types all jumbled together in RQL.Types.
## Notes
This PR also improves several `FromJSON` instances to make use of `withObject`, and to use a human readable string instead of a type name in error messages whenever possible. For instance:
- before: `expected Object for Object, but encountered X`
after: `expected Object for add computed field, but encountered X`
- before: `Expecting an object for update query`
after: `expected Object for update query, but encountered X`
This PR also renames `CreateFunctionPermission` to `FunctionPermissionArgument`, to remove the quite surprising `type DropFunctionPermission = CreateFunctionPermission`.
This PR also deletes some dead code, mostly in RQL.DML.
This PR also moves a PG-specific source resolving function from DDL.Schema.Source to the only place where it is used: App.hs.
https://github.com/hasura/graphql-engine-mono/pull/1844
GitOrigin-RevId: a594521194bb7fe6a111b02a9e099896f9fed59c
2021-07-27 13:41:42 +03:00
|
|
|
runDeleteRemoteRelationship (DeleteRemoteRelationship source table relName) = do
|
2021-04-22 00:44:37 +03:00
|
|
|
fieldInfoMap <- askFieldInfoMap @b source table
|
2020-05-27 18:02:58 +03:00
|
|
|
void $ askRemoteRel fieldInfoMap relName
|
2021-09-24 01:56:37 +03:00
|
|
|
let metadataObj =
|
|
|
|
MOSourceObjId source $
|
|
|
|
AB.mkAnyBackend $
|
|
|
|
SMOTableObj @b table $
|
|
|
|
MTORemoteRelationship relName
|
|
|
|
buildSchemaCacheFor metadataObj $
|
|
|
|
MetadataModifier $
|
|
|
|
tableMetadataSetter @b source table %~ dropRemoteRelationshipInMetadata relName
|
2020-05-27 18:02:58 +03:00
|
|
|
pure successMsg
|
|
|
|
|
2021-07-23 02:06:10 +03:00
|
|
|
-- | 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
|
2021-09-24 01:56:37 +03:00
|
|
|
{ _prsSourceMetadata :: !(SourceMetadata b),
|
|
|
|
_resolvedSource :: !(ResolvedSource b),
|
|
|
|
_tableCoreInfoMap :: !(HashMap (TableName b) (TableCoreInfoG b (ColumnInfo b) (ColumnInfo b)))
|
2021-07-23 02:06:10 +03:00
|
|
|
}
|
|
|
|
|
|
|
|
-- 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?
|
2021-09-24 01:56:37 +03:00
|
|
|
buildRemoteFieldInfo ::
|
|
|
|
forall m b.
|
|
|
|
(Backend b, QErrM m) =>
|
|
|
|
SourceName ->
|
|
|
|
TableName b ->
|
|
|
|
FieldInfoMap (FieldInfo b) ->
|
|
|
|
RemoteRelationship b ->
|
|
|
|
HashMap SourceName (AB.AnyBackend PartiallyResolvedSource) ->
|
|
|
|
RemoteSchemaMap ->
|
|
|
|
m (RemoteFieldInfo b, [SchemaDependency])
|
|
|
|
buildRemoteFieldInfo sourceSource sourceTable fields RemoteRelationship {..} allSources remoteSchemaMap =
|
2021-07-23 02:06:10 +03:00
|
|
|
case _rtrDefinition of
|
2021-09-24 01:56:37 +03:00
|
|
|
RemoteSourceRelDef RemoteSourceRelationshipDef {..} -> do
|
|
|
|
targetTables <-
|
|
|
|
Map.lookup _rsrSource allSources
|
|
|
|
`onNothing` throw400 NotFound ("source not found: " <>> _rsrSource)
|
2021-07-23 02:06:10 +03:00
|
|
|
AB.dispatchAnyBackend @Backend targetTables \(partiallyResolvedSource :: PartiallyResolvedSource b') -> do
|
|
|
|
let PartiallyResolvedSource _ targetSourceInfo targetTablesInfo = partiallyResolvedSource
|
|
|
|
(targetTable :: TableName b') <- runAesonParser J.parseJSON _rsrTable
|
2021-09-24 01:56:37 +03:00
|
|
|
targetColumns <-
|
|
|
|
fmap _tciFieldInfoMap $
|
|
|
|
onNothing (Map.lookup targetTable targetTablesInfo) $ throwTableDoesNotExist @b' targetTable
|
2021-07-23 02:06:10 +03:00
|
|
|
columnPairs <- for (Map.toList _rsrFieldMapping) \(srcFieldName, tgtFieldName) -> do
|
2021-09-24 01:56:37 +03:00
|
|
|
srcField <- askFieldInfo fields srcFieldName
|
|
|
|
tgtField <- askFieldInfo targetColumns tgtFieldName
|
2021-07-23 02:06:10 +03:00
|
|
|
srcColumn <- case srcField of
|
|
|
|
FIColumn column -> pure column
|
2021-09-24 01:56:37 +03:00
|
|
|
_ -> throw400 NotSupported "relationships from non-columns are not supported yet"
|
2021-07-23 02:06:10 +03:00
|
|
|
pure (srcFieldName, srcColumn, tgtField)
|
|
|
|
mapping <- for columnPairs \(srcFieldName, srcColumn, tgtColumn) -> do
|
|
|
|
tgtScalar <- case pgiType tgtColumn of
|
|
|
|
ColumnScalar scalarType -> pure scalarType
|
2021-09-24 01:56:37 +03:00
|
|
|
ColumnEnumReference _ -> throw400 NotSupported "relationships to enum fields are not supported yet"
|
2021-07-23 02:06:10 +03:00
|
|
|
pure (srcFieldName, (srcColumn, tgtScalar, pgiColumn tgtColumn))
|
|
|
|
let sourceConfig = _rsConfig targetSourceInfo
|
|
|
|
rsri = RemoteSourceRelationshipInfo _rtrName _rsrRelationshipType _rsrSource sourceConfig targetTable $ Map.fromList mapping
|
|
|
|
tableDependencies =
|
2021-09-24 01:56:37 +03:00
|
|
|
[ SchemaDependency (SOSourceObj sourceSource $ AB.mkAnyBackend $ SOITable @b sourceTable) DRTable,
|
|
|
|
SchemaDependency (SOSourceObj _rsrSource $ AB.mkAnyBackend $ SOITable @b' targetTable) DRTable
|
2021-07-23 02:06:10 +03:00
|
|
|
]
|
|
|
|
columnDependencies = flip concatMap columnPairs \(_, srcColumn, tgtColumn) ->
|
2021-09-24 01:56:37 +03:00
|
|
|
[ SchemaDependency (SOSourceObj sourceSource $ AB.mkAnyBackend $ SOITableObj @b sourceTable $ TOCol @b $ pgiColumn srcColumn) DRRemoteRelationship,
|
|
|
|
SchemaDependency (SOSourceObj _rsrSource $ AB.mkAnyBackend $ SOITableObj @b' targetTable $ TOCol @b' $ pgiColumn tgtColumn) DRRemoteRelationship
|
2021-07-23 02:06:10 +03:00
|
|
|
]
|
|
|
|
pure (RFISource $ mkAnyBackend @b' rsri, tableDependencies <> columnDependencies)
|
2021-09-24 01:56:37 +03:00
|
|
|
RemoteSchemaRelDef _ remoteRelationship@RemoteSchemaRelationshipDef {..} -> do
|
2021-07-30 14:33:06 +03:00
|
|
|
RemoteSchemaCtx {..} <-
|
2021-09-24 01:56:37 +03:00
|
|
|
onNothing (Map.lookup _rrdRemoteSchemaName remoteSchemaMap) $
|
|
|
|
throw400 RemoteSchemaError $ "remote schema with name " <> _rrdRemoteSchemaName <<> " not found"
|
|
|
|
remoteField <-
|
|
|
|
validateRemoteSchemaRelationship remoteRelationship _rtrTable _rtrName _rtrSource (_rscInfo, _rscIntroOriginal) fields
|
|
|
|
`onLeft` (throw400 RemoteSchemaError . errorToText)
|
2021-07-23 02:06:10 +03:00
|
|
|
let tableDep = SchemaDependency (SOSourceObj _rtrSource $ AB.mkAnyBackend $ SOITable @b _rtrTable) DRTable
|
|
|
|
remoteSchemaDep = SchemaDependency (SORemoteSchema _rrdRemoteSchemaName) DRRemoteSchema
|
2021-09-24 01:56:37 +03:00
|
|
|
fieldsDep =
|
|
|
|
S.toList (_rfiHasuraFields remoteField) <&> \case
|
|
|
|
JoinColumn columnInfo ->
|
|
|
|
-- TODO: shouldn't this be DRColumn??
|
|
|
|
mkColDep @b DRRemoteRelationship _rtrSource _rtrTable $ pgiColumn columnInfo
|
|
|
|
JoinComputedField computedFieldInfo ->
|
|
|
|
mkComputedFieldDep @b DRRemoteRelationship _rtrSource _rtrTable $ _scfName computedFieldInfo
|
2021-07-23 02:06:10 +03:00
|
|
|
schemaDependencies = (tableDep : remoteSchemaDep : fieldsDep)
|
|
|
|
pure (RFISchema remoteField, schemaDependencies)
|