2019-03-01 12:17:22 +03:00
|
|
|
module Hasura.RQL.DDL.Relationship
|
2021-09-24 01:56:37 +03:00
|
|
|
( CreateArrRel (..),
|
|
|
|
CreateObjRel (..),
|
|
|
|
runCreateRelationship,
|
|
|
|
objRelP2Setup,
|
|
|
|
arrRelP2Setup,
|
|
|
|
DropRel,
|
|
|
|
runDropRel,
|
|
|
|
dropRelationshipInMetadata,
|
|
|
|
SetRelComment,
|
|
|
|
runSetRelComment,
|
2019-03-01 12:17:22 +03:00
|
|
|
)
|
|
|
|
where
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
import Control.Lens ((.~))
|
|
|
|
import Data.Aeson.Types
|
2022-04-26 18:12:47 +03:00
|
|
|
import Data.HashMap.Strict qualified as Map
|
2021-09-24 01:56:37 +03:00
|
|
|
import Data.HashMap.Strict.InsOrd qualified as OMap
|
2022-05-10 18:43:24 +03:00
|
|
|
import Data.HashMap.Strict.NonEmpty qualified as NEHashMap
|
2022-04-26 18:12:47 +03:00
|
|
|
import Data.HashSet qualified as Set
|
2021-09-24 01:56:37 +03:00
|
|
|
import Data.Text.Extended
|
|
|
|
import Data.Tuple (swap)
|
|
|
|
import Hasura.Base.Error
|
|
|
|
import Hasura.EncJSON
|
|
|
|
import Hasura.Prelude
|
|
|
|
import Hasura.RQL.DDL.Permission
|
2022-04-27 16:57:28 +03:00
|
|
|
import Hasura.RQL.Types.Backend
|
|
|
|
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.Local
|
|
|
|
import Hasura.RQL.Types.SchemaCache
|
|
|
|
import Hasura.RQL.Types.SchemaCache.Build
|
|
|
|
import Hasura.RQL.Types.SchemaCacheTypes
|
|
|
|
import Hasura.RQL.Types.Table
|
2021-09-24 01:56:37 +03:00
|
|
|
import Hasura.SQL.AnyBackend qualified as AB
|
2021-04-27 16:44:51 +03:00
|
|
|
|
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
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- Create local relationship
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
newtype CreateArrRel b = CreateArrRel {unCreateArrRel :: WithTable b (ArrRelDef b)}
|
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
|
|
|
deriving newtype (FromJSON)
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
newtype CreateObjRel b = CreateObjRel {unCreateObjRel :: WithTable b (ObjRelDef b)}
|
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
|
|
|
deriving newtype (FromJSON)
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
runCreateRelationship ::
|
|
|
|
forall m b a.
|
|
|
|
(MonadError QErr m, CacheRWM m, ToJSON a, MetadataM m, Backend b, BackendMetadata b) =>
|
|
|
|
RelType ->
|
|
|
|
WithTable b (RelDef a) ->
|
|
|
|
m EncJSON
|
2020-12-28 15:56:00 +03:00
|
|
|
runCreateRelationship relType (WithTable source tableName relDef) = do
|
2020-12-08 17:22:31 +03:00
|
|
|
let relName = _rdName relDef
|
|
|
|
-- Check if any field with relationship name already exists in the table
|
2021-04-22 00:44:37 +03:00
|
|
|
tableFields <- _tciFieldInfoMap <$> askTableCoreInfo @b source tableName
|
2022-04-26 18:12:47 +03:00
|
|
|
onJust (Map.lookup (fromRel relName) tableFields) $
|
2021-09-24 01:56:37 +03:00
|
|
|
const $
|
|
|
|
throw400 AlreadyExists $
|
|
|
|
"field with name " <> relName <<> " already exists in table " <>> tableName
|
2021-05-21 05:46:58 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
tableCache <-
|
|
|
|
askSchemaCache
|
|
|
|
>>= flip onNothing (throw400 NotFound "Could not find source.")
|
|
|
|
. unsafeTableCache source
|
|
|
|
. scSources
|
2021-05-21 05:46:58 +03:00
|
|
|
|
2020-12-08 17:22:31 +03:00
|
|
|
let comment = _rdComment relDef
|
2021-09-24 01:56:37 +03:00
|
|
|
metadataObj =
|
|
|
|
MOSourceObjId source $
|
|
|
|
AB.mkAnyBackend $
|
|
|
|
SMOTableObj @b tableName $
|
|
|
|
MTORel relName relType
|
2020-12-08 17:22:31 +03:00
|
|
|
addRelationshipToMetadata <- case relType of
|
|
|
|
ObjRel -> do
|
2021-05-21 05:46:58 +03:00
|
|
|
value <- decodeValue $ toJSON relDef
|
|
|
|
validateRelationship @b
|
|
|
|
tableCache
|
|
|
|
tableName
|
|
|
|
(Left value)
|
|
|
|
pure $ tmObjectRelationships %~ OMap.insert relName (RelDef relName (_rdUsing value) comment)
|
2020-12-08 17:22:31 +03:00
|
|
|
ArrRel -> do
|
2021-05-21 05:46:58 +03:00
|
|
|
value <- decodeValue $ toJSON relDef
|
|
|
|
validateRelationship @b
|
|
|
|
tableCache
|
|
|
|
tableName
|
|
|
|
(Right value)
|
|
|
|
pure $ tmArrayRelationships %~ OMap.insert relName (RelDef relName (_rdUsing value) comment)
|
2020-12-08 17:22:31 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
buildSchemaCacheFor metadataObj $
|
|
|
|
MetadataModifier $
|
|
|
|
tableMetadataSetter @b source tableName %~ addRelationshipToMetadata
|
2019-11-20 21:21:30 +03:00
|
|
|
pure successMsg
|
2019-05-08 10:36:43 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
objRelP2Setup ::
|
|
|
|
forall b m.
|
|
|
|
(QErrM m, Backend b) =>
|
|
|
|
SourceName ->
|
|
|
|
TableName b ->
|
|
|
|
HashMap (TableName b) (HashSet (ForeignKey b)) ->
|
|
|
|
RelDef (ObjRelUsing b) ->
|
|
|
|
m (RelInfo b, [SchemaDependency])
|
server: fix the nullability of object relationships (fix hasura/graphql-engine#7201)
When adding object relationships, we set the nullability of the generated GraphQL field based on whether the database backend enforces that the referenced data always exists. For manual relationships (corresponding to `manual_configuration`), the database backend is unaware of any relationship between data, and hence such fields are always set to be nullable.
For relationships generated from foreign key constraints (corresponding to `foreign_key_constraint_on`), we distinguish between two cases:
1. The "forward" object relationship from a referencing table (i.e. which has the foreign key constraint) to a referenced table. This should be set to be non-nullable when all referencing columns are non-nullable. But in fact, it used to set it to be non-nullable if *any* referencing column is non-nullable, which is only correct in Postgres when `MATCH FULL` is set (a flag we don't consider). This fixes that by changing a boolean conjunction to a disjunction.
2. The "reverse" object relationship from a referenced table to a referencing table which has the foreign key constraint. This should always be set to be nullable. But in fact, it used to always be set to non-nullable, as was reported in hasura/graphql-engine#7201. This fixes that.
Moreover, we have moved the computation of the nullability from `Hasura.RQL.DDL.Relationship` to `Hasura.GraphQL.Schema.Select`: this nullability used to be passed through the `riIsNullable` field of `RelInfo`, but for array relationships this information is not actually used, and moreover the remaining fields of `RelInfo` are already enough to deduce the nullability.
This also adds regression tests for both (1) and (2) above.
https://github.com/hasura/graphql-engine-mono/pull/2159
GitOrigin-RevId: 617f12765614f49746d18d3368f41dfae2f3e6ca
2021-08-26 18:26:43 +03:00
|
|
|
objRelP2Setup source qt foreignKeys (RelDef rn ru _) = case ru of
|
2020-01-14 10:09:10 +03:00
|
|
|
RUManual rm -> do
|
2019-11-20 21:21:30 +03:00
|
|
|
let refqt = rmTable rm
|
2022-04-26 18:12:47 +03:00
|
|
|
(lCols, rCols) = unzip $ Map.toList $ rmColumns rm
|
2021-03-03 16:02:00 +03:00
|
|
|
io = fromMaybe BeforeParent $ rmInsertOrder rm
|
2021-09-24 01:56:37 +03:00
|
|
|
mkDependency tableName reason col =
|
|
|
|
SchemaDependency
|
|
|
|
( SOSourceObj source $
|
|
|
|
AB.mkAnyBackend $
|
|
|
|
SOITableObj @b tableName $
|
|
|
|
TOCol @b col
|
|
|
|
)
|
|
|
|
reason
|
|
|
|
dependencies =
|
|
|
|
map (mkDependency qt DRLeftColumn) lCols
|
|
|
|
<> map (mkDependency refqt DRRightColumn) rCols
|
server: fix the nullability of object relationships (fix hasura/graphql-engine#7201)
When adding object relationships, we set the nullability of the generated GraphQL field based on whether the database backend enforces that the referenced data always exists. For manual relationships (corresponding to `manual_configuration`), the database backend is unaware of any relationship between data, and hence such fields are always set to be nullable.
For relationships generated from foreign key constraints (corresponding to `foreign_key_constraint_on`), we distinguish between two cases:
1. The "forward" object relationship from a referencing table (i.e. which has the foreign key constraint) to a referenced table. This should be set to be non-nullable when all referencing columns are non-nullable. But in fact, it used to set it to be non-nullable if *any* referencing column is non-nullable, which is only correct in Postgres when `MATCH FULL` is set (a flag we don't consider). This fixes that by changing a boolean conjunction to a disjunction.
2. The "reverse" object relationship from a referenced table to a referencing table which has the foreign key constraint. This should always be set to be nullable. But in fact, it used to always be set to non-nullable, as was reported in hasura/graphql-engine#7201. This fixes that.
Moreover, we have moved the computation of the nullability from `Hasura.RQL.DDL.Relationship` to `Hasura.GraphQL.Schema.Select`: this nullability used to be passed through the `riIsNullable` field of `RelInfo`, but for array relationships this information is not actually used, and moreover the remaining fields of `RelInfo` are already enough to deduce the nullability.
This also adds regression tests for both (1) and (2) above.
https://github.com/hasura/graphql-engine-mono/pull/2159
GitOrigin-RevId: 617f12765614f49746d18d3368f41dfae2f3e6ca
2021-08-26 18:26:43 +03:00
|
|
|
pure (RelInfo rn ObjRel (rmColumns rm) refqt True io, dependencies)
|
2021-05-21 05:46:58 +03:00
|
|
|
RUFKeyOn (SameTable columns) -> do
|
2022-04-26 18:12:47 +03:00
|
|
|
foreignTableForeignKeys <-
|
|
|
|
Map.lookup qt foreignKeys
|
|
|
|
`onNothing` throw400 NotFound ("table " <> qt <<> " does not exist in source: " <> sourceNameToText source)
|
|
|
|
ForeignKey constraint foreignTable colMap <- getRequiredFkey columns (Set.toList foreignTableForeignKeys)
|
2019-11-20 21:21:30 +03:00
|
|
|
let dependencies =
|
2021-03-15 16:02:58 +03:00
|
|
|
[ SchemaDependency
|
2021-09-24 01:56:37 +03:00
|
|
|
( SOSourceObj source $
|
|
|
|
AB.mkAnyBackend $
|
|
|
|
SOITableObj @b qt $
|
|
|
|
TOForeignKey @b (_cName constraint)
|
|
|
|
)
|
|
|
|
DRFkey,
|
|
|
|
-- this needs to be added explicitly to handle the remote table being untracked. In this case,
|
|
|
|
-- neither the using_col nor the constraint name will help.
|
|
|
|
SchemaDependency
|
|
|
|
( SOSourceObj source $
|
|
|
|
AB.mkAnyBackend $
|
|
|
|
SOITable @b foreignTable
|
|
|
|
)
|
2021-03-15 16:02:58 +03:00
|
|
|
DRRemoteTable
|
2021-09-24 01:56:37 +03:00
|
|
|
]
|
|
|
|
<> fmap (drUsingColumnDep @b source qt) (toList columns)
|
2022-05-10 18:43:24 +03:00
|
|
|
pure (RelInfo rn ObjRel (NEHashMap.toHashMap colMap) foreignTable False BeforeParent, dependencies)
|
2021-05-21 05:46:58 +03:00
|
|
|
RUFKeyOn (RemoteTable remoteTable remoteCols) ->
|
|
|
|
mkFkeyRel ObjRel AfterParent source rn qt remoteTable remoteCols foreignKeys
|
2019-11-20 21:21:30 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
arrRelP2Setup ::
|
|
|
|
forall b m.
|
|
|
|
(QErrM m, Backend b) =>
|
|
|
|
HashMap (TableName b) (HashSet (ForeignKey b)) ->
|
|
|
|
SourceName ->
|
|
|
|
TableName b ->
|
|
|
|
ArrRelDef b ->
|
|
|
|
m (RelInfo b, [SchemaDependency])
|
2020-12-28 15:56:00 +03:00
|
|
|
arrRelP2Setup foreignKeys source qt (RelDef rn ru _) = case ru of
|
2020-01-14 10:09:10 +03:00
|
|
|
RUManual rm -> do
|
2019-11-20 21:21:30 +03:00
|
|
|
let refqt = rmTable rm
|
2022-04-26 18:12:47 +03:00
|
|
|
(lCols, rCols) = unzip $ Map.toList $ rmColumns rm
|
2021-09-24 01:56:37 +03:00
|
|
|
deps =
|
|
|
|
map
|
|
|
|
( \c ->
|
|
|
|
SchemaDependency
|
|
|
|
( SOSourceObj source $
|
|
|
|
AB.mkAnyBackend $
|
|
|
|
SOITableObj @b qt $
|
|
|
|
TOCol @b c
|
|
|
|
)
|
|
|
|
DRLeftColumn
|
|
|
|
)
|
|
|
|
lCols
|
|
|
|
<> map
|
|
|
|
( \c ->
|
|
|
|
SchemaDependency
|
|
|
|
( SOSourceObj source $
|
|
|
|
AB.mkAnyBackend $
|
|
|
|
SOITableObj @b refqt $
|
|
|
|
TOCol @b c
|
|
|
|
)
|
|
|
|
DRRightColumn
|
|
|
|
)
|
|
|
|
rCols
|
|
|
|
pure (RelInfo rn ArrRel (rmColumns rm) refqt True AfterParent, deps)
|
2021-05-21 05:46:58 +03:00
|
|
|
RUFKeyOn (ArrRelUsingFKeyOn refqt refCols) ->
|
|
|
|
mkFkeyRel ArrRel AfterParent source rn qt refqt refCols foreignKeys
|
2021-04-27 16:44:51 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
mkFkeyRel ::
|
|
|
|
forall b m.
|
|
|
|
QErrM m =>
|
|
|
|
Backend b =>
|
|
|
|
RelType ->
|
|
|
|
InsertOrder ->
|
|
|
|
SourceName ->
|
|
|
|
RelName ->
|
|
|
|
TableName b ->
|
|
|
|
TableName b ->
|
|
|
|
NonEmpty (Column b) ->
|
|
|
|
HashMap (TableName b) (HashSet (ForeignKey b)) ->
|
|
|
|
m (RelInfo b, [SchemaDependency])
|
2021-05-21 05:46:58 +03:00
|
|
|
mkFkeyRel relType io source rn sourceTable remoteTable remoteColumns foreignKeys = do
|
2022-04-26 18:12:47 +03:00
|
|
|
foreignTableForeignKeys <-
|
|
|
|
Map.lookup remoteTable foreignKeys
|
|
|
|
`onNothing` throw400 NotFound ("table " <> remoteTable <<> " does not exist in source: " <> sourceNameToText source)
|
|
|
|
let keysThatReferenceUs = filter ((== sourceTable) . _fkForeignTable) (Set.toList foreignTableForeignKeys)
|
2021-09-24 01:56:37 +03:00
|
|
|
ForeignKey constraint _foreignTable colMap <- getRequiredFkey remoteColumns keysThatReferenceUs
|
|
|
|
let dependencies =
|
|
|
|
[ SchemaDependency
|
|
|
|
( SOSourceObj source $
|
|
|
|
AB.mkAnyBackend $
|
|
|
|
SOITableObj @b remoteTable $
|
|
|
|
TOForeignKey @b (_cName constraint)
|
|
|
|
)
|
|
|
|
DRRemoteFkey,
|
|
|
|
SchemaDependency
|
|
|
|
( SOSourceObj source $
|
|
|
|
AB.mkAnyBackend $
|
|
|
|
SOITable @b remoteTable
|
|
|
|
)
|
|
|
|
DRRemoteTable
|
|
|
|
]
|
|
|
|
<> fmap (drUsingColumnDep @b source remoteTable) (toList remoteColumns)
|
2022-05-10 18:43:24 +03:00
|
|
|
pure (RelInfo rn relType (reverseMap (NEHashMap.toHashMap colMap)) remoteTable False io, dependencies)
|
2021-04-27 16:44:51 +03:00
|
|
|
where
|
2022-04-26 18:12:47 +03:00
|
|
|
reverseMap :: Eq y => Hashable y => HashMap x y -> HashMap y x
|
|
|
|
reverseMap = Map.fromList . fmap swap . Map.toList
|
2019-11-20 21:21:30 +03:00
|
|
|
|
server: fix the nullability of object relationships (fix hasura/graphql-engine#7201)
When adding object relationships, we set the nullability of the generated GraphQL field based on whether the database backend enforces that the referenced data always exists. For manual relationships (corresponding to `manual_configuration`), the database backend is unaware of any relationship between data, and hence such fields are always set to be nullable.
For relationships generated from foreign key constraints (corresponding to `foreign_key_constraint_on`), we distinguish between two cases:
1. The "forward" object relationship from a referencing table (i.e. which has the foreign key constraint) to a referenced table. This should be set to be non-nullable when all referencing columns are non-nullable. But in fact, it used to set it to be non-nullable if *any* referencing column is non-nullable, which is only correct in Postgres when `MATCH FULL` is set (a flag we don't consider). This fixes that by changing a boolean conjunction to a disjunction.
2. The "reverse" object relationship from a referenced table to a referencing table which has the foreign key constraint. This should always be set to be nullable. But in fact, it used to always be set to non-nullable, as was reported in hasura/graphql-engine#7201. This fixes that.
Moreover, we have moved the computation of the nullability from `Hasura.RQL.DDL.Relationship` to `Hasura.GraphQL.Schema.Select`: this nullability used to be passed through the `riIsNullable` field of `RelInfo`, but for array relationships this information is not actually used, and moreover the remaining fields of `RelInfo` are already enough to deduce the nullability.
This also adds regression tests for both (1) and (2) above.
https://github.com/hasura/graphql-engine-mono/pull/2159
GitOrigin-RevId: 617f12765614f49746d18d3368f41dfae2f3e6ca
2021-08-26 18:26:43 +03:00
|
|
|
-- | Try to find a foreign key constraint, identifying a constraint by its set of columns
|
2021-09-24 01:56:37 +03:00
|
|
|
getRequiredFkey ::
|
|
|
|
(QErrM m, Backend b) =>
|
|
|
|
NonEmpty (Column b) ->
|
|
|
|
[ForeignKey b] ->
|
|
|
|
m (ForeignKey b)
|
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
|
|
|
getRequiredFkey cols fkeys =
|
|
|
|
case filteredFkeys of
|
|
|
|
[k] -> return k
|
2021-09-24 01:56:37 +03:00
|
|
|
[] -> throw400 ConstraintError "no foreign constraint exists on the given column(s)"
|
|
|
|
_ -> throw400 ConstraintError "more than one foreign key constraint exists on the given column(s)"
|
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
|
|
|
where
|
2022-05-10 18:43:24 +03:00
|
|
|
filteredFkeys = filter ((== Set.fromList (toList cols)) . Map.keysSet . NEHashMap.toHashMap . _fkColumnMapping) fkeys
|
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-09-24 01:56:37 +03:00
|
|
|
drUsingColumnDep ::
|
|
|
|
forall b.
|
|
|
|
Backend b =>
|
|
|
|
SourceName ->
|
|
|
|
TableName b ->
|
|
|
|
Column b ->
|
|
|
|
SchemaDependency
|
2021-05-21 05:46:58 +03:00
|
|
|
drUsingColumnDep source qt col =
|
|
|
|
SchemaDependency
|
2021-09-24 01:56:37 +03:00
|
|
|
( SOSourceObj source $
|
|
|
|
AB.mkAnyBackend $
|
|
|
|
SOITableObj @b qt $
|
|
|
|
TOCol @b col
|
|
|
|
)
|
|
|
|
DRUsingColumn
|
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
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- Drop local relationship
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
data DropRel b = DropRel
|
|
|
|
{ _drSource :: !SourceName,
|
|
|
|
_drTable :: !(TableName b),
|
|
|
|
_drRelationship :: !RelName,
|
|
|
|
_drCascade :: !Bool
|
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 (DropRel b) where
|
2021-09-20 22:49:33 +03:00
|
|
|
parseJSON = withObject "DropRel" $ \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
|
|
|
DropRel
|
|
|
|
<$> o .:? "source" .!= defaultSource
|
|
|
|
<*> o .: "table"
|
|
|
|
<*> o .: "relationship"
|
|
|
|
<*> o .:? "cascade" .!= False
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
runDropRel ::
|
|
|
|
forall b m.
|
|
|
|
(MonadError QErr m, CacheRWM m, MetadataM m, BackendMetadata b) =>
|
|
|
|
DropRel 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
|
|
|
runDropRel (DropRel source qt rn cascade) = do
|
|
|
|
depObjs <- collectDependencies
|
|
|
|
withNewInconsistentObjsCheck do
|
|
|
|
metadataModifiers <- traverse purgeRelDep depObjs
|
2021-09-24 01:56:37 +03:00
|
|
|
buildSchemaCache $
|
|
|
|
MetadataModifier $
|
|
|
|
tableMetadataSetter @b source qt
|
|
|
|
%~ dropRelationshipInMetadata rn . foldr (.) id metadataModifiers
|
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
|
|
|
pure successMsg
|
|
|
|
where
|
|
|
|
collectDependencies = do
|
|
|
|
tabInfo <- askTableCoreInfo @b source qt
|
|
|
|
void $ askRelType (_tciFieldInfoMap tabInfo) rn ""
|
2021-09-24 01:56:37 +03:00
|
|
|
sc <- askSchemaCache
|
|
|
|
let depObjs =
|
|
|
|
getDependentObjs
|
|
|
|
sc
|
|
|
|
( SOSourceObj source $
|
|
|
|
AB.mkAnyBackend $
|
|
|
|
SOITableObj @b qt $
|
|
|
|
TORel rn
|
|
|
|
)
|
2022-05-27 15:27:18 +03:00
|
|
|
when (not (null depObjs) && not cascade) $ reportDependentObjectsExist depObjs
|
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
|
|
|
pure depObjs
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
purgeRelDep ::
|
|
|
|
forall b m.
|
|
|
|
QErrM m =>
|
|
|
|
Backend b =>
|
|
|
|
SchemaObjId ->
|
|
|
|
m (TableMetadata b -> TableMetadata b)
|
2021-03-15 16:02:58 +03:00
|
|
|
purgeRelDep (SOSourceObj _ exists)
|
|
|
|
| Just (SOITableObj _ (TOPerm rn pt)) <- AB.unpackAnyBackend @b exists =
|
2021-09-24 01:56:37 +03:00
|
|
|
pure $ dropPermissionInMetadata rn pt
|
|
|
|
purgeRelDep d =
|
|
|
|
throw500 $
|
|
|
|
"unexpected dependency of relationship : "
|
|
|
|
<> reportSchemaObj d
|
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
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- Set local relationship comment
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
data SetRelComment b = SetRelComment
|
|
|
|
{ arSource :: !SourceName,
|
|
|
|
arTable :: !(TableName b),
|
|
|
|
arRelationship :: !RelName,
|
|
|
|
arComment :: !(Maybe Text)
|
|
|
|
}
|
|
|
|
deriving (Generic)
|
|
|
|
|
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
|
|
|
deriving instance (Backend b) => Show (SetRelComment b)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
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
|
|
|
deriving instance (Backend b) => Eq (SetRelComment b)
|
|
|
|
|
|
|
|
instance (Backend b) => FromJSON (SetRelComment b) where
|
2021-09-20 22:49:33 +03:00
|
|
|
parseJSON = withObject "SetRelComment" $ \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
|
|
|
SetRelComment
|
|
|
|
<$> o .:? "source" .!= defaultSource
|
|
|
|
<*> o .: "table"
|
|
|
|
<*> o .: "relationship"
|
|
|
|
<*> o .:? "comment"
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
runSetRelComment ::
|
|
|
|
forall m b.
|
|
|
|
(CacheRWM m, MonadError QErr m, MetadataM m, BackendMetadata b) =>
|
|
|
|
SetRelComment b ->
|
|
|
|
m EncJSON
|
2018-12-13 10:26:15 +03:00
|
|
|
runSetRelComment defn = do
|
2021-04-22 00:44:37 +03:00
|
|
|
tabInfo <- askTableCoreInfo @b source qt
|
2020-12-08 17:22:31 +03:00
|
|
|
relType <- riType <$> askRelType (_tciFieldInfoMap tabInfo) rn ""
|
2021-09-24 01:56:37 +03:00
|
|
|
let metadataObj =
|
|
|
|
MOSourceObjId source $
|
|
|
|
AB.mkAnyBackend $
|
|
|
|
SMOTableObj @b qt $
|
|
|
|
MTORel rn relType
|
|
|
|
buildSchemaCacheFor metadataObj $
|
|
|
|
MetadataModifier $
|
|
|
|
tableMetadataSetter @b source qt %~ case relType of
|
|
|
|
ObjRel -> tmObjectRelationships . ix rn . rdComment .~ comment
|
|
|
|
ArrRel -> tmArrayRelationships . ix rn . rdComment .~ comment
|
2020-12-08 17:22:31 +03:00
|
|
|
pure successMsg
|
2019-03-01 12:17:22 +03:00
|
|
|
where
|
2020-12-28 15:56:00 +03:00
|
|
|
SetRelComment source qt rn comment = defn
|