mirror of
https://github.com/hasura/graphql-engine.git
synced 2024-12-17 04:24:35 +03:00
e5f88d8039
## Description This change adds support for querying into nested arrays in Data Connector agents that support such a concept (currently MongoDB). ### DC API changes - New API type `ColumnType` which allows representing the type of a "column" as either a scalar type, an object reference or an array of `ColumnType`s. This recursive definition allows arbitrary nesting of arrays of types. - The `type` fields in the API types `ColumnInfo` and `ColumnInsertSchema` now take a `ColumnType` instead of a `ScalarType`. - To ensure backwards compatibility, a `ColumnType` representing a scalar serialises and deserialises to the same representation as `ScalarType`. - In queries, the `Field` type now has a new constructor `NestedArrayField`. This contains a nested `Field` along with optional `limit`, `offset`, `where` and `order_by` arguments. (These optional arguments are not yet used by either HGE or the MongoDB agent.) ### MongoDB Haskell agent changes - The `/schema` endpoint will now recognise arrays within the JSON validation schema and generate corresponding arrays in the DC schema. - The `/query` endpoint will now handle `NestedArrayField`s within queries (although it does not yet handle `limit`, `offset`, `where` and `order_by`). ### HGE server changes - The `Backend` type class adds a new type family `XNestedArrays b` to enable nested arrays on a per-backend basis (currently enabled only for the `DataConnector` backend. - Within `RawColumnInfo` the column type is now represented by a new type `RawColumnType b` which mirrors the shape of the DC API `ColumnType`, but uses `XNestedObjects b` and `XNestedArrays b` type families to allow turning nested object and array supports on or off for a particular backend. In the `DataConnector` backend `API.CustomType` is converted into `RawColumnInfo 'DataConnector` while building the schema. - In the next stage of schema building, the `RawColumnInfo` is converted into a `StructuredColumnInfo` which allows us to represent the three different types of columns: scalar, object and array. TODO: the `StructuredColumnInfo` looks very similar to the Logical Model types. The main difference is that it uses the `XNestedObjects` and `XNestedArrays` type families. We should be able to combine these two representations. - The `StructuredColumnInfo` is then placed into a `FIColumn` `FieldInfo`. This involved some refactoring of `FieldInfo` as I had previously split out `FINestedObject` into a separate constructor. However it works out better to represent all "column" fields (i.e. scalar, object and array) using `FIColumn` as this make it easier to implement permission checking correctly. This is the reason the `StructuredColumnInfo` was needed. - Next, the `FieldInfo` are used to generate `FieldParser`s. We add a new constructor to `AnnFieldG` for `AFNestedArray`. An `AFNestedArray` field parser can contain either a simple array selection or an array aggregate. Simple array `FieldParsers` are currently limited to subfield selection. We will add support for limit, offset, where and order_by in a future PR. We also don't yet generate array aggregate `FieldParsers. - The new `AFNestedArray` field is handled by the `QueryPlan` module in the `DataConnector` backend. There we generate an `API.NestedArrayField` from the AFNestedArray. We also handle nested arrays when reshaping the response from the DC agent. ## Limitations - Support for limit, offset, filter (where) and order_by is not yet fully implemented, although it should not be hard to add this - Support for aggregations on nested arrays is not yet fully implemented - Permissions involving nested arrays (and objects) not yet implemented - This should be integrated with Logical Model types, but that will happen in a separate PR PR-URL: https://github.com/hasura/graphql-engine-mono/pull/9149 GitOrigin-RevId: 0e7b71a994fc1d2ca1ef73bfe7b96e95b5328531
128 lines
3.7 KiB
Haskell
128 lines
3.7 KiB
Haskell
module Hasura.RQL.DML.Delete
|
|
( validateDeleteQWith,
|
|
validateDeleteQ,
|
|
AnnDelG (..),
|
|
AnnDel,
|
|
execDeleteQuery,
|
|
runDelete,
|
|
)
|
|
where
|
|
|
|
import Control.Lens ((^?))
|
|
import Control.Monad.Trans.Control (MonadBaseControl)
|
|
import Data.Aeson
|
|
import Data.Sequence qualified as DS
|
|
import Database.PG.Query qualified as PG
|
|
import Hasura.Backends.Postgres.Connection
|
|
import Hasura.Backends.Postgres.Execute.Mutation
|
|
import Hasura.Backends.Postgres.SQL.DML qualified as S
|
|
import Hasura.Backends.Postgres.Translate.Returning
|
|
import Hasura.Backends.Postgres.Types.Table
|
|
import Hasura.Base.Error
|
|
import Hasura.EncJSON
|
|
import Hasura.Prelude
|
|
import Hasura.QueryTags
|
|
import Hasura.RQL.DML.Internal
|
|
import Hasura.RQL.DML.Types
|
|
import Hasura.RQL.IR.Delete
|
|
import Hasura.RQL.Types.BackendType
|
|
import Hasura.RQL.Types.Column
|
|
import Hasura.RQL.Types.Common
|
|
import Hasura.RQL.Types.Metadata
|
|
import Hasura.RQL.Types.SchemaCache
|
|
import Hasura.Session
|
|
import Hasura.Tracing qualified as Tracing
|
|
|
|
validateDeleteQWith ::
|
|
(UserInfoM m, QErrM m, TableInfoRM ('Postgres 'Vanilla) m) =>
|
|
SessionVariableBuilder m ->
|
|
(ColumnType ('Postgres 'Vanilla) -> Value -> m S.SQLExp) ->
|
|
DeleteQuery ->
|
|
m (AnnDel ('Postgres 'Vanilla))
|
|
validateDeleteQWith
|
|
sessVarBldr
|
|
prepValBldr
|
|
(DeleteQuery tableName _ rqlBE mRetCols) = do
|
|
tableInfo <- askTableInfoSource tableName
|
|
let coreInfo = _tiCoreInfo tableInfo
|
|
|
|
-- If table is view then check if it deletable
|
|
mutableView
|
|
tableName
|
|
viIsDeletable
|
|
(_tciViewInfo coreInfo)
|
|
"deletable"
|
|
|
|
-- Check if the role has delete permissions
|
|
delPerm <- askDelPermInfo tableInfo
|
|
|
|
-- Check if all dependent headers are present
|
|
validateHeaders $ dpiRequiredHeaders delPerm
|
|
|
|
-- Check if select is allowed
|
|
selPerm <-
|
|
modifyErr (<> selNecessaryMsg) $
|
|
askSelPermInfo tableInfo
|
|
|
|
let fieldInfoMap = _tciFieldInfoMap coreInfo
|
|
allCols = mapMaybe (^? _SCIScalarColumn) $ getCols fieldInfoMap
|
|
|
|
-- convert the returning cols into sql returing exp
|
|
mAnnRetCols <- forM mRetCols $ \retCols ->
|
|
withPathK "returning" $ checkRetCols fieldInfoMap selPerm retCols
|
|
|
|
-- convert the where clause
|
|
annSQLBoolExp <-
|
|
withPathK "where" $
|
|
convBoolExp fieldInfoMap selPerm rqlBE sessVarBldr fieldInfoMap (valueParserWithCollectableType prepValBldr)
|
|
|
|
resolvedDelFltr <-
|
|
convAnnBoolExpPartialSQL sessVarBldr $
|
|
dpiFilter delPerm
|
|
|
|
return $
|
|
AnnDel
|
|
tableName
|
|
(resolvedDelFltr, annSQLBoolExp)
|
|
(mkDefaultMutFlds mAnnRetCols)
|
|
allCols
|
|
Nothing
|
|
where
|
|
selNecessaryMsg =
|
|
"; \"delete\" is only allowed if the role "
|
|
<> "has \"select\" permission as \"where\" can't be used "
|
|
<> "without \"select\" permission on the table"
|
|
|
|
validateDeleteQ ::
|
|
(QErrM m, UserInfoM m, CacheRM m) =>
|
|
DeleteQuery ->
|
|
m (AnnDel ('Postgres 'Vanilla), DS.Seq PG.PrepArg)
|
|
validateDeleteQ query = do
|
|
let source = doSource query
|
|
tableCache :: TableCache ('Postgres 'Vanilla) <- fold <$> askTableCache source
|
|
flip runTableCacheRT tableCache $
|
|
runDMLP1T $
|
|
validateDeleteQWith sessVarFromCurrentSetting binRHSBuilder query
|
|
|
|
runDelete ::
|
|
forall m.
|
|
( QErrM m,
|
|
UserInfoM m,
|
|
CacheRM m,
|
|
MonadIO m,
|
|
Tracing.MonadTrace m,
|
|
MonadBaseControl IO m,
|
|
MetadataM m
|
|
) =>
|
|
SQLGenCtx ->
|
|
DeleteQuery ->
|
|
m EncJSON
|
|
runDelete sqlGen q = do
|
|
sourceConfig <- askSourceConfig @('Postgres 'Vanilla) (doSource q)
|
|
let strfyNum = stringifyNum sqlGen
|
|
userInfo <- askUserInfo
|
|
validateDeleteQ q
|
|
>>= runTxWithCtx (_pscExecCtx sourceConfig) (Tx PG.ReadWrite Nothing) LegacyRQLQuery
|
|
. flip runReaderT emptyQueryTagsComment
|
|
. execDeleteQuery strfyNum Nothing userInfo
|