2021-12-22 02:14:56 +03:00
|
|
|
module Hasura.GraphQL.Schema.RemoteRelationship
|
|
|
|
( remoteRelationshipField,
|
|
|
|
)
|
|
|
|
where
|
|
|
|
|
|
|
|
import Control.Lens
|
|
|
|
import Data.Has
|
|
|
|
import Data.HashMap.Strict.Extended qualified as Map
|
|
|
|
import Data.List.NonEmpty qualified as NE
|
|
|
|
import Data.Text.Extended
|
|
|
|
import Hasura.Base.Error
|
|
|
|
import Hasura.GraphQL.Execute.Types qualified as ET
|
|
|
|
import Hasura.GraphQL.Parser
|
|
|
|
import Hasura.GraphQL.Parser qualified as P
|
2022-04-18 22:43:00 +03:00
|
|
|
import Hasura.GraphQL.Parser.Constants qualified as G
|
2021-12-22 02:14:56 +03:00
|
|
|
import Hasura.GraphQL.Parser.Internal.Parser qualified as P
|
|
|
|
import Hasura.GraphQL.Schema.Backend
|
|
|
|
import Hasura.GraphQL.Schema.Common
|
|
|
|
import Hasura.GraphQL.Schema.Instances ()
|
|
|
|
import Hasura.GraphQL.Schema.Remote
|
|
|
|
import Hasura.GraphQL.Schema.Select
|
|
|
|
import Hasura.GraphQL.Schema.Table
|
|
|
|
import Hasura.Prelude
|
|
|
|
import Hasura.RQL.DDL.RemoteRelationship.Validate
|
|
|
|
import Hasura.RQL.IR qualified as IR
|
|
|
|
import Hasura.RQL.Types.Common (FieldName, RelType (..), relNameToTxt)
|
|
|
|
import Hasura.RQL.Types.Relationships.Remote
|
|
|
|
import Hasura.RQL.Types.Relationships.ToSchema
|
|
|
|
import Hasura.RQL.Types.Relationships.ToSchema qualified as Remote
|
|
|
|
import Hasura.RQL.Types.RemoteSchema
|
|
|
|
import Hasura.RQL.Types.ResultCustomization
|
2022-04-26 18:12:47 +03:00
|
|
|
import Hasura.RQL.Types.SchemaCache hiding (askTableInfo)
|
Remove circular dependency in schema building code
### Description
The main goal of this PR is, as stated, to remove the circular dependency in the schema building code. This cycle arises from the existence of remote relationships: when we build the schema for a source A, a remote relationship might force us to jump to the schema of a source B, or some remote schema. As a result, we end up having to do a dispatch from a "leaf" of the schema, similar to the one done at the root. In turn, this forces us to carry along in the schema a lot of information required for that dispatch, AND it forces us to import the instances in scope, creating an import loop.
As discussed in #4489, this PR implements the "dependency injection" solution: we pass to the schema a function to call to do the dispatch, and to get a generated field for a remote relationship. That way, this function can be chosen at the root level, and the leaves need not be aware of the overall context.
This PR grew a bit bigger than that, however; in an attempt to try and remove the `SourceCache` from the schema altogether, it changed a lot of functions across the schema building code, to thread along the `SourceInfo b` of the source being built. This avoids having to do cache lookups within a given source. A few cases remain, such as relay, that we might try to tackle in a subsequent PR.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/4557
GitOrigin-RevId: 9388e48372877520a72a9fd1677005df9f7b2d72
2022-05-27 20:21:22 +03:00
|
|
|
import Hasura.RQL.Types.Source
|
2022-05-26 14:54:30 +03:00
|
|
|
import Hasura.RQL.Types.SourceCustomization (NamingCase (..), mkCustomizedTypename)
|
2021-12-22 02:14:56 +03:00
|
|
|
import Hasura.SQL.AnyBackend
|
|
|
|
import Hasura.Session
|
|
|
|
import Language.GraphQL.Draft.Syntax qualified as G
|
|
|
|
|
|
|
|
-- | Remote relationship field parsers
|
|
|
|
remoteRelationshipField ::
|
Remove circular dependency in schema building code
### Description
The main goal of this PR is, as stated, to remove the circular dependency in the schema building code. This cycle arises from the existence of remote relationships: when we build the schema for a source A, a remote relationship might force us to jump to the schema of a source B, or some remote schema. As a result, we end up having to do a dispatch from a "leaf" of the schema, similar to the one done at the root. In turn, this forces us to carry along in the schema a lot of information required for that dispatch, AND it forces us to import the instances in scope, creating an import loop.
As discussed in #4489, this PR implements the "dependency injection" solution: we pass to the schema a function to call to do the dispatch, and to get a generated field for a remote relationship. That way, this function can be chosen at the root level, and the leaves need not be aware of the overall context.
This PR grew a bit bigger than that, however; in an attempt to try and remove the `SourceCache` from the schema altogether, it changed a lot of functions across the schema building code, to thread along the `SourceInfo b` of the source being built. This avoids having to do cache lookups within a given source. A few cases remain, such as relay, that we might try to tackle in a subsequent PR.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/4557
GitOrigin-RevId: 9388e48372877520a72a9fd1677005df9f7b2d72
2022-05-27 20:21:22 +03:00
|
|
|
SourceCache ->
|
|
|
|
RemoteSchemaMap ->
|
|
|
|
RemoteRelationshipParserBuilder
|
|
|
|
remoteRelationshipField sourceCache remoteSchemaCache = RemoteRelationshipParserBuilder
|
|
|
|
\RemoteFieldInfo {..} -> runMaybeT do
|
|
|
|
queryType <- retrieve soQueryType
|
|
|
|
-- https://github.com/hasura/graphql-engine/issues/5144
|
|
|
|
-- The above issue is easily fixable by removing the following guard
|
|
|
|
guard $ queryType == ET.QueryHasura
|
|
|
|
case _rfiRHS of
|
|
|
|
RFISource anyRemoteSourceFieldInfo ->
|
|
|
|
dispatchAnyBackend @BackendSchema anyRemoteSourceFieldInfo \remoteSourceFieldInfo -> do
|
|
|
|
fields <- lift $ remoteRelationshipToSourceField sourceCache remoteSourceFieldInfo
|
|
|
|
pure $ fmap (IR.RemoteSourceField . mkAnyBackend) <$> fields
|
|
|
|
RFISchema remoteSchema -> do
|
|
|
|
fields <- MaybeT $ remoteRelationshipToSchemaField remoteSchemaCache _rfiLHS remoteSchema
|
|
|
|
pure $ pure $ IR.RemoteSchemaField <$> fields
|
2021-12-22 02:14:56 +03:00
|
|
|
|
|
|
|
-- | Parser(s) for remote relationship fields to a remote schema
|
|
|
|
remoteRelationshipToSchemaField ::
|
|
|
|
forall r m n lhsJoinField.
|
|
|
|
(MonadBuildSchemaBase r m n) =>
|
Remove circular dependency in schema building code
### Description
The main goal of this PR is, as stated, to remove the circular dependency in the schema building code. This cycle arises from the existence of remote relationships: when we build the schema for a source A, a remote relationship might force us to jump to the schema of a source B, or some remote schema. As a result, we end up having to do a dispatch from a "leaf" of the schema, similar to the one done at the root. In turn, this forces us to carry along in the schema a lot of information required for that dispatch, AND it forces us to import the instances in scope, creating an import loop.
As discussed in #4489, this PR implements the "dependency injection" solution: we pass to the schema a function to call to do the dispatch, and to get a generated field for a remote relationship. That way, this function can be chosen at the root level, and the leaves need not be aware of the overall context.
This PR grew a bit bigger than that, however; in an attempt to try and remove the `SourceCache` from the schema altogether, it changed a lot of functions across the schema building code, to thread along the `SourceInfo b` of the source being built. This avoids having to do cache lookups within a given source. A few cases remain, such as relay, that we might try to tackle in a subsequent PR.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/4557
GitOrigin-RevId: 9388e48372877520a72a9fd1677005df9f7b2d72
2022-05-27 20:21:22 +03:00
|
|
|
RemoteSchemaMap ->
|
2021-12-22 02:14:56 +03:00
|
|
|
Map.HashMap FieldName lhsJoinField ->
|
|
|
|
RemoteSchemaFieldInfo ->
|
2022-05-31 01:07:02 +03:00
|
|
|
m (Maybe (FieldParser n (IR.RemoteSchemaSelect (IR.RemoteRelationshipField IR.UnpreparedValue))))
|
Remove circular dependency in schema building code
### Description
The main goal of this PR is, as stated, to remove the circular dependency in the schema building code. This cycle arises from the existence of remote relationships: when we build the schema for a source A, a remote relationship might force us to jump to the schema of a source B, or some remote schema. As a result, we end up having to do a dispatch from a "leaf" of the schema, similar to the one done at the root. In turn, this forces us to carry along in the schema a lot of information required for that dispatch, AND it forces us to import the instances in scope, creating an import loop.
As discussed in #4489, this PR implements the "dependency injection" solution: we pass to the schema a function to call to do the dispatch, and to get a generated field for a remote relationship. That way, this function can be chosen at the root level, and the leaves need not be aware of the overall context.
This PR grew a bit bigger than that, however; in an attempt to try and remove the `SourceCache` from the schema altogether, it changed a lot of functions across the schema building code, to thread along the `SourceInfo b` of the source being built. This avoids having to do cache lookups within a given source. A few cases remain, such as relay, that we might try to tackle in a subsequent PR.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/4557
GitOrigin-RevId: 9388e48372877520a72a9fd1677005df9f7b2d72
2022-05-27 20:21:22 +03:00
|
|
|
remoteRelationshipToSchemaField remoteSchemaCache lhsFields RemoteSchemaFieldInfo {..} = runMaybeT do
|
|
|
|
remoteSchemaPermsCtx <- retrieve soRemoteSchemaPermsCtx
|
2022-03-10 15:12:36 +03:00
|
|
|
roleName <- asks getter
|
2022-03-14 19:21:26 +03:00
|
|
|
remoteSchemaContext <-
|
|
|
|
Map.lookup _rrfiRemoteSchemaName remoteSchemaCache
|
|
|
|
`onNothing` throw500 ("invalid remote schema name: " <>> _rrfiRemoteSchemaName)
|
|
|
|
introspection <- hoistMaybe $ getIntrospectionResult remoteSchemaPermsCtx roleName remoteSchemaContext
|
|
|
|
let remoteSchemaRelationships = _rscRemoteRelationships remoteSchemaContext
|
|
|
|
roleIntrospection = irDoc introspection
|
|
|
|
remoteSchemaRoot = irQueryRoot introspection
|
|
|
|
remoteSchemaCustomizer = rsCustomizer $ _rscInfo remoteSchemaContext
|
|
|
|
RemoteSchemaIntrospection typeDefns = roleIntrospection
|
2021-12-22 02:14:56 +03:00
|
|
|
let hasuraFieldNames = Map.keysSet lhsFields
|
|
|
|
relationshipDef = ToSchemaRelationshipDef _rrfiRemoteSchemaName hasuraFieldNames _rrfiRemoteFields
|
|
|
|
(newInpValDefns :: [G.TypeDefinition [G.Name] RemoteSchemaInputValueDefinition], remoteFieldParamMap) <-
|
2022-03-10 15:12:36 +03:00
|
|
|
if roleName == adminRoleName
|
2021-12-22 02:14:56 +03:00
|
|
|
then do
|
|
|
|
-- we don't validate the remote relationship when the role is admin
|
|
|
|
-- because it's already been validated, when the remote relationship
|
|
|
|
-- was created
|
|
|
|
pure (_rrfiInputValueDefinitions, _rrfiParamMap)
|
|
|
|
else do
|
|
|
|
(_, roleRemoteField) <-
|
|
|
|
afold @(Either _) $
|
|
|
|
-- TODO: this really needs to go way, we shouldn't be doing
|
|
|
|
-- validation when building parsers
|
2022-03-14 19:21:26 +03:00
|
|
|
validateToSchemaRelationship relationshipDef _rrfiLHSIdentifier _rrfiName (_rrfiRemoteSchema, introspection) lhsFields
|
2021-12-22 02:14:56 +03:00
|
|
|
pure (Remote._rrfiInputValueDefinitions roleRemoteField, Remote._rrfiParamMap roleRemoteField)
|
2022-03-14 19:21:26 +03:00
|
|
|
let -- add the new input value definitions created by the remote relationship
|
2021-12-22 02:14:56 +03:00
|
|
|
-- to the existing schema introspection of the role
|
|
|
|
remoteRelationshipIntrospection = RemoteSchemaIntrospection $ typeDefns <> Map.fromListOn getTypeName newInpValDefns
|
|
|
|
fieldName <- textToName $ relNameToTxt _rrfiName
|
|
|
|
|
|
|
|
-- This selection set parser, should be of the remote node's selection set parser, which comes
|
|
|
|
-- from the fieldCall
|
|
|
|
let fieldCalls = unRemoteFields _rrfiRemoteFields
|
2022-03-14 19:21:26 +03:00
|
|
|
nestedFieldType <- lift $ lookupNestedFieldType remoteSchemaRoot roleIntrospection fieldCalls
|
2021-12-22 02:14:56 +03:00
|
|
|
let typeName = G.getBaseType nestedFieldType
|
|
|
|
fieldTypeDefinition <-
|
|
|
|
onNothing (lookupType roleIntrospection typeName)
|
|
|
|
-- the below case will never happen because we get the type name
|
|
|
|
-- from the schema document itself i.e. if a field exists for the
|
|
|
|
-- given role, then it's return type also must exist
|
|
|
|
$
|
|
|
|
throw500 $ "unexpected: " <> typeName <<> " not found "
|
|
|
|
-- These are the arguments that are given by the user while executing a query
|
|
|
|
let remoteFieldUserArguments = map snd $ Map.toList remoteFieldParamMap
|
|
|
|
remoteFld <-
|
|
|
|
withRemoteSchemaCustomization remoteSchemaCustomizer $
|
|
|
|
lift $
|
|
|
|
P.wrapFieldParser nestedFieldType
|
2022-03-14 19:21:26 +03:00
|
|
|
<$> remoteField remoteRelationshipIntrospection remoteSchemaRelationships remoteSchemaRoot fieldName Nothing remoteFieldUserArguments fieldTypeDefinition
|
2021-12-22 02:14:56 +03:00
|
|
|
|
|
|
|
pure $
|
|
|
|
remoteFld
|
2022-02-25 23:37:32 +03:00
|
|
|
`P.bindField` \fld@IR.GraphQLField {IR._fArguments = args, IR._fSelectionSet = selSet, IR._fName = fname} -> do
|
2021-12-22 02:14:56 +03:00
|
|
|
let remoteArgs =
|
|
|
|
Map.toList args <&> \(argName, argVal) -> IR.RemoteFieldArgument argName $ P.GraphQLValue argVal
|
|
|
|
let resultCustomizer =
|
|
|
|
applyFieldCalls fieldCalls $
|
|
|
|
applyAliasMapping (singletonAliasMapping fname (fcName $ NE.last fieldCalls)) $
|
|
|
|
makeResultCustomizer remoteSchemaCustomizer fld
|
|
|
|
pure $
|
|
|
|
IR.RemoteSchemaSelect
|
|
|
|
{ IR._rselArgs = remoteArgs,
|
|
|
|
IR._rselResultCustomizer = resultCustomizer,
|
|
|
|
IR._rselSelection = selSet,
|
|
|
|
IR._rselFieldCall = fieldCalls,
|
|
|
|
IR._rselRemoteSchema = _rrfiRemoteSchema
|
|
|
|
}
|
|
|
|
where
|
|
|
|
-- Apply parent field calls so that the result customizer modifies the nested field
|
|
|
|
applyFieldCalls :: NonEmpty FieldCall -> ResultCustomizer -> ResultCustomizer
|
|
|
|
applyFieldCalls fieldCalls resultCustomizer =
|
|
|
|
foldr (modifyFieldByName . fcName) resultCustomizer $ NE.init fieldCalls
|
|
|
|
|
|
|
|
lookupNestedFieldType' ::
|
|
|
|
(MonadSchema n m, MonadError QErr m) =>
|
|
|
|
G.Name ->
|
|
|
|
RemoteSchemaIntrospection ->
|
|
|
|
FieldCall ->
|
|
|
|
m G.GType
|
|
|
|
lookupNestedFieldType' parentTypeName remoteSchemaIntrospection (FieldCall fcName _) =
|
|
|
|
case lookupObject remoteSchemaIntrospection parentTypeName of
|
|
|
|
Nothing -> throw400 RemoteSchemaError $ "object with name " <> parentTypeName <<> " not found"
|
|
|
|
Just G.ObjectTypeDefinition {..} ->
|
|
|
|
case find ((== fcName) . G._fldName) _otdFieldsDefinition of
|
|
|
|
Nothing -> throw400 RemoteSchemaError $ "field with name " <> fcName <<> " not found"
|
|
|
|
Just G.FieldDefinition {..} -> pure _fldType
|
|
|
|
|
|
|
|
lookupNestedFieldType ::
|
|
|
|
(MonadSchema n m, MonadError QErr m) =>
|
|
|
|
G.Name ->
|
|
|
|
RemoteSchemaIntrospection ->
|
|
|
|
NonEmpty FieldCall ->
|
|
|
|
m G.GType
|
|
|
|
lookupNestedFieldType parentTypeName remoteSchemaIntrospection (fieldCall :| rest) = do
|
|
|
|
fieldType <- lookupNestedFieldType' parentTypeName remoteSchemaIntrospection fieldCall
|
|
|
|
case NE.nonEmpty rest of
|
|
|
|
Nothing -> pure fieldType
|
|
|
|
Just rest' -> do
|
|
|
|
lookupNestedFieldType (G.getBaseType fieldType) remoteSchemaIntrospection rest'
|
|
|
|
|
|
|
|
-- | Parser(s) for remote relationship fields to a database table.
|
|
|
|
-- Note that when the target is a database table, an array relationship
|
|
|
|
-- declaration would have the '_aggregate' field in addition to the array
|
|
|
|
-- relationship field, hence [FieldParser ...] instead of 'FieldParser'
|
|
|
|
remoteRelationshipToSourceField ::
|
|
|
|
forall r m n tgt.
|
|
|
|
(MonadBuildSchemaBase r m n, BackendSchema tgt) =>
|
Remove circular dependency in schema building code
### Description
The main goal of this PR is, as stated, to remove the circular dependency in the schema building code. This cycle arises from the existence of remote relationships: when we build the schema for a source A, a remote relationship might force us to jump to the schema of a source B, or some remote schema. As a result, we end up having to do a dispatch from a "leaf" of the schema, similar to the one done at the root. In turn, this forces us to carry along in the schema a lot of information required for that dispatch, AND it forces us to import the instances in scope, creating an import loop.
As discussed in #4489, this PR implements the "dependency injection" solution: we pass to the schema a function to call to do the dispatch, and to get a generated field for a remote relationship. That way, this function can be chosen at the root level, and the leaves need not be aware of the overall context.
This PR grew a bit bigger than that, however; in an attempt to try and remove the `SourceCache` from the schema altogether, it changed a lot of functions across the schema building code, to thread along the `SourceInfo b` of the source being built. This avoids having to do cache lookups within a given source. A few cases remain, such as relay, that we might try to tackle in a subsequent PR.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/4557
GitOrigin-RevId: 9388e48372877520a72a9fd1677005df9f7b2d72
2022-05-27 20:21:22 +03:00
|
|
|
SourceCache ->
|
2021-12-22 02:14:56 +03:00
|
|
|
RemoteSourceFieldInfo tgt ->
|
2022-05-31 01:07:02 +03:00
|
|
|
m [FieldParser n (IR.RemoteSourceSelect (IR.RemoteRelationshipField IR.UnpreparedValue) IR.UnpreparedValue tgt)]
|
Remove circular dependency in schema building code
### Description
The main goal of this PR is, as stated, to remove the circular dependency in the schema building code. This cycle arises from the existence of remote relationships: when we build the schema for a source A, a remote relationship might force us to jump to the schema of a source B, or some remote schema. As a result, we end up having to do a dispatch from a "leaf" of the schema, similar to the one done at the root. In turn, this forces us to carry along in the schema a lot of information required for that dispatch, AND it forces us to import the instances in scope, creating an import loop.
As discussed in #4489, this PR implements the "dependency injection" solution: we pass to the schema a function to call to do the dispatch, and to get a generated field for a remote relationship. That way, this function can be chosen at the root level, and the leaves need not be aware of the overall context.
This PR grew a bit bigger than that, however; in an attempt to try and remove the `SourceCache` from the schema altogether, it changed a lot of functions across the schema building code, to thread along the `SourceInfo b` of the source being built. This avoids having to do cache lookups within a given source. A few cases remain, such as relay, that we might try to tackle in a subsequent PR.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/4557
GitOrigin-RevId: 9388e48372877520a72a9fd1677005df9f7b2d72
2022-05-27 20:21:22 +03:00
|
|
|
remoteRelationshipToSourceField sourceCache RemoteSourceFieldInfo {..} =
|
2022-05-26 14:54:30 +03:00
|
|
|
withTypenameCustomization (mkCustomizedTypename (Just _rsfiSourceCustomization) HasuraCase) do
|
Remove circular dependency in schema building code
### Description
The main goal of this PR is, as stated, to remove the circular dependency in the schema building code. This cycle arises from the existence of remote relationships: when we build the schema for a source A, a remote relationship might force us to jump to the schema of a source B, or some remote schema. As a result, we end up having to do a dispatch from a "leaf" of the schema, similar to the one done at the root. In turn, this forces us to carry along in the schema a lot of information required for that dispatch, AND it forces us to import the instances in scope, creating an import loop.
As discussed in #4489, this PR implements the "dependency injection" solution: we pass to the schema a function to call to do the dispatch, and to get a generated field for a remote relationship. That way, this function can be chosen at the root level, and the leaves need not be aware of the overall context.
This PR grew a bit bigger than that, however; in an attempt to try and remove the `SourceCache` from the schema altogether, it changed a lot of functions across the schema building code, to thread along the `SourceInfo b` of the source being built. This avoids having to do cache lookups within a given source. A few cases remain, such as relay, that we might try to tackle in a subsequent PR.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/4557
GitOrigin-RevId: 9388e48372877520a72a9fd1677005df9f7b2d72
2022-05-27 20:21:22 +03:00
|
|
|
sourceInfo <-
|
|
|
|
onNothing (unsafeSourceInfo @tgt =<< Map.lookup _rsfiSource sourceCache) $
|
|
|
|
throw500 $ "source not found " <> dquote _rsfiSource
|
|
|
|
tableInfo <- askTableInfo sourceInfo _rsfiTable
|
2021-12-22 02:14:56 +03:00
|
|
|
fieldName <- textToName $ relNameToTxt _rsfiName
|
|
|
|
maybePerms <- tableSelectPermissions @tgt tableInfo
|
|
|
|
case maybePerms of
|
|
|
|
Nothing -> pure []
|
|
|
|
Just tablePerms -> do
|
|
|
|
parsers <- case _rsfiType of
|
|
|
|
ObjRel -> do
|
Remove circular dependency in schema building code
### Description
The main goal of this PR is, as stated, to remove the circular dependency in the schema building code. This cycle arises from the existence of remote relationships: when we build the schema for a source A, a remote relationship might force us to jump to the schema of a source B, or some remote schema. As a result, we end up having to do a dispatch from a "leaf" of the schema, similar to the one done at the root. In turn, this forces us to carry along in the schema a lot of information required for that dispatch, AND it forces us to import the instances in scope, creating an import loop.
As discussed in #4489, this PR implements the "dependency injection" solution: we pass to the schema a function to call to do the dispatch, and to get a generated field for a remote relationship. That way, this function can be chosen at the root level, and the leaves need not be aware of the overall context.
This PR grew a bit bigger than that, however; in an attempt to try and remove the `SourceCache` from the schema altogether, it changed a lot of functions across the schema building code, to thread along the `SourceInfo b` of the source being built. This avoids having to do cache lookups within a given source. A few cases remain, such as relay, that we might try to tackle in a subsequent PR.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/4557
GitOrigin-RevId: 9388e48372877520a72a9fd1677005df9f7b2d72
2022-05-27 20:21:22 +03:00
|
|
|
selectionSetParserM <- tableSelectionSet sourceInfo tableInfo
|
Role-invariant schema constructors
We build the GraphQL schema by combining building blocks such as `tableSelectionSet` and `columnParser`. These building blocks individually build `{InputFields,Field,}Parser` objects. Those object specify the valid GraphQL schema.
Since the GraphQL schema is role-dependent, at some point we need to know what fragment of the GraphQL schema a specific role is allowed to access, and this is stored in `{Sel,Upd,Ins,Del}PermInfo` objects.
We have passed around these permission objects as function arguments to the schema building blocks since we first started dealing with permissions during the PDV refactor - see hasura/graphql-engine@5168b99e463199b1934d8645bd6cd37eddb64ae1 in hasura/graphql-engine#4111. This means that, for instance, `tableSelectionSet` has as its type:
```haskell
tableSelectionSet ::
forall b r m n.
MonadBuildSchema b r m n =>
SourceName ->
TableInfo b ->
SelPermInfo b ->
m (Parser 'Output n (AnnotatedFields b))
```
There are three reasons to change this.
1. We often pass a `Maybe (xPermInfo b)` instead of a proper `xPermInfo b`, and it's not clear what the intended semantics of this is. Some potential improvements on the data types involved are discussed in issue hasura/graphql-engine-mono#3125.
2. In most cases we also already pass a `TableInfo b`, and together with the `MonadRole` that is usually also in scope, this means that we could look up the required permissions regardless: so passing the permissions explicitly undermines the "single source of truth" principle. Breaking this principle also makes the code more difficult to read.
3. We are working towards role-based parsers (see hasura/graphql-engine-mono#2711), where the `{InputFields,Field,}Parser` objects are constructed in a role-invariant way, so that we have a single object that can be used for all roles. In particular, this means that the schema building blocks _need_ to be constructed in a role-invariant way. While this PR doesn't accomplish that, it does reduce the amount of role-specific arguments being passed, thus fixing hasura/graphql-engine-mono#3068.
Concretely, this PR simply drops the `xPermInfo b` argument from almost all schema building blocks. Instead these objects are looked up from the `TableInfo b` as-needed. The resulting code is considerably simpler and shorter.
One way to interpret this change is as follows. Before this PR, we figured out permissions at the top-level in `Hasura.GraphQL.Schema`, passing down the obtained `xPermInfo` objects as required. After this PR, we have a bottom-up approach where the schema building blocks themselves decide whether they want to be included for a particular role.
So this moves some permission logic out of `Hasura.GraphQL.Schema`, which is very complex.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/3608
GitOrigin-RevId: 51a744f34ec7d57bc8077667ae7f9cb9c4f6c962
2022-02-17 11:16:20 +03:00
|
|
|
pure $ case selectionSetParserM of
|
|
|
|
Nothing -> []
|
|
|
|
Just selectionSetParser ->
|
|
|
|
pure $
|
|
|
|
subselection_ fieldName Nothing selectionSetParser <&> \fields ->
|
|
|
|
IR.SourceRelationshipObject $
|
|
|
|
IR.AnnObjectSelectG fields _rsfiTable $ IR._tpFilter $ tablePermissionsInfo tablePerms
|
2021-12-22 02:14:56 +03:00
|
|
|
ArrRel -> do
|
2022-04-18 22:43:00 +03:00
|
|
|
let aggFieldName = fieldName <> G.__aggregate
|
Remove circular dependency in schema building code
### Description
The main goal of this PR is, as stated, to remove the circular dependency in the schema building code. This cycle arises from the existence of remote relationships: when we build the schema for a source A, a remote relationship might force us to jump to the schema of a source B, or some remote schema. As a result, we end up having to do a dispatch from a "leaf" of the schema, similar to the one done at the root. In turn, this forces us to carry along in the schema a lot of information required for that dispatch, AND it forces us to import the instances in scope, creating an import loop.
As discussed in #4489, this PR implements the "dependency injection" solution: we pass to the schema a function to call to do the dispatch, and to get a generated field for a remote relationship. That way, this function can be chosen at the root level, and the leaves need not be aware of the overall context.
This PR grew a bit bigger than that, however; in an attempt to try and remove the `SourceCache` from the schema altogether, it changed a lot of functions across the schema building code, to thread along the `SourceInfo b` of the source being built. This avoids having to do cache lookups within a given source. A few cases remain, such as relay, that we might try to tackle in a subsequent PR.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/4557
GitOrigin-RevId: 9388e48372877520a72a9fd1677005df9f7b2d72
2022-05-27 20:21:22 +03:00
|
|
|
selectionSetParser <- selectTable sourceInfo tableInfo fieldName Nothing
|
|
|
|
aggSelectionSetParser <- selectTableAggregate sourceInfo tableInfo aggFieldName Nothing
|
2021-12-22 02:14:56 +03:00
|
|
|
pure $
|
|
|
|
catMaybes
|
Role-invariant schema constructors
We build the GraphQL schema by combining building blocks such as `tableSelectionSet` and `columnParser`. These building blocks individually build `{InputFields,Field,}Parser` objects. Those object specify the valid GraphQL schema.
Since the GraphQL schema is role-dependent, at some point we need to know what fragment of the GraphQL schema a specific role is allowed to access, and this is stored in `{Sel,Upd,Ins,Del}PermInfo` objects.
We have passed around these permission objects as function arguments to the schema building blocks since we first started dealing with permissions during the PDV refactor - see hasura/graphql-engine@5168b99e463199b1934d8645bd6cd37eddb64ae1 in hasura/graphql-engine#4111. This means that, for instance, `tableSelectionSet` has as its type:
```haskell
tableSelectionSet ::
forall b r m n.
MonadBuildSchema b r m n =>
SourceName ->
TableInfo b ->
SelPermInfo b ->
m (Parser 'Output n (AnnotatedFields b))
```
There are three reasons to change this.
1. We often pass a `Maybe (xPermInfo b)` instead of a proper `xPermInfo b`, and it's not clear what the intended semantics of this is. Some potential improvements on the data types involved are discussed in issue hasura/graphql-engine-mono#3125.
2. In most cases we also already pass a `TableInfo b`, and together with the `MonadRole` that is usually also in scope, this means that we could look up the required permissions regardless: so passing the permissions explicitly undermines the "single source of truth" principle. Breaking this principle also makes the code more difficult to read.
3. We are working towards role-based parsers (see hasura/graphql-engine-mono#2711), where the `{InputFields,Field,}Parser` objects are constructed in a role-invariant way, so that we have a single object that can be used for all roles. In particular, this means that the schema building blocks _need_ to be constructed in a role-invariant way. While this PR doesn't accomplish that, it does reduce the amount of role-specific arguments being passed, thus fixing hasura/graphql-engine-mono#3068.
Concretely, this PR simply drops the `xPermInfo b` argument from almost all schema building blocks. Instead these objects are looked up from the `TableInfo b` as-needed. The resulting code is considerably simpler and shorter.
One way to interpret this change is as follows. Before this PR, we figured out permissions at the top-level in `Hasura.GraphQL.Schema`, passing down the obtained `xPermInfo` objects as required. After this PR, we have a bottom-up approach where the schema building blocks themselves decide whether they want to be included for a particular role.
So this moves some permission logic out of `Hasura.GraphQL.Schema`, which is very complex.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/3608
GitOrigin-RevId: 51a744f34ec7d57bc8077667ae7f9cb9c4f6c962
2022-02-17 11:16:20 +03:00
|
|
|
[ selectionSetParser <&> fmap IR.SourceRelationshipArray,
|
2021-12-22 02:14:56 +03:00
|
|
|
aggSelectionSetParser <&> fmap IR.SourceRelationshipArrayAggregate
|
|
|
|
]
|
|
|
|
pure $
|
|
|
|
parsers <&> fmap \select ->
|
|
|
|
IR.RemoteSourceSelect _rsfiSource _rsfiSourceConfig select _rsfiMapping
|