2022-03-16 03:39:21 +03:00
|
|
|
{-# LANGUAGE TemplateHaskell #-}
|
2021-12-14 09:45:13 +03:00
|
|
|
{-# LANGUAGE UndecidableInstances #-}
|
|
|
|
|
2020-05-27 18:02:58 +03:00
|
|
|
module Hasura.RQL.DDL.RemoteRelationship
|
2021-12-01 07:53:34 +03:00
|
|
|
( CreateFromSourceRelationship (..),
|
|
|
|
runCreateRemoteRelationship,
|
2021-09-24 01:56:37 +03:00
|
|
|
runDeleteRemoteRelationship,
|
|
|
|
runUpdateRemoteRelationship,
|
2021-12-01 07:53:34 +03:00
|
|
|
DeleteFromSourceRelationship (..),
|
2021-09-24 01:56:37 +03:00
|
|
|
dropRemoteRelationshipInMetadata,
|
|
|
|
PartiallyResolvedSource (..),
|
|
|
|
buildRemoteFieldInfo,
|
2022-02-03 21:58:37 +03:00
|
|
|
CreateRemoteSchemaRemoteRelationship (..),
|
|
|
|
runCreateRemoteSchemaRemoteRelationship,
|
|
|
|
runUpdateRemoteSchemaRemoteRelationship,
|
|
|
|
DeleteRemoteSchemaRemoteRelationship (..),
|
|
|
|
runDeleteRemoteSchemaRemoteRelationship,
|
|
|
|
getRemoteSchemaEntityJoinColumns,
|
2021-09-24 01:56:37 +03:00
|
|
|
)
|
|
|
|
where
|
2020-05-27 18:02:58 +03:00
|
|
|
|
2022-06-09 19:39:50 +03:00
|
|
|
import Control.Lens (at, non, to, (^?))
|
2021-12-14 09:45:13 +03:00
|
|
|
import Data.Aeson (FromJSON (..), ToJSON (..), (.!=), (.:), (.:?), (.=))
|
2021-09-24 01:56:37 +03:00
|
|
|
import Data.Aeson qualified as J
|
2022-06-08 18:31:28 +03:00
|
|
|
import Data.Aeson.KeyMap qualified as KM
|
2022-02-03 21:58:37 +03:00
|
|
|
import Data.Aeson.TH qualified as J
|
2021-09-24 01:56:37 +03:00
|
|
|
import Data.HashMap.Strict qualified as Map
|
|
|
|
import Data.HashMap.Strict.InsOrd qualified as OMap
|
2021-12-14 09:45:13 +03:00
|
|
|
import Data.Text.Extended ((<<>), (<>>))
|
2021-09-24 01:56:37 +03:00
|
|
|
import Hasura.Base.Error
|
2022-02-03 21:58:37 +03:00
|
|
|
( Code (NotExists, NotFound, NotSupported, RemoteSchemaError),
|
2021-12-14 09:45:13 +03:00
|
|
|
QErr,
|
|
|
|
QErrM,
|
|
|
|
runAesonParser,
|
|
|
|
throw400,
|
|
|
|
)
|
|
|
|
import Hasura.EncJSON (EncJSON)
|
2021-09-24 01:56:37 +03:00
|
|
|
import Hasura.Prelude
|
|
|
|
import Hasura.RQL.DDL.RemoteRelationship.Validate
|
2021-12-14 09:45:13 +03:00
|
|
|
( errorToText,
|
2021-12-22 02:14:56 +03:00
|
|
|
validateToSchemaRelationship,
|
2021-12-14 09:45:13 +03:00
|
|
|
)
|
2022-04-27 16:57:28 +03:00
|
|
|
import Hasura.RQL.Types.Backend
|
|
|
|
import Hasura.RQL.Types.Column
|
|
|
|
import Hasura.RQL.Types.Common
|
|
|
|
import Hasura.RQL.Types.Metadata
|
|
|
|
import Hasura.RQL.Types.Metadata.Backend
|
|
|
|
import Hasura.RQL.Types.Metadata.Object
|
|
|
|
import Hasura.RQL.Types.Relationships.Remote
|
|
|
|
import Hasura.RQL.Types.Relationships.ToSchema
|
|
|
|
import Hasura.RQL.Types.Relationships.ToSource
|
|
|
|
import Hasura.RQL.Types.RemoteSchema
|
|
|
|
import Hasura.RQL.Types.SchemaCache
|
|
|
|
import Hasura.RQL.Types.SchemaCache.Build
|
|
|
|
import Hasura.RQL.Types.SchemaCacheTypes
|
|
|
|
import Hasura.RQL.Types.Source
|
|
|
|
import Hasura.RQL.Types.Table
|
2021-09-24 01:56:37 +03:00
|
|
|
import Hasura.SQL.AnyBackend qualified as AB
|
2022-04-27 16:57:28 +03:00
|
|
|
import Hasura.SQL.Backend
|
2022-02-03 21:58:37 +03:00
|
|
|
import Language.GraphQL.Draft.Syntax qualified as G
|
2020-10-27 16:53:49 +03:00
|
|
|
|
2021-12-01 07:53:34 +03:00
|
|
|
--------------------------------------------------------------------------------
|
2022-02-03 21:58:37 +03:00
|
|
|
-- Create or update relationship from source
|
2021-12-01 07:53:34 +03:00
|
|
|
|
|
|
|
-- | 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,
|
2021-12-14 09:45:13 +03:00
|
|
|
_crrName :: RelName,
|
|
|
|
_crrDefinition :: RemoteRelationshipDefinition
|
2021-12-01 07:53:34 +03:00
|
|
|
}
|
2021-12-14 09:45:13 +03:00
|
|
|
|
|
|
|
deriving stock instance (Eq (TableName b)) => Eq (CreateFromSourceRelationship b)
|
|
|
|
|
|
|
|
deriving stock instance (Show (TableName b)) => Show (CreateFromSourceRelationship b)
|
2021-12-01 07:53:34 +03:00
|
|
|
|
|
|
|
instance Backend b => FromJSON (CreateFromSourceRelationship b) where
|
2021-12-14 09:45:13 +03:00
|
|
|
parseJSON = J.withObject "CreateFromSourceRelationship" $ \o -> do
|
|
|
|
_crrSource <- o .:? "source" .!= defaultSource
|
|
|
|
_crrTable <- o .: "table"
|
|
|
|
_crrName <- o .: "name"
|
Fix several issues with remote relationships.
## 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
2021-12-16 23:28:08 +03:00
|
|
|
-- In the old format, the definition is inlined; in the new format, the
|
2021-12-20 22:31:02 +03:00
|
|
|
-- definition is in the "definition" object, and we don't allow legacy
|
|
|
|
-- fields to appear under it.
|
Fix several issues with remote relationships.
## 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
2021-12-16 23:28:08 +03:00
|
|
|
remoteSchema :: Maybe J.Value <- o .:? "remote_schema"
|
|
|
|
definition <- o .:? "definition"
|
|
|
|
_crrDefinition <- case (remoteSchema, definition) of
|
|
|
|
-- old format
|
2021-12-20 22:31:02 +03:00
|
|
|
(Just {}, Nothing) -> parseRemoteRelationshipDefinition RRPLegacy $ J.Object o
|
Fix several issues with remote relationships.
## 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
2021-12-16 23:28:08 +03:00
|
|
|
-- new format
|
2021-12-20 22:31:02 +03:00
|
|
|
(Nothing, Just def) -> parseRemoteRelationshipDefinition RRPStrict def
|
Fix several issues with remote relationships.
## 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
2021-12-16 23:28:08 +03:00
|
|
|
-- both or neither
|
|
|
|
_ -> fail "create_remote_relationship expects exactly one of: remote_schema, definition"
|
2021-12-14 09:45:13 +03:00
|
|
|
pure $ CreateFromSourceRelationship {..}
|
2021-12-01 07:53:34 +03:00
|
|
|
|
|
|
|
instance (Backend b) => ToJSON (CreateFromSourceRelationship b) where
|
2022-02-03 21:58:37 +03:00
|
|
|
toJSON CreateFromSourceRelationship {..} =
|
Fix several issues with remote relationships.
## 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
2021-12-16 23:28:08 +03:00
|
|
|
-- 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.
|
2022-06-08 18:31:28 +03:00
|
|
|
J.Object obj -> commonFields <> KM.toList obj
|
Fix several issues with remote relationships.
## 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
2021-12-16 23:28:08 +03:00
|
|
|
_ -> []
|
|
|
|
-- new format
|
|
|
|
_ -> ("definition" .= _crrDefinition) : commonFields
|
|
|
|
where
|
|
|
|
commonFields =
|
|
|
|
[ "source" .= _crrSource,
|
|
|
|
"table" .= _crrTable,
|
|
|
|
"name" .= _crrName
|
|
|
|
]
|
2021-12-01 07:53:34 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
runCreateRemoteRelationship ::
|
|
|
|
forall b m.
|
|
|
|
(MonadError QErr m, CacheRWM m, MetadataM m, BackendMetadata b) =>
|
2021-12-01 07:53:34 +03:00
|
|
|
CreateFromSourceRelationship b ->
|
2021-09-24 01:56:37 +03:00
|
|
|
m EncJSON
|
2021-12-01 07:53:34 +03:00
|
|
|
runCreateRemoteRelationship CreateFromSourceRelationship {..} = do
|
2022-04-26 18:12:47 +03:00
|
|
|
void $ askTableInfo @b _crrSource _crrTable
|
2021-12-14 09:45:13 +03:00
|
|
|
let metadataObj =
|
2021-12-01 07:53:34 +03:00
|
|
|
MOSourceObjId _crrSource $
|
2021-09-24 01:56:37 +03:00
|
|
|
AB.mkAnyBackend $
|
2021-12-01 07:53:34 +03:00
|
|
|
SMOTableObj @b _crrTable $
|
2021-12-14 09:45:13 +03:00
|
|
|
MTORemoteRelationship _crrName
|
2021-09-24 01:56:37 +03:00
|
|
|
buildSchemaCacheFor metadataObj $
|
|
|
|
MetadataModifier $
|
2021-12-01 07:53:34 +03:00
|
|
|
tableMetadataSetter @b _crrSource _crrTable . tmRemoteRelationships
|
2021-12-14 09:45:13 +03:00
|
|
|
%~ OMap.insert _crrName (RemoteRelationship _crrName _crrDefinition)
|
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) =>
|
2021-12-01 07:53:34 +03:00
|
|
|
CreateFromSourceRelationship b ->
|
2021-09-24 01:56:37 +03:00
|
|
|
m EncJSON
|
2021-12-01 07:53:34 +03:00
|
|
|
runUpdateRemoteRelationship CreateFromSourceRelationship {..} = do
|
2022-04-26 18:12:47 +03:00
|
|
|
fieldInfoMap <- askTableFieldInfoMap @b _crrSource _crrTable
|
2021-12-14 09:45:13 +03:00
|
|
|
let metadataObj =
|
2021-12-01 07:53:34 +03:00
|
|
|
MOSourceObjId _crrSource $
|
2021-09-24 01:56:37 +03:00
|
|
|
AB.mkAnyBackend $
|
2021-12-01 07:53:34 +03:00
|
|
|
SMOTableObj @b _crrTable $
|
2021-12-14 09:45:13 +03:00
|
|
|
MTORemoteRelationship _crrName
|
|
|
|
void $ askRemoteRel fieldInfoMap _crrName
|
2021-09-24 01:56:37 +03:00
|
|
|
buildSchemaCacheFor metadataObj $
|
|
|
|
MetadataModifier $
|
2021-12-01 07:53:34 +03:00
|
|
|
tableMetadataSetter @b _crrSource _crrTable . tmRemoteRelationships
|
2021-12-14 09:45:13 +03:00
|
|
|
%~ OMap.insert _crrName (RemoteRelationship _crrName _crrDefinition)
|
2020-05-27 18:02:58 +03:00
|
|
|
pure successMsg
|
|
|
|
|
2021-12-01 07:53:34 +03:00
|
|
|
--------------------------------------------------------------------------------
|
2022-02-03 21:58:37 +03:00
|
|
|
-- Drop relationship from source
|
2021-12-01 07:53:34 +03:00
|
|
|
|
|
|
|
-- | Argument to the @_drop_remote_relationship@ family of metadata commands.
|
|
|
|
data DeleteFromSourceRelationship (b :: BackendType) = DeleteFromSourceRelationship
|
|
|
|
{ _drrSource :: SourceName,
|
|
|
|
_drrTable :: TableName b,
|
|
|
|
_drrName :: RelName
|
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
|
|
|
}
|
|
|
|
|
2021-12-01 07:53:34 +03:00
|
|
|
instance Backend b => FromJSON (DeleteFromSourceRelationship b) where
|
2021-12-14 09:45:13 +03:00
|
|
|
parseJSON = J.withObject "DeleteFromSourceRelationship" $ \o ->
|
2021-12-01 07:53:34 +03:00
|
|
|
DeleteFromSourceRelationship
|
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
|
|
|
<$> 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) =>
|
2021-12-01 07:53:34 +03:00
|
|
|
DeleteFromSourceRelationship b ->
|
2021-09-24 01:56:37 +03:00
|
|
|
m EncJSON
|
2021-12-01 07:53:34 +03:00
|
|
|
runDeleteRemoteRelationship (DeleteFromSourceRelationship source table relName) = do
|
2022-04-26 18:12:47 +03:00
|
|
|
fieldInfoMap <- askTableFieldInfoMap @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
|
|
|
|
|
2022-02-03 21:58:37 +03:00
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- Create relationship from remote schema
|
|
|
|
|
|
|
|
data CreateRemoteSchemaRemoteRelationship = CreateRemoteSchemaRemoteRelationship
|
|
|
|
{ _crsrrRemoteSchema :: RemoteSchemaName,
|
|
|
|
_crsrrType :: G.Name,
|
|
|
|
_crsrrName :: RelName,
|
|
|
|
_crsrrDefinition :: RemoteRelationshipDefinition
|
|
|
|
}
|
|
|
|
deriving (Generic)
|
|
|
|
|
|
|
|
instance FromJSON CreateRemoteSchemaRemoteRelationship where
|
|
|
|
parseJSON = J.withObject "CreateRemoteSchemaRemoteRelationship" $ \o ->
|
|
|
|
CreateRemoteSchemaRemoteRelationship
|
|
|
|
<$> o .: "remote_schema"
|
|
|
|
<*> o .: "type_name"
|
|
|
|
<*> o .: "name"
|
|
|
|
<*> (o .: "definition" >>= parseRemoteRelationshipDefinition RRPStrict)
|
|
|
|
|
|
|
|
$(J.deriveToJSON hasuraJSON ''CreateRemoteSchemaRemoteRelationship)
|
|
|
|
|
|
|
|
runCreateRemoteSchemaRemoteRelationship ::
|
|
|
|
forall m.
|
|
|
|
(MonadError QErr m, CacheRWM m, MetadataM m) =>
|
|
|
|
CreateRemoteSchemaRemoteRelationship ->
|
|
|
|
m EncJSON
|
|
|
|
runCreateRemoteSchemaRemoteRelationship CreateRemoteSchemaRemoteRelationship {..} = do
|
|
|
|
let metadataObj =
|
|
|
|
MORemoteSchemaRemoteRelationship _crsrrRemoteSchema _crsrrType _crsrrName
|
|
|
|
buildSchemaCacheFor metadataObj $
|
|
|
|
MetadataModifier $
|
|
|
|
metaRemoteSchemas . ix _crsrrRemoteSchema . rsmRemoteRelationships
|
|
|
|
. at _crsrrType
|
|
|
|
. non (RemoteSchemaTypeRelationships _crsrrType mempty)
|
|
|
|
. rstrsRelationships
|
|
|
|
%~ OMap.insert _crsrrName (RemoteRelationship _crsrrName _crsrrDefinition)
|
|
|
|
pure successMsg
|
|
|
|
|
|
|
|
runUpdateRemoteSchemaRemoteRelationship ::
|
|
|
|
forall m.
|
|
|
|
(MonadError QErr m, CacheRWM m, MetadataM m) =>
|
|
|
|
CreateRemoteSchemaRemoteRelationship ->
|
|
|
|
m EncJSON
|
|
|
|
runUpdateRemoteSchemaRemoteRelationship crss@CreateRemoteSchemaRemoteRelationship {..} = do
|
|
|
|
schemaCache <- askSchemaCache
|
|
|
|
let remoteRelationship =
|
|
|
|
schemaCache
|
|
|
|
^? to scRemoteSchemas
|
|
|
|
. ix _crsrrRemoteSchema
|
|
|
|
. rscRemoteRelationships
|
|
|
|
. ix _crsrrType
|
|
|
|
. ix _crsrrName
|
|
|
|
void $
|
|
|
|
onNothing remoteRelationship $
|
|
|
|
throw400 NotExists $
|
|
|
|
"no relationship defined on remote schema " <>> _crsrrRemoteSchema <<> " with name " <>> _crsrrName
|
|
|
|
runCreateRemoteSchemaRemoteRelationship crss
|
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- Drop relationship from remote schema
|
|
|
|
|
|
|
|
-- | Argument to the @_drop_remote_relationship@ family of metadata commands.
|
|
|
|
data DeleteRemoteSchemaRemoteRelationship = DeleteRemoteSchemaRemoteRelationship
|
|
|
|
{ _drsrrRemoteSchema :: RemoteSchemaName,
|
|
|
|
_drsrrTypeName :: G.Name,
|
|
|
|
_drsrrName :: RelName
|
|
|
|
}
|
|
|
|
|
|
|
|
instance FromJSON DeleteRemoteSchemaRemoteRelationship where
|
|
|
|
parseJSON = J.withObject "DeleteRemoteSchemaRemoteRelationship" $ \o ->
|
|
|
|
DeleteRemoteSchemaRemoteRelationship
|
|
|
|
<$> o .: "remote_schema"
|
|
|
|
<*> o .: "type_name"
|
|
|
|
<*> o .: "name"
|
|
|
|
|
|
|
|
runDeleteRemoteSchemaRemoteRelationship ::
|
|
|
|
forall m.
|
|
|
|
(MonadError QErr m, CacheRWM m, MetadataM m) =>
|
|
|
|
DeleteRemoteSchemaRemoteRelationship ->
|
|
|
|
m EncJSON
|
|
|
|
runDeleteRemoteSchemaRemoteRelationship DeleteRemoteSchemaRemoteRelationship {..} = do
|
|
|
|
let relName = _drsrrName
|
|
|
|
metadataObj =
|
|
|
|
MORemoteSchemaRemoteRelationship _drsrrRemoteSchema _drsrrTypeName relName
|
|
|
|
buildSchemaCacheFor metadataObj $
|
|
|
|
MetadataModifier $
|
|
|
|
metaRemoteSchemas . ix _drsrrRemoteSchema . rsmRemoteRelationships . ix _drsrrTypeName . rstrsRelationships
|
|
|
|
%~ OMap.delete relName
|
|
|
|
pure successMsg
|
|
|
|
|
2021-12-01 07:53:34 +03:00
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- Schema cache building (TODO: move this elsewere!)
|
|
|
|
|
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
|
2022-06-27 03:36:53 +03:00
|
|
|
{ _prsSourceMetadata :: SourceMetadata b,
|
|
|
|
_resolvedSource :: ResolvedSource b,
|
|
|
|
_tableCoreInfoMap :: HashMap (TableName b) (TableCoreInfoG b (ColumnInfo b) (ColumnInfo b)),
|
|
|
|
_eventTriggerInfoMap :: HashMap (TableName b) (EventTriggerInfoMap b)
|
2021-07-23 02:06:10 +03:00
|
|
|
}
|
|
|
|
|
2021-12-22 02:14:56 +03:00
|
|
|
-- | Builds the schema cache representation of a remote relationship
|
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 ::
|
2021-12-22 02:14:56 +03:00
|
|
|
QErrM m =>
|
|
|
|
-- | The entity on which the remote relationship is defined
|
|
|
|
LHSIdentifier ->
|
|
|
|
-- | join fields provided by the LHS entity
|
|
|
|
Map.HashMap FieldName lhsJoinField ->
|
|
|
|
-- | definition of remote relationship
|
2021-12-01 07:53:34 +03:00
|
|
|
RemoteRelationship ->
|
2021-12-22 02:14:56 +03:00
|
|
|
-- | Required context to process cross boundary relationships
|
2021-09-24 01:56:37 +03:00
|
|
|
HashMap SourceName (AB.AnyBackend PartiallyResolvedSource) ->
|
2021-12-22 02:14:56 +03:00
|
|
|
-- | Required context to process cross boundary relationships
|
2021-09-24 01:56:37 +03:00
|
|
|
RemoteSchemaMap ->
|
2021-12-22 02:14:56 +03:00
|
|
|
-- | returns
|
|
|
|
-- 1. schema cache representation of the remote relationships
|
|
|
|
-- 2. the dependencies on the RHS of the join. The dependencies
|
|
|
|
-- on the LHS entities has to be handled by the calling function
|
|
|
|
m (RemoteFieldInfo lhsJoinField, [SchemaDependency])
|
|
|
|
buildRemoteFieldInfo lhsIdentifier lhsJoinFields RemoteRelationship {..} allSources remoteSchemaMap =
|
2021-12-01 07:53:34 +03:00
|
|
|
case _rrDefinition of
|
|
|
|
RelationshipToSource ToSourceRelationshipDef {..} -> do
|
2021-09-24 01:56:37 +03:00
|
|
|
targetTables <-
|
2021-12-01 07:53:34 +03:00
|
|
|
Map.lookup _tsrdSource allSources
|
|
|
|
`onNothing` throw400 NotFound ("source not found: " <>> _tsrdSource)
|
2021-07-23 02:06:10 +03:00
|
|
|
AB.dispatchAnyBackend @Backend targetTables \(partiallyResolvedSource :: PartiallyResolvedSource b') -> do
|
2022-06-27 03:36:53 +03:00
|
|
|
let PartiallyResolvedSource _ targetSourceInfo targetTablesInfo _ = partiallyResolvedSource
|
2021-12-01 07:53:34 +03:00
|
|
|
(targetTable :: TableName b') <- runAesonParser J.parseJSON _tsrdTable
|
2021-09-24 01:56:37 +03:00
|
|
|
targetColumns <-
|
|
|
|
fmap _tciFieldInfoMap $
|
2022-04-26 18:12:47 +03:00
|
|
|
onNothing (Map.lookup targetTable targetTablesInfo) $
|
|
|
|
throw400 NotExists $ "table " <> targetTable <<> " does not exist in source: " <> sourceNameToText _tsrdSource
|
2021-12-22 02:14:56 +03:00
|
|
|
-- TODO: rhs fields should also ideally be DBJoinFields
|
2021-12-01 07:53:34 +03:00
|
|
|
columnPairs <- for (Map.toList _tsrdFieldMapping) \(srcFieldName, tgtFieldName) -> do
|
2021-12-22 02:14:56 +03:00
|
|
|
lhsJoinField <- askFieldInfo lhsJoinFields srcFieldName
|
2021-09-24 01:56:37 +03:00
|
|
|
tgtField <- askFieldInfo targetColumns tgtFieldName
|
2021-12-22 02:14:56 +03:00
|
|
|
pure (srcFieldName, lhsJoinField, tgtField)
|
2022-02-03 21:58:37 +03:00
|
|
|
columnMapping <- for columnPairs \(srcFieldName, srcColumn, tgtColumn) -> do
|
2022-01-19 11:37:50 +03:00
|
|
|
tgtScalar <- case ciType tgtColumn of
|
2021-07-23 02:06:10 +03:00
|
|
|
ColumnScalar scalarType -> pure scalarType
|
2021-09-24 01:56:37 +03:00
|
|
|
ColumnEnumReference _ -> throw400 NotSupported "relationships to enum fields are not supported yet"
|
2022-01-19 11:37:50 +03:00
|
|
|
pure (srcFieldName, (srcColumn, tgtScalar, ciColumn tgtColumn))
|
2021-07-23 02:06:10 +03:00
|
|
|
let sourceConfig = _rsConfig targetSourceInfo
|
2021-10-29 17:42:07 +03:00
|
|
|
sourceCustomization = _rsCustomization targetSourceInfo
|
2021-12-22 02:14:56 +03:00
|
|
|
rsri =
|
|
|
|
RemoteSourceFieldInfo _rrName _tsrdRelationshipType _tsrdSource sourceConfig sourceCustomization targetTable $
|
2022-02-03 21:58:37 +03:00
|
|
|
fmap (\(_, tgtType, tgtColumn) -> (tgtType, tgtColumn)) $ Map.fromList columnMapping
|
2021-12-22 02:14:56 +03:00
|
|
|
rhsDependencies =
|
|
|
|
SchemaDependency (SOSourceObj _tsrdSource $ AB.mkAnyBackend $ SOITable @b' targetTable) DRTable :
|
|
|
|
flip map columnPairs \(_, _srcColumn, tgtColumn) ->
|
|
|
|
SchemaDependency
|
|
|
|
( SOSourceObj _tsrdSource $
|
2022-01-19 11:37:50 +03:00
|
|
|
AB.mkAnyBackend $ SOITableObj @b' targetTable $ TOCol @b' $ ciColumn tgtColumn
|
2021-12-22 02:14:56 +03:00
|
|
|
)
|
|
|
|
DRRemoteRelationship
|
2022-02-03 21:58:37 +03:00
|
|
|
requiredLHSJoinFields = fmap (\(srcField, _, _) -> srcField) $ Map.fromList columnMapping
|
2021-12-22 02:14:56 +03:00
|
|
|
pure (RemoteFieldInfo requiredLHSJoinFields $ RFISource $ AB.mkAnyBackend @b' rsri, rhsDependencies)
|
2021-12-01 07:53:34 +03:00
|
|
|
RelationshipToSchema _ remoteRelationship@ToSchemaRelationshipDef {..} -> do
|
2021-07-30 14:33:06 +03:00
|
|
|
RemoteSchemaCtx {..} <-
|
2021-12-01 07:53:34 +03:00
|
|
|
onNothing (Map.lookup _trrdRemoteSchema remoteSchemaMap) $
|
|
|
|
throw400 RemoteSchemaError $ "remote schema with name " <> _trrdRemoteSchema <<> " not found"
|
2021-12-22 02:14:56 +03:00
|
|
|
(requiredLHSJoinFields, remoteField) <-
|
|
|
|
validateToSchemaRelationship remoteRelationship lhsIdentifier _rrName (_rscInfo, _rscIntroOriginal) lhsJoinFields
|
2021-09-24 01:56:37 +03:00
|
|
|
`onLeft` (throw400 RemoteSchemaError . errorToText)
|
2021-12-22 02:14:56 +03:00
|
|
|
let rhsDependencies = [SchemaDependency (SORemoteSchema _trrdRemoteSchema) DRRemoteSchema]
|
|
|
|
pure (RemoteFieldInfo requiredLHSJoinFields $ RFISchema remoteField, rhsDependencies)
|
2022-02-03 21:58:37 +03:00
|
|
|
|
|
|
|
getRemoteSchemaEntityJoinColumns ::
|
|
|
|
(MonadError QErr m) =>
|
|
|
|
RemoteSchemaName ->
|
|
|
|
RemoteSchemaIntrospection ->
|
|
|
|
G.Name ->
|
|
|
|
m (HashMap FieldName G.Name)
|
|
|
|
getRemoteSchemaEntityJoinColumns remoteSchemaName introspection typeName = do
|
|
|
|
typeDefinition <-
|
|
|
|
onNothing (lookupType introspection typeName) $
|
2022-03-17 23:53:56 +03:00
|
|
|
throw400 NotFound ("no type named " <> typeName <<> " defined in remote schema " <>> remoteSchemaName)
|
2022-02-03 21:58:37 +03:00
|
|
|
case typeDefinition of
|
|
|
|
G.TypeDefinitionObject objectDefinition ->
|
|
|
|
pure $
|
|
|
|
Map.fromList $ do
|
|
|
|
fieldDefinition <- G._otdFieldsDefinition objectDefinition
|
|
|
|
guard $ null $ G._fldArgumentsDefinition fieldDefinition
|
|
|
|
pure (FieldName $ G.unName $ G._fldName fieldDefinition, G._fldName fieldDefinition)
|
|
|
|
_ -> throw400 NotSupported "remote relationships on a remote schema can only be defined on object types"
|