graphql-engine/server/src-lib/Hasura/GraphQL/Execute/Backend.hs

Ignoring revisions in .git-blame-ignore-revs. Click here to bypass and see the normal blame view.

271 lines
9.8 KiB
Haskell
Raw Normal View History

module Hasura.GraphQL.Execute.Backend where
import Control.Monad.Trans.Control (MonadBaseControl)
import Data.Aeson qualified as J
import Data.Aeson.Casing qualified as J
import Data.Aeson.Ordered qualified as JO
import Data.Kind (Type)
import Data.Tagged
import Data.Text.Extended
import Data.Text.NonEmpty (mkNonEmptyTextUnsafe)
import Database.PG.Query qualified as Q
import Hasura.Base.Error
import Hasura.EncJSON
import Hasura.GraphQL.Execute.Action.Types (ActionExecutionPlan)
import Hasura.GraphQL.Execute.LiveQuery.Plan
import Hasura.GraphQL.Execute.RemoteJoin.Types
import Hasura.GraphQL.Namespace (RootFieldAlias, RootFieldMap)
import Hasura.GraphQL.Parser hiding (Type)
import Hasura.GraphQL.Transport.HTTP.Protocol qualified as GH
import Hasura.Metadata.Class
import Hasura.Prelude
import Hasura.QueryTags
import Hasura.RQL.DDL.Schema.Cache (CacheRWT)
import Hasura.RQL.IR
import Hasura.RQL.Types.Action
import Hasura.RQL.Types.Backend
import Hasura.RQL.Types.Column (ColumnType, fromCol)
import Hasura.RQL.Types.Common
import Hasura.RQL.Types.QueryTags (QueryTagsConfig)
import Hasura.RQL.Types.RemoteSchema
import Hasura.RQL.Types.ResultCustomization
import Hasura.RQL.Types.Run (RunT (..))
import Hasura.RQL.Types.SchemaCache.Build (MetadataT (..))
import Hasura.SQL.AnyBackend qualified as AB
import Hasura.SQL.Backend
import Hasura.Session
import Hasura.Tracing (TraceT)
import Language.GraphQL.Draft.Syntax qualified as G
import Network.HTTP.Types qualified as HTTP
-- | This typeclass enacapsulates how a given backend translates a root field into an execution
-- plan. For now, each root field maps to one execution step, but in the future, when we have
-- a client-side dataloader, each root field might translate into a multi-step plan.
class
( Backend b,
ToTxt (MultiplexedQuery b),
Monad (ExecutionMonad b)
) =>
BackendExecute (b :: BackendType)
where
-- generated query information
type PreparedQuery b :: Type
type MultiplexedQuery b :: Type
type ExecutionMonad b :: Type -> Type
-- execution plan generation
mkDBQueryPlan ::
forall m.
( MonadError QErr m,
MonadQueryTags m,
MonadReader QueryTagsComment m
) =>
UserInfo ->
SourceName ->
SourceConfig b ->
QueryDB b (Const Void) (UnpreparedValue b) ->
m (DBStepInfo b)
mkDBMutationPlan ::
forall m.
( MonadError QErr m,
MonadQueryTags m,
MonadReader QueryTagsComment m
) =>
UserInfo ->
Bool ->
SourceName ->
SourceConfig b ->
MutationDB b (Const Void) (UnpreparedValue b) ->
m (DBStepInfo b)
mkDBSubscriptionPlan ::
forall m.
( MonadError QErr m,
MonadIO m,
server/mssql: add cascade to mssql_run_sql <!-- Thank you for ss in the Title above ^ --> ## Description <!-- Please fill thier. --> <!-- Describe the changes from a user's perspective --> We don't have dependency reporting mechanism for `mssql_run_sql` API i.e when a database object (table, column etc.) is dropped through the API we should raise an exception if any dependencies (relationships, permissions etc.) with the database object exists in the metadata. This PR addresses the above mentioned problem by -> Integrating transaction to the API to rollback the SQL query execution if dependencies exists and exception is thrown -> Accepting `cascade` optional field in the API payload to drop the dependencies, if any -> Accepting `check_metadata_consistency` optional field to bypass (if value set to `false`) the dependency check ### Related Issues <!-- Please make surt title --> <!-- Add the issue number below (e.g. #234) --> Close #1853 ### Solution and Design <!-- How is this iss --> <!-- It's better if we elaborate --> The design/solution follows the `run_sql` API implementation for Postgres backend. ### Steps to test and verify <!-- If this is a fehis is a bug-fix, how do we verify the fix? --> - Create author - article tables and track them - Defined object and array relationships - Try to drop the article table without cascade or cascade set to `false` - The server should raise the relationship dependency exists exception ## Changelog - ✅ `CHANGELOG.md` is updated with user-facing content relevant to this PR. If no changelog is required, then add the `no-changelog-required` label. ## Affected components <!-- Remove non-affected components from the list --> - ✅ Server - ❎ Console - ❎ CLI - ❎ Docs - ❎ Community Content - ❎ Build System - ✅ Tests - ❎ Other (list it) PR-URL: https://github.com/hasura/graphql-engine-mono/pull/2636 GitOrigin-RevId: 0ab152295394056c4ca6f02923142a1658ad25dc
2021-10-22 17:49:15 +03:00
MonadBaseControl IO m,
MonadReader QueryTagsComment m
) =>
UserInfo ->
SourceName ->
SourceConfig b ->
Maybe G.Name ->
RootFieldMap (QueryDB b (Const Void) (UnpreparedValue b)) ->
m (LiveQueryPlan b (MultiplexedQuery b))
mkDBQueryExplain ::
forall m.
( MonadError QErr m
) =>
RootFieldAlias ->
UserInfo ->
SourceName ->
SourceConfig b ->
QueryDB b (Const Void) (UnpreparedValue b) ->
m (AB.AnyBackend DBStepInfo)
mkLiveQueryExplain ::
( MonadError QErr m,
MonadIO m,
MonadBaseControl IO m
) =>
LiveQueryPlan b (MultiplexedQuery b) ->
m LiveQueryPlanExplanation
mkDBRemoteRelationshipPlan ::
forall m.
( MonadError QErr m,
MonadQueryTags m
) =>
UserInfo ->
SourceName ->
SourceConfig b ->
-- | List of json objects, each of which becomes a row of the table.
NonEmpty J.Object ->
-- | The above objects have this schema.
HashMap FieldName (Column b, ScalarType b) ->
-- | This is a field name from the lhs that *has* to be selected in the
-- response along with the relationship.
FieldName ->
(FieldName, SourceRelationshipSelection b (Const Void) UnpreparedValue) ->
m (DBStepInfo b)
-- | This is a helper function to convert a remote source's relationship to a
-- normal relationship to a temporary table. This function can be used to
-- implement executeRemoteRelationship function in databases which support
-- constructing a temporary table for a list of json objects.
convertRemoteSourceRelationship ::
forall b.
(Backend b) =>
-- | Join columns for the relationship
HashMap (Column b) (Column b) ->
-- | The LHS of the join, this is the expression which selects from json
-- objects
SelectFromG b (UnpreparedValue b) ->
-- | This is the __argument__ id column, that needs to be added to the response
-- This is used by by the remote joins processing logic to convert the
-- response from upstream to join indices
Column b ->
-- | This is the type of the __argument__ id column
ColumnType b ->
-- | The relationship column and its name (how it should be selected in the
-- response)
(FieldName, SourceRelationshipSelection b (Const Void) UnpreparedValue) ->
QueryDB b (Const Void) (UnpreparedValue b)
convertRemoteSourceRelationship
columnMapping
selectFrom
argumentIdColumn
argumentIdColumnType
(relationshipName, relationship) =
QDBMultipleRows simpleSelect
where
-- TODO: FieldName should have also been a wrapper around NonEmptyText
relName = RelName $ mkNonEmptyTextUnsafe $ getFieldNameTxt relationshipName
relationshipField = case relationship of
SourceRelationshipObject s ->
AFObjectRelation $ AnnRelationSelectG relName columnMapping s
SourceRelationshipArray s ->
AFArrayRelation $ ASSimple $ AnnRelationSelectG relName columnMapping s
SourceRelationshipArrayAggregate s ->
AFArrayRelation $ ASAggregate $ AnnRelationSelectG relName columnMapping s
argumentIdField =
( fromCol @b argumentIdColumn,
AFColumn $
AnnColumnField
{ _acfColumn = argumentIdColumn,
_acfType = argumentIdColumnType,
_acfAsText = False,
_acfOp = Nothing,
_acfCaseBoolExpression = Nothing
}
)
simpleSelect =
AnnSelectG
{ _asnFields = [argumentIdField, (relationshipName, relationshipField)],
_asnFrom = selectFrom,
_asnPerm = TablePerm annBoolExpTrue Nothing,
_asnArgs = noSelectArgs,
_asnStrfyNum = False
}
data DBStepInfo b = DBStepInfo
{ dbsiSourceName :: SourceName,
dbsiSourceConfig :: SourceConfig b,
dbsiPreparedQuery :: Maybe (PreparedQuery b),
dbsiAction :: ExecutionMonad b EncJSON
}
-- | The result of an explain query: for a given root field (denoted by its name): the generated SQL
-- query, and the detailed explanation obtained from the database (if any). We mostly use this type
-- as an intermediary step, and immediately tranform any value we obtain into an equivalent JSON
-- representation.
data ExplainPlan = ExplainPlan
{ _fpField :: !RootFieldAlias,
_fpSql :: !(Maybe Text),
_fpPlan :: !(Maybe [Text])
}
deriving (Show, Eq, Generic)
instance J.ToJSON ExplainPlan where
toJSON = J.genericToJSON $ J.aesonPrefix J.camelCase
-- | One execution step to processing a GraphQL query (e.g. one root field).
data ExecutionStep where
server: support remote relationships on SQL Server and BigQuery (#1497) Remote relationships are now supported on SQL Server and BigQuery. The major change though is the re-architecture of remote join execution logic. Prior to this PR, each backend is responsible for processing the remote relationships that are part of their AST. This is not ideal as there is nothing specific about a remote join's execution that ties it to a backend. The only backend specific part is whether or not the specification of the remote relationship is valid (i.e, we'll need to validate whether the scalars are compatible). The approach now changes to this: 1. Before delegating the AST to the backend, we traverse the AST, collect all the remote joins while modifying the AST to add necessary join fields where needed. 1. Once the remote joins are collected from the AST, the database call is made to fetch the response. The necessary data for the remote join(s) is collected from the database's response and one or more remote schema calls are constructed as necessary. 1. The remote schema calls are then executed and the data from the database and from the remote schemas is joined to produce the final response. ### Known issues 1. Ideally the traversal of the IR to collect remote joins should return an AST which does not include remote join fields. This operation can be type safe but isn't taken up as part of the PR. 1. There is a lot of code duplication between `Transport/HTTP.hs` and `Transport/Websocket.hs` which needs to be fixed ASAP. This too hasn't been taken up by this PR. 1. The type which represents the execution plan is only modified to handle our current remote joins and as such it will have to be changed to accommodate general remote joins. 1. Use of lenses would have reduced the boilerplate code to collect remote joins from the base AST. 1. The current remote join logic assumes that the join columns of a remote relationship appear with their names in the database response. This however is incorrect as they could be aliased. This can be taken up by anyone, I've left a comment in the code. ### Notes to the reviewers I think it is best reviewed commit by commit. 1. The first one is very straight forward. 1. The second one refactors the remote join execution logic but other than moving things around, it doesn't change the user facing functionality. This moves Postgres specific parts to `Backends/Postgres` module from `Execute`. Some IR related code to `Hasura.RQL.IR` module. Simplifies various type class function signatures as a backend doesn't have to handle remote joins anymore 1. The third one fixes partial case matches that for some weird reason weren't shown as warnings before this refactor 1. The fourth one generalizes the validation logic of remote relationships and implements `scalarTypeGraphQLName` function on SQL Server and BigQuery which is used by the validation logic. This enables remote relationships on BigQuery and SQL Server. https://github.com/hasura/graphql-engine-mono/pull/1497 GitOrigin-RevId: 77dd8eed326602b16e9a8496f52f46d22b795598
2021-06-11 06:26:50 +03:00
-- | A query to execute against the database
ExecStepDB ::
HTTP.ResponseHeaders ->
AB.AnyBackend DBStepInfo ->
Maybe RemoteJoins ->
ExecutionStep
server: support remote relationships on SQL Server and BigQuery (#1497) Remote relationships are now supported on SQL Server and BigQuery. The major change though is the re-architecture of remote join execution logic. Prior to this PR, each backend is responsible for processing the remote relationships that are part of their AST. This is not ideal as there is nothing specific about a remote join's execution that ties it to a backend. The only backend specific part is whether or not the specification of the remote relationship is valid (i.e, we'll need to validate whether the scalars are compatible). The approach now changes to this: 1. Before delegating the AST to the backend, we traverse the AST, collect all the remote joins while modifying the AST to add necessary join fields where needed. 1. Once the remote joins are collected from the AST, the database call is made to fetch the response. The necessary data for the remote join(s) is collected from the database's response and one or more remote schema calls are constructed as necessary. 1. The remote schema calls are then executed and the data from the database and from the remote schemas is joined to produce the final response. ### Known issues 1. Ideally the traversal of the IR to collect remote joins should return an AST which does not include remote join fields. This operation can be type safe but isn't taken up as part of the PR. 1. There is a lot of code duplication between `Transport/HTTP.hs` and `Transport/Websocket.hs` which needs to be fixed ASAP. This too hasn't been taken up by this PR. 1. The type which represents the execution plan is only modified to handle our current remote joins and as such it will have to be changed to accommodate general remote joins. 1. Use of lenses would have reduced the boilerplate code to collect remote joins from the base AST. 1. The current remote join logic assumes that the join columns of a remote relationship appear with their names in the database response. This however is incorrect as they could be aliased. This can be taken up by anyone, I've left a comment in the code. ### Notes to the reviewers I think it is best reviewed commit by commit. 1. The first one is very straight forward. 1. The second one refactors the remote join execution logic but other than moving things around, it doesn't change the user facing functionality. This moves Postgres specific parts to `Backends/Postgres` module from `Execute`. Some IR related code to `Hasura.RQL.IR` module. Simplifies various type class function signatures as a backend doesn't have to handle remote joins anymore 1. The third one fixes partial case matches that for some weird reason weren't shown as warnings before this refactor 1. The fourth one generalizes the validation logic of remote relationships and implements `scalarTypeGraphQLName` function on SQL Server and BigQuery which is used by the validation logic. This enables remote relationships on BigQuery and SQL Server. https://github.com/hasura/graphql-engine-mono/pull/1497 GitOrigin-RevId: 77dd8eed326602b16e9a8496f52f46d22b795598
2021-06-11 06:26:50 +03:00
-- | Execute an action
ExecStepAction ::
ActionExecutionPlan ->
ActionsInfo ->
Maybe RemoteJoins ->
ExecutionStep
server: support remote relationships on SQL Server and BigQuery (#1497) Remote relationships are now supported on SQL Server and BigQuery. The major change though is the re-architecture of remote join execution logic. Prior to this PR, each backend is responsible for processing the remote relationships that are part of their AST. This is not ideal as there is nothing specific about a remote join's execution that ties it to a backend. The only backend specific part is whether or not the specification of the remote relationship is valid (i.e, we'll need to validate whether the scalars are compatible). The approach now changes to this: 1. Before delegating the AST to the backend, we traverse the AST, collect all the remote joins while modifying the AST to add necessary join fields where needed. 1. Once the remote joins are collected from the AST, the database call is made to fetch the response. The necessary data for the remote join(s) is collected from the database's response and one or more remote schema calls are constructed as necessary. 1. The remote schema calls are then executed and the data from the database and from the remote schemas is joined to produce the final response. ### Known issues 1. Ideally the traversal of the IR to collect remote joins should return an AST which does not include remote join fields. This operation can be type safe but isn't taken up as part of the PR. 1. There is a lot of code duplication between `Transport/HTTP.hs` and `Transport/Websocket.hs` which needs to be fixed ASAP. This too hasn't been taken up by this PR. 1. The type which represents the execution plan is only modified to handle our current remote joins and as such it will have to be changed to accommodate general remote joins. 1. Use of lenses would have reduced the boilerplate code to collect remote joins from the base AST. 1. The current remote join logic assumes that the join columns of a remote relationship appear with their names in the database response. This however is incorrect as they could be aliased. This can be taken up by anyone, I've left a comment in the code. ### Notes to the reviewers I think it is best reviewed commit by commit. 1. The first one is very straight forward. 1. The second one refactors the remote join execution logic but other than moving things around, it doesn't change the user facing functionality. This moves Postgres specific parts to `Backends/Postgres` module from `Execute`. Some IR related code to `Hasura.RQL.IR` module. Simplifies various type class function signatures as a backend doesn't have to handle remote joins anymore 1. The third one fixes partial case matches that for some weird reason weren't shown as warnings before this refactor 1. The fourth one generalizes the validation logic of remote relationships and implements `scalarTypeGraphQLName` function on SQL Server and BigQuery which is used by the validation logic. This enables remote relationships on BigQuery and SQL Server. https://github.com/hasura/graphql-engine-mono/pull/1497 GitOrigin-RevId: 77dd8eed326602b16e9a8496f52f46d22b795598
2021-06-11 06:26:50 +03:00
-- | A graphql query to execute against a remote schema
ExecStepRemote ::
!RemoteSchemaInfo ->
!ResultCustomizer ->
!GH.GQLReqOutgoing ->
ExecutionStep
server: support remote relationships on SQL Server and BigQuery (#1497) Remote relationships are now supported on SQL Server and BigQuery. The major change though is the re-architecture of remote join execution logic. Prior to this PR, each backend is responsible for processing the remote relationships that are part of their AST. This is not ideal as there is nothing specific about a remote join's execution that ties it to a backend. The only backend specific part is whether or not the specification of the remote relationship is valid (i.e, we'll need to validate whether the scalars are compatible). The approach now changes to this: 1. Before delegating the AST to the backend, we traverse the AST, collect all the remote joins while modifying the AST to add necessary join fields where needed. 1. Once the remote joins are collected from the AST, the database call is made to fetch the response. The necessary data for the remote join(s) is collected from the database's response and one or more remote schema calls are constructed as necessary. 1. The remote schema calls are then executed and the data from the database and from the remote schemas is joined to produce the final response. ### Known issues 1. Ideally the traversal of the IR to collect remote joins should return an AST which does not include remote join fields. This operation can be type safe but isn't taken up as part of the PR. 1. There is a lot of code duplication between `Transport/HTTP.hs` and `Transport/Websocket.hs` which needs to be fixed ASAP. This too hasn't been taken up by this PR. 1. The type which represents the execution plan is only modified to handle our current remote joins and as such it will have to be changed to accommodate general remote joins. 1. Use of lenses would have reduced the boilerplate code to collect remote joins from the base AST. 1. The current remote join logic assumes that the join columns of a remote relationship appear with their names in the database response. This however is incorrect as they could be aliased. This can be taken up by anyone, I've left a comment in the code. ### Notes to the reviewers I think it is best reviewed commit by commit. 1. The first one is very straight forward. 1. The second one refactors the remote join execution logic but other than moving things around, it doesn't change the user facing functionality. This moves Postgres specific parts to `Backends/Postgres` module from `Execute`. Some IR related code to `Hasura.RQL.IR` module. Simplifies various type class function signatures as a backend doesn't have to handle remote joins anymore 1. The third one fixes partial case matches that for some weird reason weren't shown as warnings before this refactor 1. The fourth one generalizes the validation logic of remote relationships and implements `scalarTypeGraphQLName` function on SQL Server and BigQuery which is used by the validation logic. This enables remote relationships on BigQuery and SQL Server. https://github.com/hasura/graphql-engine-mono/pull/1497 GitOrigin-RevId: 77dd8eed326602b16e9a8496f52f46d22b795598
2021-06-11 06:26:50 +03:00
-- | Output a plain JSON object
ExecStepRaw ::
JO.Value ->
ExecutionStep
-- | The series of steps that need to be executed for a given query. For now, those steps are all
-- independent. In the future, when we implement a client-side dataloader and generalized joins,
-- this will need to be changed into an annotated tree.
type ExecutionPlan = RootFieldMap ExecutionStep
class (Monad m) => MonadQueryTags m where
-- | Creates Query Tags. These are appended to the Generated SQL.
-- Helps users to use native database monitoring tools to get some 'application-context'.
createQueryTags ::
QueryTagsAttributes -> Maybe QueryTagsConfig -> Tagged m QueryTagsComment
instance (MonadQueryTags m) => MonadQueryTags (ReaderT r m) where
createQueryTags qtSourceConfig attr = retag (createQueryTags @m qtSourceConfig attr) :: Tagged (ReaderT r m) QueryTagsComment
instance (MonadQueryTags m) => MonadQueryTags (ExceptT e m) where
createQueryTags qtSourceConfig attr = retag (createQueryTags @m qtSourceConfig attr) :: Tagged (ExceptT e m) QueryTagsComment
instance (MonadQueryTags m) => MonadQueryTags (TraceT m) where
createQueryTags qtSourceConfig attr = retag (createQueryTags @m qtSourceConfig attr) :: Tagged (TraceT m) QueryTagsComment
instance (MonadQueryTags m) => MonadQueryTags (MetadataStorageT m) where
createQueryTags qtSourceConfig attr = retag (createQueryTags @m qtSourceConfig attr) :: Tagged (MetadataStorageT m) QueryTagsComment
instance (MonadQueryTags m) => MonadQueryTags (Q.TxET QErr m) where
createQueryTags qtSourceConfig attr = retag (createQueryTags @m qtSourceConfig attr) :: Tagged (Q.TxET QErr m) QueryTagsComment
instance (MonadQueryTags m) => MonadQueryTags (MetadataT m) where
createQueryTags qtSourceConfig attr = retag (createQueryTags @m qtSourceConfig attr) :: Tagged (MetadataT m) QueryTagsComment
instance (MonadQueryTags m) => MonadQueryTags (CacheRWT m) where
createQueryTags qtSourceConfig attr = retag (createQueryTags @m qtSourceConfig attr) :: Tagged (CacheRWT m) QueryTagsComment
instance (MonadQueryTags m) => MonadQueryTags (RunT m) where
createQueryTags qtSourceConfig attr = retag (createQueryTags @m qtSourceConfig attr) :: Tagged (RunT m) QueryTagsComment