graphql-engine/server/src-lib/Hasura/RQL/IR/Select.hs

743 lines
23 KiB
Haskell
Raw Normal View History

{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE UndecidableInstances #-}
-- | This modules defines the tree of Select types: how we represent a query internally, from its top
-- level 'QueryDB' down to each individual field. Most of those types have three type arguments:
--
-- b: BackendType
-- The backend that is targeted by that specific select (Postgres Vanilla, MSSQL...); we use the
-- type families in the Backend class to decide how different parts of the IR are represented in
-- different backends.
--
-- v: Type
-- The type of the leaf values in our AST; used almost exclusively for column values, over which
-- queries can be parameterized. The output of the parser phase will use @UnpreparedValue b@ for
-- the leaves, and most backends will then transform the AST to interpret those values and
-- consequently change @v@ to be @SQLExpression b@
--
-- r: BackendType -> Type
-- Joins across backends mean that the aforementioned @b@ parameter won't be the same throughout
-- the entire tree; at some point we will have an 'AnyBackend' used to encapsulate a branch that
-- uses a different @b@. We still want, however, to be able to parameterize the values of the
-- leaves in that separate branch, and that's what the @r@ parameter is for. We also use
-- 'UnpreparedValue' here during the parsing phase, meaning all leaf values will be
-- @UnpreparedValue b@ for their respective backend @b@, and most backends will then transform
-- their AST, cutting all such remote branches, and therefore using @Const Void@ for @r@.
module Hasura.RQL.IR.Select
( AggregateField (..),
AggregateFields,
AggregateOp (..),
AnnAggregateSelect,
AnnAggregateSelectG,
AnnColumnField (..),
AnnField,
AnnFieldG (..),
AnnFields,
AnnFieldsG,
Support nested object fields in DC API and use this to implement nest… ## Description This change adds support for nested object fields in HGE IR and Schema Cache, the Data Connectors backend and API, and the MongoDB agent. ### Data Connector API changes - The `/schema` endpoint response now includes an optional set of GraphQL type definitions. Table column types can refer to these definitions by name. - Queries can now include a new field type `object` which contains a column name and a nested query. This allows querying into a nested object within a field. ### MongoDB agent changes - Add support for querying into nested documents using the new `object` field type. ### HGE changes - The `Backend` type class has a new type family `XNestedObjects b` which controls whether or not a backend supports querying into nested objects. This is currently enabled only for the `DataConnector` backend. - For backends that support nested objects, the `FieldInfo` type gets a new constructor `FINestedObject`, and the `AnnFieldG` type gets a new constructor `AFNestedObject`. - If the DC `/schema` endpoint returns any custom GraphQL type definitions they are stored in the `TableInfo` for each table in the source. - During schema cache building, the function `addNonColumnFields` will check whether any column types match custom GraphQL object types stored in the `TableInfo`. If so, they are converted into `FINestedObject` instead of `FIColumn` in the `FieldInfoMap`. - When building the `FieldParser`s from `FieldInfo` (function `fieldSelection`) any `FINestedObject` fields are converted into nested object parsers returning `AFNestedObject`. - The `DataConnector` query planner converts `AFNestedObject` fields into `object` field types in the query sent to the agent. ## Limitations ### HGE not yet implemented: - Support for nested arrays - Support for nested objects/arrays in mutations - Support for nested objects/arrays in order-by - Support for filters (`where`) in nested objects/arrays - Support for adding custom GraphQL types via track table metadata API - Support for interface and union types - Tests for nested objects ### Mongo agent not yet implemented: - Generate nested object types from validation schema - Support for aggregates - Support for order-by - Configure agent port - Build agent in CI - Agent tests for nested objects and MongoDB agent PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7844 GitOrigin-RevId: aec9ec1e4216293286a68f9b1af6f3f5317db423
2023-04-11 04:29:05 +03:00
AnnNestedObjectSelectG (..),
AnnNestedObjectSelect,
AnnObjectSelect,
AnnObjectSelectG (..),
AnnSimpleSelect,
AnnSimpleSelectG,
AnnSimpleStreamSelect,
AnnSimpleStreamSelectG,
ArrayAggregateSelect,
ArrayAggregateSelectG,
ArrayConnectionSelect,
ArrayRelationSelectG,
ArraySelect,
ArraySelectFieldsG,
ArraySelectG (..),
ColFld (..),
ColumnFields,
ComputedFieldScalarSelect (..),
ComputedFieldSelect (..),
ConnectionField (..),
ConnectionFields,
ConnectionSelect (..),
ConnectionSlice (..),
ConnectionSplit (..),
ConnectionSplitKind (..),
EdgeField (..),
EdgeFields,
ObjectRelationSelect,
ObjectRelationSelectG,
PageInfoField (..),
PageInfoFields,
QueryDB (..),
RemoteSourceSelect (..),
RemoteRelationshipSelect (..),
SourceRelationshipSelection (..),
TableAggregateField,
TableAggregateFieldG (..),
TableAggregateFields,
TableAggregateFieldsG,
CountDistinct (..),
Support nested object fields in DC API and use this to implement nest… ## Description This change adds support for nested object fields in HGE IR and Schema Cache, the Data Connectors backend and API, and the MongoDB agent. ### Data Connector API changes - The `/schema` endpoint response now includes an optional set of GraphQL type definitions. Table column types can refer to these definitions by name. - Queries can now include a new field type `object` which contains a column name and a nested query. This allows querying into a nested object within a field. ### MongoDB agent changes - Add support for querying into nested documents using the new `object` field type. ### HGE changes - The `Backend` type class has a new type family `XNestedObjects b` which controls whether or not a backend supports querying into nested objects. This is currently enabled only for the `DataConnector` backend. - For backends that support nested objects, the `FieldInfo` type gets a new constructor `FINestedObject`, and the `AnnFieldG` type gets a new constructor `AFNestedObject`. - If the DC `/schema` endpoint returns any custom GraphQL type definitions they are stored in the `TableInfo` for each table in the source. - During schema cache building, the function `addNonColumnFields` will check whether any column types match custom GraphQL object types stored in the `TableInfo`. If so, they are converted into `FINestedObject` instead of `FIColumn` in the `FieldInfoMap`. - When building the `FieldParser`s from `FieldInfo` (function `fieldSelection`) any `FINestedObject` fields are converted into nested object parsers returning `AFNestedObject`. - The `DataConnector` query planner converts `AFNestedObject` fields into `object` field types in the query sent to the agent. ## Limitations ### HGE not yet implemented: - Support for nested arrays - Support for nested objects/arrays in mutations - Support for nested objects/arrays in order-by - Support for filters (`where`) in nested objects/arrays - Support for adding custom GraphQL types via track table metadata API - Support for interface and union types - Tests for nested objects ### Mongo agent not yet implemented: - Generate nested object types from validation schema - Support for aggregates - Support for order-by - Configure agent port - Build agent in CI - Agent tests for nested objects and MongoDB agent PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7844 GitOrigin-RevId: aec9ec1e4216293286a68f9b1af6f3f5317db423
2023-04-11 04:29:05 +03:00
anosSupportsNestedObjects,
anosColumn,
anosFields,
aosFields,
aosTableFrom,
aosTableFilter,
csXRelay,
csPrimaryKeyColumns,
csSplit,
csSlice,
csSelect,
insertFunctionArg,
mkAnnColumnField,
mkAnnColumnFieldAsText,
traverseSourceRelationshipSelection,
_AFArrayRelation,
_AFColumn,
_AFComputedField,
_AFExpression,
_AFNodeId,
_AFObjectRelation,
_AFRemote,
_TAFAgg,
_TAFNodes,
_TAFExp,
_ConnectionTypename,
_ConnectionPageInfo,
_ConnectionEdges,
_EdgeTypename,
_EdgeCursor,
_EdgeNode,
module Hasura.RQL.IR.Select.AnnSelectG,
module Hasura.RQL.IR.Select.Args,
module Hasura.RQL.IR.Select.From,
module Hasura.RQL.IR.Select.OrderBy,
module Hasura.RQL.IR.Select.TablePerm,
module Hasura.RQL.IR.Select.RelationSelect,
)
where
import Control.Lens.TH (makeLenses, makePrisms)
import Data.Bifoldable
import Data.HashMap.Strict qualified as HM
import Data.Kind (Type)
import Data.List.NonEmpty qualified as NE
import Data.Sequence qualified as Seq
import Hasura.Function.Cache
import Hasura.Prelude
import Hasura.RQL.IR.BoolExp
import Hasura.RQL.IR.OrderBy
import Hasura.RQL.IR.Select.AnnSelectG
import Hasura.RQL.IR.Select.Args
import Hasura.RQL.IR.Select.From
import Hasura.RQL.IR.Select.OrderBy
import Hasura.RQL.IR.Select.RelationSelect
import Hasura.RQL.IR.Select.TablePerm
import Hasura.RQL.Types.Backend
import Hasura.RQL.Types.Column
import Hasura.RQL.Types.Common
import Hasura.RQL.Types.ComputedField
import Hasura.RQL.Types.Instances ()
import Hasura.RQL.Types.Relationships.Remote
import Hasura.RQL.Types.Schema.Options (StringifyNumbers)
import Hasura.SQL.Backend
-- Root selection
2019-04-17 12:48:41 +03:00
data QueryDB (b :: BackendType) (r :: Type) v
= QDBMultipleRows (AnnSimpleSelectG b r v)
| QDBSingleRow (AnnSimpleSelectG b r v)
| QDBAggregation (AnnAggregateSelectG b r v)
| QDBConnection (ConnectionSelect b r v)
| QDBStreamMultipleRows (AnnSimpleStreamSelectG b r v)
deriving stock (Generic, Functor, Foldable, Traversable)
instance Backend b => Bifoldable (QueryDB b) where
bifoldMap f g = \case
QDBMultipleRows annSel -> bifoldMapAnnSelectG f g annSel
QDBSingleRow annSel -> bifoldMapAnnSelectG f g annSel
QDBAggregation annSel -> bifoldMapAnnSelectG f g annSel
QDBConnection connSel -> bifoldMap f g connSel
QDBStreamMultipleRows annSel -> bifoldMapAnnSelectStreamG f g annSel
-- Select
type AnnSimpleSelectG b r v = AnnSelectG b (AnnFieldG b r) v
type AnnAggregateSelectG b r v = AnnSelectG b (TableAggregateFieldG b r) v
type AnnSimpleStreamSelectG b r v = AnnSelectStreamG b (AnnFieldG b r) v
type AnnSimpleSelect b = AnnSimpleSelectG b Void (SQLExpression b)
type AnnAggregateSelect b = AnnAggregateSelectG b Void (SQLExpression b)
type AnnSimpleStreamSelect b = AnnSimpleStreamSelectG b Void (SQLExpression b)
-- Relay select
data ConnectionSelect (b :: BackendType) (r :: Type) v = ConnectionSelect
{ _csXRelay :: XRelay b,
_csPrimaryKeyColumns :: PrimaryKeyColumns b,
_csSplit :: Maybe (NE.NonEmpty (ConnectionSplit b v)),
_csSlice :: Maybe ConnectionSlice,
_csSelect :: (AnnSelectG b (ConnectionField b r) v)
}
deriving stock (Functor, Foldable, Traversable)
deriving stock instance
( Backend b,
Eq (AnnSelectG b (ConnectionField b r) v),
Eq (ConnectionSlice),
Eq (ConnectionSplit b v),
Eq (PrimaryKeyColumns b)
) =>
Eq (ConnectionSelect b r v)
deriving stock instance
( Backend b,
Show (AnnSelectG b (ConnectionField b r) v),
Show (ConnectionSlice),
Show (ConnectionSplit b v),
Show (PrimaryKeyColumns b)
) =>
Show (ConnectionSelect b r v)
instance Backend b => Bifoldable (ConnectionSelect b) where
bifoldMap f g ConnectionSelect {..} =
foldMap (foldMap $ foldMap g) _csSplit
<> bifoldMapAnnSelectG f g _csSelect
data ConnectionSplit (b :: BackendType) v = ConnectionSplit
{ _csKind :: ConnectionSplitKind,
_csValue :: v,
_csOrderBy :: (OrderByItemG b (AnnotatedOrderByElement b v))
}
deriving stock (Functor, Generic, Foldable, Traversable)
deriving stock instance
( Backend b,
Eq v,
Eq (OrderByItemG b (AnnotatedOrderByElement b v))
) =>
Eq (ConnectionSplit b v)
deriving stock instance
( Backend b,
Show v,
Show (OrderByItemG b (AnnotatedOrderByElement b v))
) =>
Show (ConnectionSplit b v)
instance
( Backend b,
Hashable v,
Hashable (OrderByItemG b (AnnotatedOrderByElement b v))
) =>
Hashable (ConnectionSplit b v)
data ConnectionSlice
= SliceFirst Int
| SliceLast Int
deriving stock (Show, Eq, Generic)
deriving anyclass (Hashable)
[Preview] Inherited roles for postgres read queries fixes #3868 docker image - `hasura/graphql-engine:inherited-roles-preview-48b73a2de` Note: To be able to use the inherited roles feature, the graphql-engine should be started with the env variable `HASURA_GRAPHQL_EXPERIMENTAL_FEATURES` set to `inherited_roles`. Introduction ------------ This PR implements the idea of multiple roles as presented in this [paper](https://www.microsoft.com/en-us/research/wp-content/uploads/2016/02/FGALanguageICDE07.pdf). The multiple roles feature in this PR can be used via inherited roles. An inherited role is a role which can be created by combining multiple singular roles. For example, if there are two roles `author` and `editor` configured in the graphql-engine, then we can create a inherited role with the name of `combined_author_editor` role which will combine the select permissions of the `author` and `editor` roles and then make GraphQL queries using the `combined_author_editor`. How are select permissions of different roles are combined? ------------------------------------------------------------ A select permission includes 5 things: 1. Columns accessible to the role 2. Row selection filter 3. Limit 4. Allow aggregation 5. Scalar computed fields accessible to the role Suppose there are two roles, `role1` gives access to the `address` column with row filter `P1` and `role2` gives access to both the `address` and the `phone` column with row filter `P2` and we create a new role `combined_roles` which combines `role1` and `role2`. Let's say the following GraphQL query is queried with the `combined_roles` role. ```graphql query { employees { address phone } } ``` This will translate to the following SQL query: ```sql select (case when (P1 or P2) then address else null end) as address, (case when P2 then phone else null end) as phone from employee where (P1 or P2) ``` The other parameters of the select permission will be combined in the following manner: 1. Limit - Minimum of the limits will be the limit of the inherited role 2. Allow aggregations - If any of the role allows aggregation, then the inherited role will allow aggregation 3. Scalar computed fields - same as table column fields, as in the above example APIs for inherited roles: ---------------------- 1. `add_inherited_role` `add_inherited_role` is the [metadata API](https://hasura.io/docs/1.0/graphql/core/api-reference/index.html#schema-metadata-api) to create a new inherited role. It accepts two arguments `role_name`: the name of the inherited role to be added (String) `role_set`: list of roles that need to be combined (Array of Strings) Example: ```json { "type": "add_inherited_role", "args": { "role_name":"combined_user", "role_set":[ "user", "user1" ] } } ``` After adding the inherited role, the inherited role can be used like single roles like earlier Note: An inherited role can only be created with non-inherited/singular roles. 2. `drop_inherited_role` The `drop_inherited_role` API accepts the name of the inherited role and drops it from the metadata. It accepts a single argument: `role_name`: name of the inherited role to be dropped Example: ```json { "type": "drop_inherited_role", "args": { "role_name":"combined_user" } } ``` Metadata --------- The derived roles metadata will be included under the `experimental_features` key while exporting the metadata. ```json { "experimental_features": { "derived_roles": [ { "role_name": "manager_is_employee_too", "role_set": [ "employee", "manager" ] } ] } } ``` Scope ------ Only postgres queries and subscriptions are supported in this PR. Important points: ----------------- 1. All columns exposed to an inherited role will be marked as `nullable`, this is done so that cell value nullification can be done. TODOs ------- - [ ] Tests - [ ] Test a GraphQL query running with a inherited role without enabling inherited roles in experimental features - [] Tests for aggregate queries, limit, computed fields, functions, subscriptions (?) - [ ] Introspection test with a inherited role (nullability changes in a inherited role) - [ ] Docs - [ ] Changelog Co-authored-by: Vamshi Surabhi <6562944+0x777@users.noreply.github.com> GitOrigin-RevId: 3b8ee1e11f5ceca80fe294f8c074d42fbccfec63
2021-03-08 14:14:13 +03:00
data ConnectionSplitKind
= CSKBefore
| CSKAfter
deriving stock (Show, Eq, Generic)
deriving anyclass (Hashable)
-- Fields
-- | captures a remote relationship's selection and the necessary context
data RemoteRelationshipSelect b r = RemoteRelationshipSelect
{ -- | The fields on the table that are required for the join condition
-- of the remote relationship
_rrsLHSJoinFields :: HashMap FieldName (DBJoinField b),
-- | The field that captures the relationship
-- r ~ (RemoteRelationshipField UnpreparedValue) when the AST is emitted by the parser.
-- r ~ Void when an execution tree is constructed so that a backend is
-- absolved of dealing with remote relationships.
_rrsRelationship :: r
}
deriving (Eq, Show, Functor, Foldable, Traversable)
data AnnFieldG (b :: BackendType) (r :: Type) v
= AFColumn (AnnColumnField b v)
| AFObjectRelation (ObjectRelationSelectG b r v)
| AFArrayRelation (ArraySelectG b r v)
Clean Relay's code, break schema cycles, introduce Node ID V2 ## Motivation This PR rewrites most of Relay to achieve the following: - ~~fix a bug in which the same node id could refer to two different tables in the schema~~ - remove one of the few remaining uses of the source cache in the schema building code In doing so, it also: - simplifies the `BackendSchema` class by removing `node` from it, - makes it much easier for other backends to support Relay, - documents, re-organizes, and clarifies the code. ## Description This PR introduces a new `NodeId` version ~~, and adapts the Postgres code to always generate this V2 version~~. This new id contains the source name, in addition to the table name, in order to disambiguate similar table names across different sources (which is now possible with source customization). In doing so, it now explicitly handles that case for V1 node ids, and returns an explicit error message instead of running the risk of _silently returning the wrong information_. Furthermore, it adapts `nodeField` to support multiple backends; most of the code was trivial to generalize, and as a result it lowers the cost of entry for other backends, that now only need to support `AFNodeId` in their translation layer. Finally, it removes one more cycle in the schema building code, by using the same trick we used for remote relationships instead of using the memoization trick of #4576. ## Remaining work - ~~[ ]write a Changelog entry~~ - ~~[x] adapt all tests that were asserting on an old node id~~ ## Future work This PR was adapted from its original form to avoid a breaking change: while it introduces a Node ID V2, we keep generating V1 IDs and the parser rejects V2 IDs. It will be easy to make the switch at a later data in a subsequent PR. PR-URL: https://github.com/hasura/graphql-engine-mono/pull/4593 GitOrigin-RevId: 88e5cb91e8b0646900547fa8c7c0e1463de267a1
2022-06-07 16:35:26 +03:00
| AFComputedField (XComputedField b) ComputedFieldName (ComputedFieldSelect b r v)
| -- | A remote relationship field
AFRemote (RemoteRelationshipSelect b r)
Clean Relay's code, break schema cycles, introduce Node ID V2 ## Motivation This PR rewrites most of Relay to achieve the following: - ~~fix a bug in which the same node id could refer to two different tables in the schema~~ - remove one of the few remaining uses of the source cache in the schema building code In doing so, it also: - simplifies the `BackendSchema` class by removing `node` from it, - makes it much easier for other backends to support Relay, - documents, re-organizes, and clarifies the code. ## Description This PR introduces a new `NodeId` version ~~, and adapts the Postgres code to always generate this V2 version~~. This new id contains the source name, in addition to the table name, in order to disambiguate similar table names across different sources (which is now possible with source customization). In doing so, it now explicitly handles that case for V1 node ids, and returns an explicit error message instead of running the risk of _silently returning the wrong information_. Furthermore, it adapts `nodeField` to support multiple backends; most of the code was trivial to generalize, and as a result it lowers the cost of entry for other backends, that now only need to support `AFNodeId` in their translation layer. Finally, it removes one more cycle in the schema building code, by using the same trick we used for remote relationships instead of using the memoization trick of #4576. ## Remaining work - ~~[ ]write a Changelog entry~~ - ~~[x] adapt all tests that were asserting on an old node id~~ ## Future work This PR was adapted from its original form to avoid a breaking change: while it introduces a Node ID V2, we keep generating V1 IDs and the parser rejects V2 IDs. It will be easy to make the switch at a later data in a subsequent PR. PR-URL: https://github.com/hasura/graphql-engine-mono/pull/4593 GitOrigin-RevId: 88e5cb91e8b0646900547fa8c7c0e1463de267a1
2022-06-07 16:35:26 +03:00
| AFNodeId (XRelay b) SourceName (TableName b) (PrimaryKeyColumns b)
| AFExpression Text
Support nested object fields in DC API and use this to implement nest… ## Description This change adds support for nested object fields in HGE IR and Schema Cache, the Data Connectors backend and API, and the MongoDB agent. ### Data Connector API changes - The `/schema` endpoint response now includes an optional set of GraphQL type definitions. Table column types can refer to these definitions by name. - Queries can now include a new field type `object` which contains a column name and a nested query. This allows querying into a nested object within a field. ### MongoDB agent changes - Add support for querying into nested documents using the new `object` field type. ### HGE changes - The `Backend` type class has a new type family `XNestedObjects b` which controls whether or not a backend supports querying into nested objects. This is currently enabled only for the `DataConnector` backend. - For backends that support nested objects, the `FieldInfo` type gets a new constructor `FINestedObject`, and the `AnnFieldG` type gets a new constructor `AFNestedObject`. - If the DC `/schema` endpoint returns any custom GraphQL type definitions they are stored in the `TableInfo` for each table in the source. - During schema cache building, the function `addNonColumnFields` will check whether any column types match custom GraphQL object types stored in the `TableInfo`. If so, they are converted into `FINestedObject` instead of `FIColumn` in the `FieldInfoMap`. - When building the `FieldParser`s from `FieldInfo` (function `fieldSelection`) any `FINestedObject` fields are converted into nested object parsers returning `AFNestedObject`. - The `DataConnector` query planner converts `AFNestedObject` fields into `object` field types in the query sent to the agent. ## Limitations ### HGE not yet implemented: - Support for nested arrays - Support for nested objects/arrays in mutations - Support for nested objects/arrays in order-by - Support for filters (`where`) in nested objects/arrays - Support for adding custom GraphQL types via track table metadata API - Support for interface and union types - Tests for nested objects ### Mongo agent not yet implemented: - Generate nested object types from validation schema - Support for aggregates - Support for order-by - Configure agent port - Build agent in CI - Agent tests for nested objects and MongoDB agent PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7844 GitOrigin-RevId: aec9ec1e4216293286a68f9b1af6f3f5317db423
2023-04-11 04:29:05 +03:00
| -- | Nested object.
AFNestedObject (AnnNestedObjectSelectG b r v)
-- TODO (dmoverton): add AFNestedArray
deriving stock (Functor, Foldable, Traversable)
deriving stock instance
( Backend b,
Eq (AnnColumnField b v),
Eq (ArraySelectG b r v),
Eq (ComputedFieldSelect b r v),
Eq (ObjectRelationSelectG b r v),
Support nested object fields in DC API and use this to implement nest… ## Description This change adds support for nested object fields in HGE IR and Schema Cache, the Data Connectors backend and API, and the MongoDB agent. ### Data Connector API changes - The `/schema` endpoint response now includes an optional set of GraphQL type definitions. Table column types can refer to these definitions by name. - Queries can now include a new field type `object` which contains a column name and a nested query. This allows querying into a nested object within a field. ### MongoDB agent changes - Add support for querying into nested documents using the new `object` field type. ### HGE changes - The `Backend` type class has a new type family `XNestedObjects b` which controls whether or not a backend supports querying into nested objects. This is currently enabled only for the `DataConnector` backend. - For backends that support nested objects, the `FieldInfo` type gets a new constructor `FINestedObject`, and the `AnnFieldG` type gets a new constructor `AFNestedObject`. - If the DC `/schema` endpoint returns any custom GraphQL type definitions they are stored in the `TableInfo` for each table in the source. - During schema cache building, the function `addNonColumnFields` will check whether any column types match custom GraphQL object types stored in the `TableInfo`. If so, they are converted into `FINestedObject` instead of `FIColumn` in the `FieldInfoMap`. - When building the `FieldParser`s from `FieldInfo` (function `fieldSelection`) any `FINestedObject` fields are converted into nested object parsers returning `AFNestedObject`. - The `DataConnector` query planner converts `AFNestedObject` fields into `object` field types in the query sent to the agent. ## Limitations ### HGE not yet implemented: - Support for nested arrays - Support for nested objects/arrays in mutations - Support for nested objects/arrays in order-by - Support for filters (`where`) in nested objects/arrays - Support for adding custom GraphQL types via track table metadata API - Support for interface and union types - Tests for nested objects ### Mongo agent not yet implemented: - Generate nested object types from validation schema - Support for aggregates - Support for order-by - Configure agent port - Build agent in CI - Agent tests for nested objects and MongoDB agent PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7844 GitOrigin-RevId: aec9ec1e4216293286a68f9b1af6f3f5317db423
2023-04-11 04:29:05 +03:00
Eq (RemoteRelationshipSelect b r),
Eq (AnnNestedObjectSelectG b r v)
) =>
Eq (AnnFieldG b r v)
deriving stock instance
( Backend b,
Show (AnnColumnField b v),
Show (ArraySelectG b r v),
Show (ComputedFieldSelect b r v),
Show (ObjectRelationSelectG b r v),
Support nested object fields in DC API and use this to implement nest… ## Description This change adds support for nested object fields in HGE IR and Schema Cache, the Data Connectors backend and API, and the MongoDB agent. ### Data Connector API changes - The `/schema` endpoint response now includes an optional set of GraphQL type definitions. Table column types can refer to these definitions by name. - Queries can now include a new field type `object` which contains a column name and a nested query. This allows querying into a nested object within a field. ### MongoDB agent changes - Add support for querying into nested documents using the new `object` field type. ### HGE changes - The `Backend` type class has a new type family `XNestedObjects b` which controls whether or not a backend supports querying into nested objects. This is currently enabled only for the `DataConnector` backend. - For backends that support nested objects, the `FieldInfo` type gets a new constructor `FINestedObject`, and the `AnnFieldG` type gets a new constructor `AFNestedObject`. - If the DC `/schema` endpoint returns any custom GraphQL type definitions they are stored in the `TableInfo` for each table in the source. - During schema cache building, the function `addNonColumnFields` will check whether any column types match custom GraphQL object types stored in the `TableInfo`. If so, they are converted into `FINestedObject` instead of `FIColumn` in the `FieldInfoMap`. - When building the `FieldParser`s from `FieldInfo` (function `fieldSelection`) any `FINestedObject` fields are converted into nested object parsers returning `AFNestedObject`. - The `DataConnector` query planner converts `AFNestedObject` fields into `object` field types in the query sent to the agent. ## Limitations ### HGE not yet implemented: - Support for nested arrays - Support for nested objects/arrays in mutations - Support for nested objects/arrays in order-by - Support for filters (`where`) in nested objects/arrays - Support for adding custom GraphQL types via track table metadata API - Support for interface and union types - Tests for nested objects ### Mongo agent not yet implemented: - Generate nested object types from validation schema - Support for aggregates - Support for order-by - Configure agent port - Build agent in CI - Agent tests for nested objects and MongoDB agent PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7844 GitOrigin-RevId: aec9ec1e4216293286a68f9b1af6f3f5317db423
2023-04-11 04:29:05 +03:00
Show (RemoteRelationshipSelect b r),
Show (AnnNestedObjectSelectG b r v)
) =>
Show (AnnFieldG b r v)
instance Backend b => Bifoldable (AnnFieldG b) where
bifoldMap f g = \case
AFColumn col -> foldMap g col
AFObjectRelation objRel -> foldMap (bifoldMap f g) objRel
AFArrayRelation arrRel -> bifoldMap f g arrRel
AFComputedField _ _ cf -> bifoldMap f g cf
AFRemote r -> foldMap f r
AFNodeId {} -> mempty
AFExpression {} -> mempty
Support nested object fields in DC API and use this to implement nest… ## Description This change adds support for nested object fields in HGE IR and Schema Cache, the Data Connectors backend and API, and the MongoDB agent. ### Data Connector API changes - The `/schema` endpoint response now includes an optional set of GraphQL type definitions. Table column types can refer to these definitions by name. - Queries can now include a new field type `object` which contains a column name and a nested query. This allows querying into a nested object within a field. ### MongoDB agent changes - Add support for querying into nested documents using the new `object` field type. ### HGE changes - The `Backend` type class has a new type family `XNestedObjects b` which controls whether or not a backend supports querying into nested objects. This is currently enabled only for the `DataConnector` backend. - For backends that support nested objects, the `FieldInfo` type gets a new constructor `FINestedObject`, and the `AnnFieldG` type gets a new constructor `AFNestedObject`. - If the DC `/schema` endpoint returns any custom GraphQL type definitions they are stored in the `TableInfo` for each table in the source. - During schema cache building, the function `addNonColumnFields` will check whether any column types match custom GraphQL object types stored in the `TableInfo`. If so, they are converted into `FINestedObject` instead of `FIColumn` in the `FieldInfoMap`. - When building the `FieldParser`s from `FieldInfo` (function `fieldSelection`) any `FINestedObject` fields are converted into nested object parsers returning `AFNestedObject`. - The `DataConnector` query planner converts `AFNestedObject` fields into `object` field types in the query sent to the agent. ## Limitations ### HGE not yet implemented: - Support for nested arrays - Support for nested objects/arrays in mutations - Support for nested objects/arrays in order-by - Support for filters (`where`) in nested objects/arrays - Support for adding custom GraphQL types via track table metadata API - Support for interface and union types - Tests for nested objects ### Mongo agent not yet implemented: - Generate nested object types from validation schema - Support for aggregates - Support for order-by - Configure agent port - Build agent in CI - Agent tests for nested objects and MongoDB agent PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7844 GitOrigin-RevId: aec9ec1e4216293286a68f9b1af6f3f5317db423
2023-04-11 04:29:05 +03:00
AFNestedObject no -> bifoldMap f g no
type AnnField b = AnnFieldG b Void (SQLExpression b)
type AnnFields b = AnnFieldsG b Void (SQLExpression b)
mkAnnColumnField ::
Column backend ->
ColumnType backend ->
Maybe (AnnColumnCaseBoolExp backend v) ->
Maybe (ScalarSelectionArguments backend) ->
AnnFieldG backend r v
mkAnnColumnField col typ caseBoolExp colOpM =
AFColumn (AnnColumnField col typ False colOpM caseBoolExp)
mkAnnColumnFieldAsText ::
ColumnInfo backend ->
AnnFieldG backend r v
mkAnnColumnFieldAsText ci =
AFColumn (AnnColumnField (ciColumn ci) (ciType ci) True Nothing Nothing)
traverseSourceRelationshipSelection ::
(Applicative f, Backend backend) =>
(vf backend -> f (vg backend)) ->
SourceRelationshipSelection backend r vf ->
f (SourceRelationshipSelection backend r vg)
traverseSourceRelationshipSelection f = \case
SourceRelationshipObject s ->
SourceRelationshipObject <$> traverse f s
SourceRelationshipArray s ->
SourceRelationshipArray <$> traverse f s
SourceRelationshipArrayAggregate s ->
SourceRelationshipArrayAggregate <$> traverse f s
-- Aggregation fields
data TableAggregateFieldG (b :: BackendType) (r :: Type) v
= TAFAgg (AggregateFields b)
| TAFNodes (XNodesAgg b) (AnnFieldsG b r v)
| TAFExp Text
deriving stock (Functor, Foldable, Traversable)
deriving stock instance
( Backend b,
Eq (AggregateFields b),
Eq (AnnFieldsG b r v)
) =>
Eq (TableAggregateFieldG b r v)
deriving stock instance
( Backend b,
Show (AggregateFields b),
Show (AnnFieldsG b r v)
) =>
Show (TableAggregateFieldG b r v)
instance Backend b => Bifoldable (TableAggregateFieldG b) where
bifoldMap f g = \case
TAFAgg {} -> mempty
TAFNodes _ fields -> foldMap (foldMap $ bifoldMap f g) fields
TAFExp {} -> mempty
data AggregateField (b :: BackendType)
= AFCount (CountType b)
| AFOp (AggregateOp b)
| AFExp Text
deriving stock instance (Backend b) => Eq (AggregateField b)
deriving stock instance (Backend b) => Show (AggregateField b)
data AggregateOp (b :: BackendType) = AggregateOp
{ _aoOp :: Text,
_aoFields :: (ColumnFields b)
}
deriving stock (Eq, Show)
data ColFld (b :: BackendType)
= CFCol (Column b) (ColumnType b)
| CFExp Text
deriving stock (Eq, Show)
type TableAggregateField b = TableAggregateFieldG b Void (SQLExpression b)
type TableAggregateFields b = TableAggregateFieldsG b Void (SQLExpression b)
type TableAggregateFieldsG b r v = Fields (TableAggregateFieldG b r v)
type ColumnFields b = Fields (ColFld b)
type AggregateFields b = Fields (AggregateField b)
type AnnFieldsG b r v = Fields (AnnFieldG b r v)
-- Relay fields
data ConnectionField (b :: BackendType) (r :: Type) v
= ConnectionTypename Text
| ConnectionPageInfo PageInfoFields
| ConnectionEdges (EdgeFields b r v)
deriving stock (Functor, Foldable, Traversable)
deriving stock instance
( Eq (EdgeFields b r v)
) =>
Eq (ConnectionField b r v)
deriving stock instance
( Show (EdgeFields b r v)
) =>
Show (ConnectionField b r v)
instance Backend b => Bifoldable (ConnectionField b) where
bifoldMap f g = \case
ConnectionTypename {} -> mempty
ConnectionPageInfo {} -> mempty
ConnectionEdges edgeFields -> foldMap (foldMap $ bifoldMap f g) edgeFields
data PageInfoField
= PageInfoTypename Text
| PageInfoHasNextPage
| PageInfoHasPreviousPage
| PageInfoStartCursor
| PageInfoEndCursor
deriving stock (Show, Eq)
data EdgeField (b :: BackendType) (r :: Type) v
= EdgeTypename Text
| EdgeCursor
| EdgeNode (AnnFieldsG b r v)
deriving stock (Functor, Foldable, Traversable)
deriving stock instance
( Eq (AnnFieldsG b r v)
) =>
Eq (EdgeField b r v)
deriving stock instance
( Show (AnnFieldsG b r v)
) =>
Show (EdgeField b r v)
instance Backend b => Bifoldable (EdgeField b) where
bifoldMap f g = \case
EdgeTypename {} -> mempty
EdgeCursor -> mempty
EdgeNode annFields -> foldMap (foldMap $ bifoldMap f g) annFields
type ConnectionFields b r v = Fields (ConnectionField b r v)
type PageInfoFields = Fields PageInfoField
type EdgeFields b r v = Fields (EdgeField b r v)
data AnnColumnField (b :: BackendType) v = AnnColumnField
{ _acfColumn :: Column b,
_acfType :: ColumnType b,
-- | If this field is 'True', columns are explicitly casted to @text@ when
-- fetched, which avoids an issue that occurs because we dont currently
-- have proper support for array types. See
-- https://github.com/hasura/graphql-engine/pull/3198 for more details.
_acfAsText :: Bool,
-- | Arguments of this column's selection. See 'ScalarSelectionArguments'
_acfArguments :: Maybe (ScalarSelectionArguments b),
-- | This type is used to determine whether the column
-- should be nullified. When the value is `Nothing`, the column value
-- will be outputted as computed and when the value is `Just c`, the
-- column will be outputted when `c` evaluates to `true` and `null`
-- when `c` evaluates to `false`.
_acfCaseBoolExpression :: (Maybe (AnnColumnCaseBoolExp b v))
}
deriving stock (Functor, Foldable, Traversable)
deriving stock instance
( Backend b,
Eq (AnnColumnCaseBoolExp b v)
) =>
Eq (AnnColumnField b v)
deriving stock instance
( Backend b,
Show (AnnColumnCaseBoolExp b v)
) =>
Show (AnnColumnField b v)
-- Computed field
2019-04-17 12:48:41 +03:00
data ComputedFieldScalarSelect (b :: BackendType) v = ComputedFieldScalarSelect
{ _cfssFunction :: FunctionName b,
_cfssArguments :: FunctionArgsExp b v,
_cfssType :: ScalarType b,
_cfssScalarArguments :: (Maybe (ScalarSelectionArguments b))
}
deriving stock instance (Backend b) => Functor (ComputedFieldScalarSelect b)
deriving stock instance (Backend b) => Foldable (ComputedFieldScalarSelect b)
deriving stock instance (Backend b) => Traversable (ComputedFieldScalarSelect b)
deriving stock instance (Backend b, Show v, Show (FunctionArgumentExp b v)) => Show (ComputedFieldScalarSelect b v)
deriving stock instance (Backend b, Eq v, Eq (FunctionArgumentExp b v)) => Eq (ComputedFieldScalarSelect b v)
data ComputedFieldSelect (b :: BackendType) (r :: Type) v
= CFSScalar
(ComputedFieldScalarSelect b v)
-- ^ Type containing info about the computed field
(Maybe (AnnColumnCaseBoolExp b v))
-- ^ This type is used to determine if whether the scalar
-- computed field should be nullified. When the value is `Nothing`,
-- the scalar computed value will be outputted as computed and when the
-- value is `Just c`, the scalar computed field will be outputted when
-- `c` evaluates to `true` and `null` when `c` evaluates to `false`
| CFSTable JsonAggSelect (AnnSimpleSelectG b r v)
deriving stock (Functor, Foldable, Traversable)
2019-04-17 12:48:41 +03:00
deriving stock instance
( Backend b,
Eq (AnnColumnCaseBoolExp b v),
Eq (AnnSimpleSelectG b r v),
Eq (ComputedFieldScalarSelect b v)
) =>
Eq (ComputedFieldSelect b r v)
deriving stock instance
( Backend b,
Show (AnnColumnCaseBoolExp b v),
Show (AnnSimpleSelectG b r v),
Show (ComputedFieldScalarSelect b v)
) =>
Show (ComputedFieldSelect b r v)
instance Backend b => Bifoldable (ComputedFieldSelect b) where
bifoldMap f g = \case
CFSScalar cfsSelect caseBoolExp -> foldMap g cfsSelect <> foldMap (foldMap $ foldMap g) caseBoolExp
CFSTable _ simpleSelect -> bifoldMapAnnSelectG f g simpleSelect
-- Local relationship
type ArrayRelationSelectG b r v = AnnRelationSelectG b (AnnSimpleSelectG b r v)
type ArrayAggregateSelectG b r v = AnnRelationSelectG b (AnnAggregateSelectG b r v)
type ArrayConnectionSelect b r v = AnnRelationSelectG b (ConnectionSelect b r v)
type ArrayAggregateSelect b = ArrayAggregateSelectG b Void (SQLExpression b)
data AnnObjectSelectG (b :: BackendType) (r :: Type) v = AnnObjectSelectG
{ _aosFields :: AnnFieldsG b r v,
_aosTableFrom :: TableName b,
_aosTableFilter :: (AnnBoolExp b v)
}
deriving stock (Functor, Foldable, Traversable)
deriving stock instance
( Backend b,
Eq (AnnBoolExp b v),
Eq (AnnFieldsG b r v)
) =>
Eq (AnnObjectSelectG b r v)
deriving stock instance
( Backend b,
Show (AnnBoolExp b v),
Show (AnnFieldsG b r v)
) =>
Show (AnnObjectSelectG b r v)
instance Backend b => Bifoldable (AnnObjectSelectG b) where
bifoldMap f g AnnObjectSelectG {..} =
foldMap (foldMap $ bifoldMap f g) _aosFields <> foldMap (foldMap g) _aosTableFilter
type AnnObjectSelect b r = AnnObjectSelectG b r (SQLExpression b)
type ObjectRelationSelectG b r v = AnnRelationSelectG b (AnnObjectSelectG b r v)
type ObjectRelationSelect b = ObjectRelationSelectG b Void (SQLExpression b)
data ArraySelectG (b :: BackendType) (r :: Type) v
= ASSimple (ArrayRelationSelectG b r v)
| ASAggregate (ArrayAggregateSelectG b r v)
| ASConnection (ArrayConnectionSelect b r v)
deriving stock (Functor, Foldable, Traversable)
deriving stock instance
( Eq (ArrayRelationSelectG b r v),
Eq (ArrayAggregateSelectG b r v),
Eq (ArrayConnectionSelect b r v)
) =>
Eq (ArraySelectG b r v)
deriving stock instance
( Show (ArrayRelationSelectG b r v),
Show (ArrayAggregateSelectG b r v),
Show (ArrayConnectionSelect b r v)
) =>
Show (ArraySelectG b r v)
instance Backend b => Bifoldable (ArraySelectG b) where
bifoldMap f g = \case
ASSimple arrayRelationSelect -> foldMap (bifoldMapAnnSelectG f g) arrayRelationSelect
ASAggregate arrayAggregateSelect -> foldMap (bifoldMapAnnSelectG f g) arrayAggregateSelect
ASConnection arrayConnectionSelect -> foldMap (bifoldMap f g) arrayConnectionSelect
type ArraySelect b = ArraySelectG b Void (SQLExpression b)
type ArraySelectFieldsG b r v = Fields (ArraySelectG b r v)
2019-04-17 12:48:41 +03:00
-- | Captures the selection set of a remote source relationship.
data
SourceRelationshipSelection
(b :: BackendType)
(r :: Type)
(vf :: BackendType -> Type)
= SourceRelationshipObject (AnnObjectSelectG b r (vf b))
| SourceRelationshipArray (AnnSimpleSelectG b r (vf b))
| SourceRelationshipArrayAggregate (AnnAggregateSelectG b r (vf b))
deriving stock instance
( Backend b,
Eq (AnnAggregateSelectG b r (vf b)),
Eq (AnnObjectSelectG b r (vf b)),
Eq (AnnSimpleSelectG b r (vf b))
) =>
Eq (SourceRelationshipSelection b r vf)
deriving stock instance
( Backend b,
Show (AnnAggregateSelectG b r (vf b)),
Show (AnnObjectSelectG b r (vf b)),
Show (AnnSimpleSelectG b r (vf b))
) =>
Show (SourceRelationshipSelection b r vf)
-- | A relationship to a remote source. 'vf' (could use a better name) is
-- analogous to 'v' in other IR types such as 'AnnFieldG'. vf's kind is
-- (BackendType -> Type) instead of v's 'Type' so that 'v' of 'AnnFieldG' can
-- be specific to the backend that it captures ('b' of an AnnFieldG changes as
-- we walk down the IR branches which capture relationships to other databases)
data
RemoteSourceSelect
(r :: Type)
(vf :: BackendType -> Type)
(tgt :: BackendType) = RemoteSourceSelect
{ _rssName :: SourceName,
_rssConfig :: SourceConfig tgt,
_rssSelection :: SourceRelationshipSelection tgt r vf,
-- | Additional information about the source's join columns:
-- (ScalarType tgt) so that the remote can interpret the join values coming
-- from src
-- (Column tgt) so that an appropriate join condition / IN clause can be built
-- by the remote
_rssJoinMapping :: (HM.HashMap FieldName (ScalarType tgt, Column tgt)),
_rssStringifyNums :: StringifyNumbers
}
deriving stock instance
( Backend tgt,
Eq (SourceRelationshipSelection tgt r vf)
) =>
Eq (RemoteSourceSelect r vf tgt)
deriving stock instance
( Backend tgt,
Show (SourceRelationshipSelection tgt r vf),
Show (SourceConfig tgt)
) =>
Show (RemoteSourceSelect r vf tgt)
Support nested object fields in DC API and use this to implement nest… ## Description This change adds support for nested object fields in HGE IR and Schema Cache, the Data Connectors backend and API, and the MongoDB agent. ### Data Connector API changes - The `/schema` endpoint response now includes an optional set of GraphQL type definitions. Table column types can refer to these definitions by name. - Queries can now include a new field type `object` which contains a column name and a nested query. This allows querying into a nested object within a field. ### MongoDB agent changes - Add support for querying into nested documents using the new `object` field type. ### HGE changes - The `Backend` type class has a new type family `XNestedObjects b` which controls whether or not a backend supports querying into nested objects. This is currently enabled only for the `DataConnector` backend. - For backends that support nested objects, the `FieldInfo` type gets a new constructor `FINestedObject`, and the `AnnFieldG` type gets a new constructor `AFNestedObject`. - If the DC `/schema` endpoint returns any custom GraphQL type definitions they are stored in the `TableInfo` for each table in the source. - During schema cache building, the function `addNonColumnFields` will check whether any column types match custom GraphQL object types stored in the `TableInfo`. If so, they are converted into `FINestedObject` instead of `FIColumn` in the `FieldInfoMap`. - When building the `FieldParser`s from `FieldInfo` (function `fieldSelection`) any `FINestedObject` fields are converted into nested object parsers returning `AFNestedObject`. - The `DataConnector` query planner converts `AFNestedObject` fields into `object` field types in the query sent to the agent. ## Limitations ### HGE not yet implemented: - Support for nested arrays - Support for nested objects/arrays in mutations - Support for nested objects/arrays in order-by - Support for filters (`where`) in nested objects/arrays - Support for adding custom GraphQL types via track table metadata API - Support for interface and union types - Tests for nested objects ### Mongo agent not yet implemented: - Generate nested object types from validation schema - Support for aggregates - Support for order-by - Configure agent port - Build agent in CI - Agent tests for nested objects and MongoDB agent PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7844 GitOrigin-RevId: aec9ec1e4216293286a68f9b1af6f3f5317db423
2023-04-11 04:29:05 +03:00
-- Nested objects
data AnnNestedObjectSelectG (b :: BackendType) (r :: Type) v = AnnNestedObjectSelectG
{ _anosSupportsNestedObjects :: XNestedObjects b,
_anosColumn :: Column b,
_anosFields :: AnnFieldsG b r v
}
deriving stock (Functor, Foldable, Traversable)
deriving stock instance
( Backend b,
Eq (AnnFieldsG b r v)
) =>
Eq (AnnNestedObjectSelectG b r v)
deriving stock instance
( Backend b,
Show (AnnFieldsG b r v)
) =>
Show (AnnNestedObjectSelectG b r v)
instance Backend b => Bifoldable (AnnNestedObjectSelectG b) where
bifoldMap f g AnnNestedObjectSelectG {..} =
foldMap (foldMap $ bifoldMap f g) _anosFields
type AnnNestedObjectSelect b r = AnnNestedObjectSelectG b r (SQLExpression b)
-- | If argument positional index is less than or equal to length of
-- 'positional' arguments then insert the value in 'positional' arguments else
-- insert the value with argument name in 'named' arguments
insertFunctionArg ::
FunctionArgName ->
Int ->
a ->
FunctionArgsExpG a ->
FunctionArgsExpG a
insertFunctionArg argName idx value (FunctionArgsExp positional named) =
if (idx + 1) <= length positional
then FunctionArgsExp (insertAt idx value positional) named
else
FunctionArgsExp positional $
HM.insert (getFuncArgNameTxt argName) value named
where
insertAt i a = toList . Seq.insertAt i a . Seq.fromList
-- | The "distinct" input field inside "count" aggregate field
--
-- count (
-- distinct: Boolean
-- ): Int
data CountDistinct
= SelectCountDistinct
| SelectCountNonDistinct
-- Lenses
$(makeLenses ''AnnObjectSelectG)
Support nested object fields in DC API and use this to implement nest… ## Description This change adds support for nested object fields in HGE IR and Schema Cache, the Data Connectors backend and API, and the MongoDB agent. ### Data Connector API changes - The `/schema` endpoint response now includes an optional set of GraphQL type definitions. Table column types can refer to these definitions by name. - Queries can now include a new field type `object` which contains a column name and a nested query. This allows querying into a nested object within a field. ### MongoDB agent changes - Add support for querying into nested documents using the new `object` field type. ### HGE changes - The `Backend` type class has a new type family `XNestedObjects b` which controls whether or not a backend supports querying into nested objects. This is currently enabled only for the `DataConnector` backend. - For backends that support nested objects, the `FieldInfo` type gets a new constructor `FINestedObject`, and the `AnnFieldG` type gets a new constructor `AFNestedObject`. - If the DC `/schema` endpoint returns any custom GraphQL type definitions they are stored in the `TableInfo` for each table in the source. - During schema cache building, the function `addNonColumnFields` will check whether any column types match custom GraphQL object types stored in the `TableInfo`. If so, they are converted into `FINestedObject` instead of `FIColumn` in the `FieldInfoMap`. - When building the `FieldParser`s from `FieldInfo` (function `fieldSelection`) any `FINestedObject` fields are converted into nested object parsers returning `AFNestedObject`. - The `DataConnector` query planner converts `AFNestedObject` fields into `object` field types in the query sent to the agent. ## Limitations ### HGE not yet implemented: - Support for nested arrays - Support for nested objects/arrays in mutations - Support for nested objects/arrays in order-by - Support for filters (`where`) in nested objects/arrays - Support for adding custom GraphQL types via track table metadata API - Support for interface and union types - Tests for nested objects ### Mongo agent not yet implemented: - Generate nested object types from validation schema - Support for aggregates - Support for order-by - Configure agent port - Build agent in CI - Agent tests for nested objects and MongoDB agent PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7844 GitOrigin-RevId: aec9ec1e4216293286a68f9b1af6f3f5317db423
2023-04-11 04:29:05 +03:00
$(makeLenses ''AnnNestedObjectSelectG)
$(makeLenses ''ConnectionSelect)
$(makePrisms ''AnnFieldG)
$(makePrisms ''TableAggregateFieldG)
$(makePrisms ''ConnectionField)
$(makePrisms ''EdgeField)