graphql-engine/server/src-lib/Hasura/GraphQL/Schema/SubscriptionStream.hs
David Overton e5f88d8039 Nested array support for Data Connectors Backend and MongoDB
## 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
2023-05-24 08:02:43 +00:00

280 lines
11 KiB
Haskell

{-# LANGUAGE ApplicativeDo #-}
{-# LANGUAGE TemplateHaskellQuotes #-}
-- | Generate the GraphQL schema types related to streaming subscriptions.
module Hasura.GraphQL.Schema.SubscriptionStream
( selectStreamTable,
)
where
import Control.Lens ((^?))
import Control.Monad.Memoize
import Data.Has
import Data.List.NonEmpty qualified as NE
import Data.Text.Casing (GQLNameIdentifier)
import Data.Text.Extended ((<>>))
import Hasura.GraphQL.Parser.Class
import Hasura.GraphQL.Schema.Backend
import Hasura.GraphQL.Schema.BoolExp (AggregationPredicatesSchema)
import Hasura.GraphQL.Schema.Common
import Hasura.GraphQL.Schema.Parser
( InputFieldsParser,
Kind (..),
Parser,
)
import Hasura.GraphQL.Schema.Parser qualified as P
import Hasura.GraphQL.Schema.Select (tablePermissionsInfo, tableSelectionList, tableWhereArg)
import Hasura.GraphQL.Schema.Table (getTableGQLName, getTableIdentifierName, tableSelectColumns, tableSelectPermissions)
import Hasura.GraphQL.Schema.Typename
import Hasura.Name qualified as Name
import Hasura.Prelude
import Hasura.RQL.IR.Select qualified as IR
import Hasura.RQL.IR.Value qualified as IR
import Hasura.RQL.Types.Column
import Hasura.RQL.Types.Metadata.Object
import Hasura.RQL.Types.NamingCase
import Hasura.RQL.Types.Schema.Options qualified as Options
import Hasura.RQL.Types.SchemaCache
import Hasura.RQL.Types.Source
import Hasura.RQL.Types.SourceCustomization
import Hasura.RQL.Types.Subscription
import Hasura.SQL.AnyBackend qualified as AB
import Hasura.Table.Cache
import Language.GraphQL.Draft.Syntax qualified as G
-- | Argument to limit the maximum number of results returned in a single batch.
cursorBatchSizeArg ::
forall n.
(MonadParse n) =>
NamingCase ->
InputFieldsParser n Int
cursorBatchSizeArg tCase =
fromIntegral
<$> P.field batchSizeName batchSizeDesc P.nonNegativeInt
where
batchSizeName = applyFieldNameCaseCust tCase Name._batch_size
batchSizeDesc = Just $ G.Description "maximum number of rows returned in a single batch"
-- | Cursor ordering enum fields
--
-- > enum cursor_ordering {
-- > ASC
-- > DESC
-- > }
cursorOrderingArgParser ::
forall b r m n.
(MonadBuildSourceSchema b r m n) =>
SchemaT r m (Parser 'Both n CursorOrdering)
cursorOrderingArgParser = do
sourceInfo :: SourceInfo b <- asks getter
let customization = _siCustomization sourceInfo
tCase = _rscNamingConvention customization
enumName = runMkTypename (_rscTypeNames customization) $ applyTypeNameCaseCust tCase Name._cursor_ordering
let description =
Just $
G.Description $
"ordering argument of a cursor"
pure $
P.enum enumName description $
NE.fromList -- It's fine to use fromList here because we know the list is never empty.
[ ( define enumNameVal,
snd enumNameVal
)
| enumNameVal <- [(Name._ASC, COAscending), (Name._DESC, CODescending)]
]
where
define (name, val) =
let orderingTypeDesc = bool "descending" "ascending" $ val == COAscending
in P.Definition name (Just $ G.Description $ orderingTypeDesc <> " ordering of the cursor") Nothing [] P.EnumValueInfo
-- | Argument to specify the ordering of the cursor.
-- > ordering: cursor_ordering
cursorOrderingArg ::
forall b r m n.
(MonadBuildSourceSchema b r m n) =>
SchemaT r m (InputFieldsParser n (Maybe CursorOrdering))
cursorOrderingArg = do
cursorOrderingParser' <- cursorOrderingArgParser @b
pure $ P.fieldOptional Name._ordering (Just $ G.Description "cursor ordering") cursorOrderingParser'
-- | Input fields parser to parse the value of a table's column
-- > column_name: column_type
streamColumnParserArg ::
forall b n m r.
(MonadBuildSchema b r m n) =>
ColumnInfo b ->
SchemaT r m (InputFieldsParser n (Maybe (ColumnInfo b, ColumnValue b)))
streamColumnParserArg colInfo = do
fieldParser <- typedParser colInfo
let fieldName = ciName colInfo
fieldDesc = ciDescription colInfo
pure do
P.fieldOptional fieldName fieldDesc fieldParser <&> fmap (colInfo,)
where
typedParser columnInfo = do
fmap IR.openValueOrigin <$> columnParser (ciType columnInfo) (G.Nullability $ ciIsNullable columnInfo)
-- | Input object parser whose keys are the column names and the values are the
-- initial values of those columns from where the streaming should start.
-- > input table_stream_cursor_value_input {
-- > col1: col1_type
-- > col2: col2_type
-- ...
-- > }
streamColumnValueParser ::
forall b r m n.
(MonadBuildSchema b r m n) =>
GQLNameIdentifier ->
[ColumnInfo b] ->
SchemaT r m (Parser 'Input n [(ColumnInfo b, ColumnValue b)])
streamColumnValueParser tableGQLIdentifier colInfos = do
sourceInfo :: SourceInfo b <- asks getter
let sourceName = _siName sourceInfo
customization = _siCustomization sourceInfo
tCase = _rscNamingConvention customization
mkTypename = runMkTypename $ _rscTypeNames customization
objName = mkTypename $ applyTypeNameCaseIdentifier tCase $ mkStreamCursorValueInputTypeName tableGQLIdentifier
description = G.Description $ "Initial value of the column from where the streaming should start"
memoizeOn 'streamColumnValueParser (sourceName, tableGQLIdentifier) $ do
columnVals <- sequenceA <$> traverse streamColumnParserArg colInfos
pure $ P.object objName (Just description) columnVals <&> catMaybes
-- | Argument to accept the initial value from where the streaming should start.
-- > initial_value: table_stream_cursor_value_input!
streamColumnValueParserArg ::
forall b r m n.
(MonadBuildSchema b r m n) =>
GQLNameIdentifier ->
[ColumnInfo b] ->
SchemaT r m (InputFieldsParser n [(ColumnInfo b, ColumnValue b)])
streamColumnValueParserArg tableGQLIdentifier colInfos = do
tCase <- retrieve $ _rscNamingConvention . _siCustomization @b
columnValueParser <- streamColumnValueParser tableGQLIdentifier colInfos
pure do
P.field (applyFieldNameCaseCust tCase Name._initial_value) (Just $ G.Description "Stream column input with initial value") columnValueParser
-- | Argument to accept the cursor data. At the time of writing this, only a single
-- column cursor is supported and if multiple column cursors are provided,
-- then a parse error is thrown.
-- >
tableStreamColumnArg ::
forall b r m n.
(MonadBuildSchema b r m n) =>
GQLNameIdentifier ->
[ColumnInfo b] ->
SchemaT r m (InputFieldsParser n [IR.StreamCursorItem b])
tableStreamColumnArg tableGQLIdentifier colInfos = do
cursorOrderingParser <- cursorOrderingArg @b
streamColumnParser <- streamColumnValueParserArg tableGQLIdentifier colInfos
pure $ do
orderingArg <- cursorOrderingParser
columnArg <- streamColumnParser
pure $ (uncurry (IR.StreamCursorItem (fromMaybe COAscending orderingArg))) <$> columnArg
-- | Input object that contains the initial value of a column
-- along with how it needs to be ordered.
-- > input table_stream_cursor_input {
-- > initial_value: table_stream_cursor_value_input!
-- > ordering: cursor_ordering
-- > }
tableStreamCursorExp ::
forall m n r b.
(MonadBuildSchema b r m n) =>
TableInfo b ->
SchemaT r m (Parser 'Input n [(IR.StreamCursorItem b)])
tableStreamCursorExp tableInfo = do
sourceInfo :: SourceInfo b <- asks getter
let sourceName = _siName sourceInfo
tableName = tableInfoName tableInfo
customization = _siCustomization sourceInfo
tCase = _rscNamingConvention customization
mkTypename = runMkTypename $ _rscTypeNames customization
memoizeOn 'tableStreamCursorExp (sourceName, tableName) $ do
tableGQLName <- getTableGQLName tableInfo
tableGQLIdentifier <- getTableIdentifierName tableInfo
columnInfos <- mapMaybe (^? _SCIScalarColumn) <$> tableSelectColumns tableInfo
let objName = mkTypename $ applyTypeNameCaseIdentifier tCase $ mkStreamCursorInputTypeName tableGQLIdentifier
description = G.Description $ "Streaming cursor of the table " <>> tableGQLName
columnParsers <- tableStreamColumnArg tableGQLIdentifier columnInfos
pure $ P.object objName (Just description) columnParsers
-- | Argument to accept the cursor input object.
-- > cursor: [table_stream_cursor_input]!
tableStreamCursorArg ::
forall b r m n.
(MonadBuildSchema b r m n) =>
TableInfo b ->
SchemaT r m (InputFieldsParser n [IR.StreamCursorItem b])
tableStreamCursorArg tableInfo = do
cursorParser <- tableStreamCursorExp tableInfo
pure $ do
cursorArgs <-
P.field cursorName cursorDesc $ P.list $ P.nullable cursorParser
pure $ concat $ catMaybes cursorArgs
where
cursorName = Name._cursor
cursorDesc = Just $ G.Description "cursor to stream the results returned by the query"
-- | Arguments to the streaming subscription field.
-- > table_stream (cursor: [table_stream_cursor_input]!, batch_size: Int!, where: table_bool_exp)
tableStreamArguments ::
forall b r m n.
( AggregationPredicatesSchema b,
MonadBuildSchema b r m n
) =>
TableInfo b ->
SchemaT r m (InputFieldsParser n (SelectStreamArgs b))
tableStreamArguments tableInfo = do
tCase <- retrieve $ _rscNamingConvention . _siCustomization @b
whereParser <- tableWhereArg tableInfo
cursorParser <- tableStreamCursorArg tableInfo
pure $ do
whereArg <- whereParser
cursorArg <-
cursorParser `P.bindFields` \case
[] -> parseError "one streaming column field is expected"
[c] -> pure c
_ -> parseError "multiple column cursors are not supported yet"
batchSizeArg <- cursorBatchSizeArg tCase
pure $
IR.SelectStreamArgsG whereArg batchSizeArg cursorArg
-- | Field parser for a streaming subscription for a table.
selectStreamTable ::
forall b r m n.
( MonadBuildSchema b r m n,
AggregationPredicatesSchema b,
BackendTableSelectSchema b
) =>
-- | table info
TableInfo b ->
-- | field display name
G.Name ->
-- | field description, if any
Maybe G.Description ->
SchemaT r m (Maybe (P.FieldParser n (StreamSelectExp b)))
selectStreamTable tableInfo fieldName description = runMaybeT $ do
sourceInfo :: SourceInfo b <- asks getter
let sourceName = _siName sourceInfo
tableName = tableInfoName tableInfo
roleName <- retrieve scRole
selectPermissions <- hoistMaybe $ tableSelectPermissions roleName tableInfo
xStreamSubscription <- hoistMaybe $ streamSubscriptionExtension @b
stringifyNumbers <- retrieve Options.soStringifyNumbers
tableStreamArgsParser <- lift $ tableStreamArguments tableInfo
selectionSetParser <- MaybeT $ tableSelectionList tableInfo
lift $
memoizeOn 'selectStreamTable (sourceName, tableName, fieldName) $ do
pure $
P.setFieldParserOrigin (MOSourceObjId sourceName (AB.mkAnyBackend $ SMOTable @b tableName)) $
P.subselection fieldName description tableStreamArgsParser selectionSetParser
<&> \(args, fields) ->
IR.AnnSelectStreamG
{ IR._assnXStreamingSubscription = xStreamSubscription,
IR._assnFields = fields,
IR._assnFrom = IR.FromTable tableName,
IR._assnPerm = tablePermissionsInfo selectPermissions,
IR._assnArgs = args,
IR._assnStrfyNum = stringifyNumbers
}