2022-01-06 12:49:03 +03:00
{- # OPTIONS_HADDOCK ignore - exports # -}
-- | Responsible for translating and building an MSSQL execution plan for
-- delete mutations.
--
-- This module is used by "Hasura.Backends.MSSQL.Instances.Execute".
module Hasura.Backends.MSSQL.Execute.Insert
( executeInsert ,
)
where
2022-03-14 18:34:14 +03:00
import Data.HashMap.Strict qualified as HM
2022-01-06 12:49:03 +03:00
import Database.MSSQL.Transaction qualified as Tx
import Hasura.Backends.MSSQL.Connection
2022-04-28 22:33:33 +03:00
import Hasura.Backends.MSSQL.Execute.QueryTags ( withQueryTags )
2022-01-06 12:49:03 +03:00
import Hasura.Backends.MSSQL.FromIr as TSQL
2022-03-10 13:33:55 +03:00
import Hasura.Backends.MSSQL.FromIr.Constants ( tempTableNameInserted , tempTableNameValues )
import Hasura.Backends.MSSQL.FromIr.Expression
import Hasura.Backends.MSSQL.FromIr.Insert ( toMerge )
import Hasura.Backends.MSSQL.FromIr.Insert qualified as TSQL
import Hasura.Backends.MSSQL.FromIr.MutationResponse
import Hasura.Backends.MSSQL.FromIr.SelectIntoTempTable qualified as TSQL
2022-01-06 12:49:03 +03:00
import Hasura.Backends.MSSQL.Plan
2022-02-07 17:11:49 +03:00
import Hasura.Backends.MSSQL.SQL.Error
2022-01-06 12:49:03 +03:00
import Hasura.Backends.MSSQL.ToQuery as TQ
import Hasura.Backends.MSSQL.Types.Insert ( BackendInsert ( .. ) , IfMatched )
import Hasura.Backends.MSSQL.Types.Internal as TSQL
import Hasura.Base.Error
import Hasura.EncJSON
Allow backend execution to happen on the base app monad.
### Description
Each Backend executes queries against the database in a slightly different stack: Postgres uses its own `TXeT`, MSSQL uses a variant of it, BigQuery is simply in `ExceptT QErr IO`... To accommodate those variations, we had originally introduced an `ExecutionMonad b` type family in `BackendExecute`, allowing each backend to describe its own stack. It was then up to that backend's `BackendTransport` instance to implement running said stack, and converting the result back into our main app monad.
However, this was not without complications: `TraceT` is one of them: as it usually needs to be on the top of the stack, converting from one stack to the other implies the use `interpTraceT`, which is quite monstrous. Furthermore, as part of the Entitlement Services work, we're trying to move to a "Services" architecture in which the entire engine runs in one base monad, that delegates features and dependencies to monad constraints; and as a result we'd like to minimize the number of different monad stacks we have to maintain and translate from and to in the codebase.
To improve things, this PR changes `ExecutionMonad b` from an _absolute_ stack to a _relative_ one: i.e.: what needs to be stacked on top of our base monad for the execution. In `Transport`, we then only need to pop the top of the stack, and voila. This greatly simplifies the implementation of the backends, as there's no longer any need to do any stack transformation: MySQL's implementation becomes a `runIdentityT`! This also removes most mentions of `TraceT` from the execution code since it's no longer required: we can rely on the base monad's existing `MonadTrace` constraint.
To continue encapsulating monadic actions in `DBStepInfo` and avoid threading a bunch of `forall` all over the place, this PR introduces a small local helper: `OnBaseMonad`. One only downside of all this is that this requires adding `MonadBaseControl IO m` constraint all over the place: previously, we would run directly on `IO` and lift, and would therefore not need to bring that constraint all the way.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7789
GitOrigin-RevId: e9b2e431c5c47fa9851abf87545c0415ff6d1a12
2023-02-09 17:38:33 +03:00
import Hasura.GraphQL.Execute.Backend
2022-07-14 20:57:28 +03:00
import Hasura.GraphQL.Schema.Options qualified as Options
2022-01-06 12:49:03 +03:00
import Hasura.Prelude
2022-04-28 22:33:33 +03:00
import Hasura.QueryTags ( QueryTagsComment )
2022-01-06 12:49:03 +03:00
import Hasura.RQL.IR
2022-04-27 16:57:28 +03:00
import Hasura.RQL.Types.Backend
import Hasura.RQL.Types.Column
import Hasura.SQL.Backend
2022-01-06 12:49:03 +03:00
import Hasura.Session
-- | Execute and insert/upsert mutation against MS SQL Server.
-- See the documentation for 'buildInsertTx' to see how it's done.
executeInsert ::
2022-04-28 22:33:33 +03:00
( MonadError QErr m , MonadReader QueryTagsComment m ) =>
2022-01-06 12:49:03 +03:00
UserInfo ->
2022-07-14 20:57:28 +03:00
Options . StringifyNumbers ->
2022-01-06 12:49:03 +03:00
SourceConfig 'MSSQL ->
2022-04-01 09:43:05 +03:00
AnnotatedInsert 'MSSQL Void ( UnpreparedValue 'MSSQL ) ->
Allow backend execution to happen on the base app monad.
### Description
Each Backend executes queries against the database in a slightly different stack: Postgres uses its own `TXeT`, MSSQL uses a variant of it, BigQuery is simply in `ExceptT QErr IO`... To accommodate those variations, we had originally introduced an `ExecutionMonad b` type family in `BackendExecute`, allowing each backend to describe its own stack. It was then up to that backend's `BackendTransport` instance to implement running said stack, and converting the result back into our main app monad.
However, this was not without complications: `TraceT` is one of them: as it usually needs to be on the top of the stack, converting from one stack to the other implies the use `interpTraceT`, which is quite monstrous. Furthermore, as part of the Entitlement Services work, we're trying to move to a "Services" architecture in which the entire engine runs in one base monad, that delegates features and dependencies to monad constraints; and as a result we'd like to minimize the number of different monad stacks we have to maintain and translate from and to in the codebase.
To improve things, this PR changes `ExecutionMonad b` from an _absolute_ stack to a _relative_ one: i.e.: what needs to be stacked on top of our base monad for the execution. In `Transport`, we then only need to pop the top of the stack, and voila. This greatly simplifies the implementation of the backends, as there's no longer any need to do any stack transformation: MySQL's implementation becomes a `runIdentityT`! This also removes most mentions of `TraceT` from the execution code since it's no longer required: we can rely on the base monad's existing `MonadTrace` constraint.
To continue encapsulating monadic actions in `DBStepInfo` and avoid threading a bunch of `forall` all over the place, this PR introduces a small local helper: `OnBaseMonad`. One only downside of all this is that this requires adding `MonadBaseControl IO m` constraint all over the place: previously, we would run directly on `IO` and lift, and would therefore not need to bring that constraint all the way.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7789
GitOrigin-RevId: e9b2e431c5c47fa9851abf87545c0415ff6d1a12
2023-02-09 17:38:33 +03:00
m ( OnBaseMonad ( ExceptT QErr ) EncJSON )
2022-01-06 12:49:03 +03:00
executeInsert userInfo stringifyNum sourceConfig annInsert = do
2022-04-28 22:33:33 +03:00
queryTags <- ask
2022-01-06 12:49:03 +03:00
-- Convert the leaf values from @'UnpreparedValue' to sql @'Expression'
insert <- traverse ( prepareValueQuery sessionVariables ) annInsert
Allow backend execution to happen on the base app monad.
### Description
Each Backend executes queries against the database in a slightly different stack: Postgres uses its own `TXeT`, MSSQL uses a variant of it, BigQuery is simply in `ExceptT QErr IO`... To accommodate those variations, we had originally introduced an `ExecutionMonad b` type family in `BackendExecute`, allowing each backend to describe its own stack. It was then up to that backend's `BackendTransport` instance to implement running said stack, and converting the result back into our main app monad.
However, this was not without complications: `TraceT` is one of them: as it usually needs to be on the top of the stack, converting from one stack to the other implies the use `interpTraceT`, which is quite monstrous. Furthermore, as part of the Entitlement Services work, we're trying to move to a "Services" architecture in which the entire engine runs in one base monad, that delegates features and dependencies to monad constraints; and as a result we'd like to minimize the number of different monad stacks we have to maintain and translate from and to in the codebase.
To improve things, this PR changes `ExecutionMonad b` from an _absolute_ stack to a _relative_ one: i.e.: what needs to be stacked on top of our base monad for the execution. In `Transport`, we then only need to pop the top of the stack, and voila. This greatly simplifies the implementation of the backends, as there's no longer any need to do any stack transformation: MySQL's implementation becomes a `runIdentityT`! This also removes most mentions of `TraceT` from the execution code since it's no longer required: we can rely on the base monad's existing `MonadTrace` constraint.
To continue encapsulating monadic actions in `DBStepInfo` and avoid threading a bunch of `forall` all over the place, this PR introduces a small local helper: `OnBaseMonad`. One only downside of all this is that this requires adding `MonadBaseControl IO m` constraint all over the place: previously, we would run directly on `IO` and lift, and would therefore not need to bring that constraint all the way.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7789
GitOrigin-RevId: e9b2e431c5c47fa9851abf87545c0415ff6d1a12
2023-02-09 17:38:33 +03:00
pure $ OnBaseMonad $ mssqlRunReadWrite ( _mscExecCtx sourceConfig ) $ buildInsertTx tableName withAlias stringifyNum insert queryTags
2022-01-06 12:49:03 +03:00
where
sessionVariables = _uiSession userInfo
tableName = _aiTableName $ _aiData annInsert
withAlias = " with_alias "
-- | Translates an IR Insert/upsert mutation description to SQL and
-- builds a corresponding transaction to run against MS SQL Server.
--
-- Execution of a MSSQL insert mutation broadly involves two steps.
--
-- > insert_table(objects: [
-- > {column1: value1, column2: value2},
-- > {column1: value3, column2: value4}
-- > ],
-- > if_matched: {match_columns: [column1], update_columns: [column2]} # Optional field to enable upserting
-- > ){
-- > affected_rows
-- > returning {
-- > column1
-- > column2
-- > }
-- > }
--
-- = Step 1: Inserting rows into the table
--
-- a. Create an empty temporary table with name #inserted to store affected rows (for the response)
--
-- > SELECT column1, column2 INTO #inserted FROM some_table WHERE (1 <> 1)
2022-02-03 17:14:33 +03:00
-- > UNION ALL SELECT column1, column2 FROM some_table WHERE (1 <> 1);
2022-01-06 12:49:03 +03:00
--
2022-02-03 17:14:33 +03:00
-- b. If 'if_matched' is found: Use MERGE statment to perform upsert
2022-01-06 12:49:03 +03:00
--
2022-02-03 17:14:33 +03:00
-- b.1 Use #values temporary table to store input object values
2022-01-06 12:49:03 +03:00
--
2022-02-03 17:14:33 +03:00
-- > SELECT column1, column2 INTO #values FROM some_table WHERE (1 <> 1)
2022-01-06 12:49:03 +03:00
--
2022-02-03 17:14:33 +03:00
-- b.2 Insert input object values into the temporary table
2022-01-06 12:49:03 +03:00
--
-- > INSERT INTO #values (column1, column2) VALUES (value1, value2), (value3, value4)
--
--
2022-02-03 17:14:33 +03:00
-- b.3 Generate an SQL Merge statement to perform either update or insert (upsert) to the table
2022-01-06 12:49:03 +03:00
--
-- > MERGE some_table AS [target]
-- > USING (SELECT column1, column2 from #values) AS [source](column1, column2) ON ([target].column1 = [source].column1)
-- > WHEN MATCHED THEN UPDATE SET [column2] = [source].[column2]
-- > WHEN NOT MATCHED THEN INSERT (column1, column2) VALUES ([source].column1, [source].column2)
-- > OUTPUT INSERTED.column1, INSERTED.column2 INTO #inserted(column1, column2)
--
-- __NOTE__: In @MERGE@ statement, we use @SELECT query from a temporary table@ as source but not @VALUES@ expression
-- because, we can't use @DEFAULT@ expression (for missing columns in @objects@ field) in @VALUES@ expression.
--
-- __else__: Generate an SQL Insert statement from the GraphQL insert mutation with OUTPUT expression to fill @#inserted@ temporary table with inserted rows
--
-- > INSERT INTO some_table (column1, column2) OUTPUT INSERTED.column1, INSERTED.column2 INTO #inserted(column1, column2) VALUES (value1, value2), (value3, value4);
--
-- = Step 2: Generation of the mutation response
--
-- An SQL statement is generated and when executed it returns the mutation selection set containing 'affected_rows' and 'returning' field values.
-- The statement is generated with multiple sub select queries explained below:
--
-- a. A SQL Select statement to fetch only inserted rows from temporary table
--
-- > <table_select> := SELECT * FROM #inserted
--
-- The above select statement is referred through a common table expression - @WITH [with_alias] AS (<table_select>)@
--
-- b. The @affected_rows@ field value is obtained by using @COUNT@ aggregation and the @returning@ field selection set is translated to
-- a SQL select statement using 'mkSQLSelect'.
--
-- > <mutation_output_select> :=
-- > SELECT (SELECT COUNT(*) FROM [with_alias]) AS [affected_rows], (select_from_returning) AS [returning]
-- > FOR JSON PATH, INCLUDE_NULL_VALUES, WITHOUT_ARRAY_WRAPPER
--
-- c. Evaluate the check constraint using @CASE@ expression. We use @SUM@ aggregation to check if any inserted row has failed the check constraint.
--
-- > <check_constraint_select> :=
2022-04-05 13:09:35 +03:00
-- > SELECT SUM([check_sub_query].[check_evaluation])
-- > FROM
-- > ( SELECT
-- > (CASE WHEN <check_boolean_expression> THEN 0 ELSE 1 END) AS [check_evaluation]
-- > FROM
-- > [with_alias]
-- > ) AS [check_sub_query]
2022-01-06 12:49:03 +03:00
--
-- d. The final select statement look like
--
-- > WITH "with_alias" AS (<table_select>)
-- > SELECT (<mutation_output_select>) AS [mutation_response], (<check_constraint_select>) AS [check_constraint_select]
--
-- When executed, the above statement returns a single row with mutation response as a string value and check constraint result as an integer value.
2022-04-28 22:33:33 +03:00
buildInsertTx ::
Allow backend execution to happen on the base app monad.
### Description
Each Backend executes queries against the database in a slightly different stack: Postgres uses its own `TXeT`, MSSQL uses a variant of it, BigQuery is simply in `ExceptT QErr IO`... To accommodate those variations, we had originally introduced an `ExecutionMonad b` type family in `BackendExecute`, allowing each backend to describe its own stack. It was then up to that backend's `BackendTransport` instance to implement running said stack, and converting the result back into our main app monad.
However, this was not without complications: `TraceT` is one of them: as it usually needs to be on the top of the stack, converting from one stack to the other implies the use `interpTraceT`, which is quite monstrous. Furthermore, as part of the Entitlement Services work, we're trying to move to a "Services" architecture in which the entire engine runs in one base monad, that delegates features and dependencies to monad constraints; and as a result we'd like to minimize the number of different monad stacks we have to maintain and translate from and to in the codebase.
To improve things, this PR changes `ExecutionMonad b` from an _absolute_ stack to a _relative_ one: i.e.: what needs to be stacked on top of our base monad for the execution. In `Transport`, we then only need to pop the top of the stack, and voila. This greatly simplifies the implementation of the backends, as there's no longer any need to do any stack transformation: MySQL's implementation becomes a `runIdentityT`! This also removes most mentions of `TraceT` from the execution code since it's no longer required: we can rely on the base monad's existing `MonadTrace` constraint.
To continue encapsulating monadic actions in `DBStepInfo` and avoid threading a bunch of `forall` all over the place, this PR introduces a small local helper: `OnBaseMonad`. One only downside of all this is that this requires adding `MonadBaseControl IO m` constraint all over the place: previously, we would run directly on `IO` and lift, and would therefore not need to bring that constraint all the way.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7789
GitOrigin-RevId: e9b2e431c5c47fa9851abf87545c0415ff6d1a12
2023-02-09 17:38:33 +03:00
( MonadIO m ) =>
2022-04-28 22:33:33 +03:00
TSQL . TableName ->
Text ->
2022-07-14 20:57:28 +03:00
Options . StringifyNumbers ->
2022-04-28 22:33:33 +03:00
AnnotatedInsert 'MSSQL Void Expression ->
QueryTagsComment ->
Allow backend execution to happen on the base app monad.
### Description
Each Backend executes queries against the database in a slightly different stack: Postgres uses its own `TXeT`, MSSQL uses a variant of it, BigQuery is simply in `ExceptT QErr IO`... To accommodate those variations, we had originally introduced an `ExecutionMonad b` type family in `BackendExecute`, allowing each backend to describe its own stack. It was then up to that backend's `BackendTransport` instance to implement running said stack, and converting the result back into our main app monad.
However, this was not without complications: `TraceT` is one of them: as it usually needs to be on the top of the stack, converting from one stack to the other implies the use `interpTraceT`, which is quite monstrous. Furthermore, as part of the Entitlement Services work, we're trying to move to a "Services" architecture in which the entire engine runs in one base monad, that delegates features and dependencies to monad constraints; and as a result we'd like to minimize the number of different monad stacks we have to maintain and translate from and to in the codebase.
To improve things, this PR changes `ExecutionMonad b` from an _absolute_ stack to a _relative_ one: i.e.: what needs to be stacked on top of our base monad for the execution. In `Transport`, we then only need to pop the top of the stack, and voila. This greatly simplifies the implementation of the backends, as there's no longer any need to do any stack transformation: MySQL's implementation becomes a `runIdentityT`! This also removes most mentions of `TraceT` from the execution code since it's no longer required: we can rely on the base monad's existing `MonadTrace` constraint.
To continue encapsulating monadic actions in `DBStepInfo` and avoid threading a bunch of `forall` all over the place, this PR introduces a small local helper: `OnBaseMonad`. One only downside of all this is that this requires adding `MonadBaseControl IO m` constraint all over the place: previously, we would run directly on `IO` and lift, and would therefore not need to bring that constraint all the way.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7789
GitOrigin-RevId: e9b2e431c5c47fa9851abf87545c0415ff6d1a12
2023-02-09 17:38:33 +03:00
Tx . TxET QErr m EncJSON
2022-04-28 22:33:33 +03:00
buildInsertTx tableName withAlias stringifyNum insert queryTags = do
2022-04-01 09:43:05 +03:00
let tableColumns = _aiTableColumns $ _aiData insert
2022-01-06 12:49:03 +03:00
ifMatchedField = _biIfMatched . _aiBackendInsert . _aiData $ insert
-- Create #inserted temporary table
let createInsertedTempTableQuery =
toQueryFlat $
TQ . fromSelectIntoTempTable $
TSQL . toSelectIntoTempTable tempTableNameInserted tableName tableColumns RemoveConstraints
2022-04-28 22:33:33 +03:00
Tx . unitQueryE defaultMSSQLTxErrorHandler ( createInsertedTempTableQuery ` withQueryTags ` queryTags )
2022-01-06 12:49:03 +03:00
-- Choose between running a regular @INSERT INTO@ statement or a @MERGE@ statement
-- depending on the @if_matched@ field.
--
-- Affected rows will be inserted into the #inserted temporary table regardless.
case ifMatchedField of
2022-02-03 17:14:33 +03:00
Nothing -> do
-- Insert values into the table using INSERT query
let insertQuery = toQueryFlat $ TQ . fromInsert $ TSQL . fromInsert insert
2022-04-28 22:33:33 +03:00
Tx . unitQueryE mutationMSSQLTxErrorHandler ( insertQuery ` withQueryTags ` queryTags )
Just ifMatched -> buildUpsertTx tableName insert ifMatched queryTags
2022-01-06 12:49:03 +03:00
-- Build a response to the user using the values in the temporary table named #inserted
2022-04-28 22:33:33 +03:00
( responseText , checkConditionInt ) <- buildInsertResponseTx stringifyNum withAlias insert queryTags
2022-01-06 12:49:03 +03:00
-- Drop the #inserted temp table
2022-04-28 22:33:33 +03:00
let dropInsertedTempTableQuery = toQueryFlat $ dropTempTableQuery tempTableNameInserted
Tx . unitQueryE defaultMSSQLTxErrorHandler ( dropInsertedTempTableQuery ` withQueryTags ` queryTags )
2022-01-06 12:49:03 +03:00
-- Raise an exception if the check condition is not met
unless ( checkConditionInt == 0 ) $
2022-10-27 15:19:19 +03:00
throw400 PermissionError " check constraint of an insert/update permission has failed "
2022-01-06 12:49:03 +03:00
pure $ encJFromText responseText
-- | Translates an IR IfMatched clause to SQL and
-- builds a corresponding transaction to run against MS SQL Server.
--
-- We do this in 2 steps:
--
-- 1. Create a temporary table called @#values@ which will hold the values the user want to insert,
-- and insert the values into it
-- 2. Build an run a @MERGE@ statement to either insert or upsert the values from the temporary table @#values@
-- into the original table, and output the affected rows into another temporary table called @#inserted@
-- which will be used to build a "response" for the user.
--
-- Should be used as part of a bigger transaction in 'buildInsertTx'.
2022-04-28 22:33:33 +03:00
buildUpsertTx ::
Allow backend execution to happen on the base app monad.
### Description
Each Backend executes queries against the database in a slightly different stack: Postgres uses its own `TXeT`, MSSQL uses a variant of it, BigQuery is simply in `ExceptT QErr IO`... To accommodate those variations, we had originally introduced an `ExecutionMonad b` type family in `BackendExecute`, allowing each backend to describe its own stack. It was then up to that backend's `BackendTransport` instance to implement running said stack, and converting the result back into our main app monad.
However, this was not without complications: `TraceT` is one of them: as it usually needs to be on the top of the stack, converting from one stack to the other implies the use `interpTraceT`, which is quite monstrous. Furthermore, as part of the Entitlement Services work, we're trying to move to a "Services" architecture in which the entire engine runs in one base monad, that delegates features and dependencies to monad constraints; and as a result we'd like to minimize the number of different monad stacks we have to maintain and translate from and to in the codebase.
To improve things, this PR changes `ExecutionMonad b` from an _absolute_ stack to a _relative_ one: i.e.: what needs to be stacked on top of our base monad for the execution. In `Transport`, we then only need to pop the top of the stack, and voila. This greatly simplifies the implementation of the backends, as there's no longer any need to do any stack transformation: MySQL's implementation becomes a `runIdentityT`! This also removes most mentions of `TraceT` from the execution code since it's no longer required: we can rely on the base monad's existing `MonadTrace` constraint.
To continue encapsulating monadic actions in `DBStepInfo` and avoid threading a bunch of `forall` all over the place, this PR introduces a small local helper: `OnBaseMonad`. One only downside of all this is that this requires adding `MonadBaseControl IO m` constraint all over the place: previously, we would run directly on `IO` and lift, and would therefore not need to bring that constraint all the way.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7789
GitOrigin-RevId: e9b2e431c5c47fa9851abf87545c0415ff6d1a12
2023-02-09 17:38:33 +03:00
MonadIO m =>
2022-04-28 22:33:33 +03:00
TSQL . TableName ->
AnnotatedInsert 'MSSQL Void Expression ->
IfMatched Expression ->
QueryTagsComment ->
Allow backend execution to happen on the base app monad.
### Description
Each Backend executes queries against the database in a slightly different stack: Postgres uses its own `TXeT`, MSSQL uses a variant of it, BigQuery is simply in `ExceptT QErr IO`... To accommodate those variations, we had originally introduced an `ExecutionMonad b` type family in `BackendExecute`, allowing each backend to describe its own stack. It was then up to that backend's `BackendTransport` instance to implement running said stack, and converting the result back into our main app monad.
However, this was not without complications: `TraceT` is one of them: as it usually needs to be on the top of the stack, converting from one stack to the other implies the use `interpTraceT`, which is quite monstrous. Furthermore, as part of the Entitlement Services work, we're trying to move to a "Services" architecture in which the entire engine runs in one base monad, that delegates features and dependencies to monad constraints; and as a result we'd like to minimize the number of different monad stacks we have to maintain and translate from and to in the codebase.
To improve things, this PR changes `ExecutionMonad b` from an _absolute_ stack to a _relative_ one: i.e.: what needs to be stacked on top of our base monad for the execution. In `Transport`, we then only need to pop the top of the stack, and voila. This greatly simplifies the implementation of the backends, as there's no longer any need to do any stack transformation: MySQL's implementation becomes a `runIdentityT`! This also removes most mentions of `TraceT` from the execution code since it's no longer required: we can rely on the base monad's existing `MonadTrace` constraint.
To continue encapsulating monadic actions in `DBStepInfo` and avoid threading a bunch of `forall` all over the place, this PR introduces a small local helper: `OnBaseMonad`. One only downside of all this is that this requires adding `MonadBaseControl IO m` constraint all over the place: previously, we would run directly on `IO` and lift, and would therefore not need to bring that constraint all the way.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7789
GitOrigin-RevId: e9b2e431c5c47fa9851abf87545c0415ff6d1a12
2023-02-09 17:38:33 +03:00
Tx . TxET QErr m ()
2022-04-28 22:33:33 +03:00
buildUpsertTx tableName insert ifMatched queryTags = do
2022-04-21 19:32:43 +03:00
let presets = _aiPresetValues $ _aiData insert
2022-03-14 18:34:14 +03:00
insertColumnNames =
2022-04-01 09:43:05 +03:00
concatMap ( map fst . getInsertColumns ) ( _aiInsertObject $ _aiData insert ) <> HM . keys presets
allTableColumns = _aiTableColumns $ _aiData insert
2022-02-03 17:14:33 +03:00
insertColumns = filter ( \ c -> ciColumn c ` elem ` insertColumnNames ) allTableColumns
2022-01-06 12:49:03 +03:00
createValuesTempTableQuery =
toQueryFlat $
TQ . fromSelectIntoTempTable $
-- We want to KeepConstraints here so the user can omit values for identity columns such as `id`
2022-02-03 17:14:33 +03:00
TSQL . toSelectIntoTempTable tempTableNameValues tableName insertColumns KeepConstraints
2022-01-06 12:49:03 +03:00
-- Create #values temporary table
2022-04-28 22:33:33 +03:00
Tx . unitQueryE defaultMSSQLTxErrorHandler ( createValuesTempTableQuery ` withQueryTags ` queryTags )
2022-01-06 12:49:03 +03:00
2022-02-03 17:14:33 +03:00
-- Store values in #values temporary table
let insertValuesIntoTempTableQuery =
toQueryFlat $
TQ . fromInsertValuesIntoTempTable $
TSQL . toInsertValuesIntoTempTable tempTableNameValues insert
2022-04-28 22:33:33 +03:00
Tx . unitQueryE mutationMSSQLTxErrorHandler ( insertValuesIntoTempTableQuery ` withQueryTags ` queryTags )
2022-02-03 17:14:33 +03:00
-- Run the MERGE query and store the mutated rows in #inserted temporary table
2022-04-01 09:43:05 +03:00
merge <- runFromIr ( toMerge tableName ( _aiInsertObject $ _aiData insert ) allTableColumns ifMatched )
2022-02-03 17:14:33 +03:00
let mergeQuery = toQueryFlat $ TQ . fromMerge merge
2022-04-28 22:33:33 +03:00
Tx . unitQueryE mutationMSSQLTxErrorHandler ( mergeQuery ` withQueryTags ` queryTags )
2022-01-06 12:49:03 +03:00
-- After @MERGE@ we no longer need this temporary table
2022-04-28 22:33:33 +03:00
Tx . unitQueryE defaultMSSQLTxErrorHandler ( toQueryFlat ( dropTempTableQuery tempTableNameValues ) ` withQueryTags ` queryTags )
2022-01-06 12:49:03 +03:00
-- | Builds a response to the user using the values in the temporary table named #inserted.
2022-04-28 22:33:33 +03:00
buildInsertResponseTx ::
Allow backend execution to happen on the base app monad.
### Description
Each Backend executes queries against the database in a slightly different stack: Postgres uses its own `TXeT`, MSSQL uses a variant of it, BigQuery is simply in `ExceptT QErr IO`... To accommodate those variations, we had originally introduced an `ExecutionMonad b` type family in `BackendExecute`, allowing each backend to describe its own stack. It was then up to that backend's `BackendTransport` instance to implement running said stack, and converting the result back into our main app monad.
However, this was not without complications: `TraceT` is one of them: as it usually needs to be on the top of the stack, converting from one stack to the other implies the use `interpTraceT`, which is quite monstrous. Furthermore, as part of the Entitlement Services work, we're trying to move to a "Services" architecture in which the entire engine runs in one base monad, that delegates features and dependencies to monad constraints; and as a result we'd like to minimize the number of different monad stacks we have to maintain and translate from and to in the codebase.
To improve things, this PR changes `ExecutionMonad b` from an _absolute_ stack to a _relative_ one: i.e.: what needs to be stacked on top of our base monad for the execution. In `Transport`, we then only need to pop the top of the stack, and voila. This greatly simplifies the implementation of the backends, as there's no longer any need to do any stack transformation: MySQL's implementation becomes a `runIdentityT`! This also removes most mentions of `TraceT` from the execution code since it's no longer required: we can rely on the base monad's existing `MonadTrace` constraint.
To continue encapsulating monadic actions in `DBStepInfo` and avoid threading a bunch of `forall` all over the place, this PR introduces a small local helper: `OnBaseMonad`. One only downside of all this is that this requires adding `MonadBaseControl IO m` constraint all over the place: previously, we would run directly on `IO` and lift, and would therefore not need to bring that constraint all the way.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7789
GitOrigin-RevId: e9b2e431c5c47fa9851abf87545c0415ff6d1a12
2023-02-09 17:38:33 +03:00
MonadIO m =>
2022-07-14 20:57:28 +03:00
Options . StringifyNumbers ->
2022-04-28 22:33:33 +03:00
Text ->
AnnotatedInsert 'MSSQL Void Expression ->
QueryTagsComment ->
Allow backend execution to happen on the base app monad.
### Description
Each Backend executes queries against the database in a slightly different stack: Postgres uses its own `TXeT`, MSSQL uses a variant of it, BigQuery is simply in `ExceptT QErr IO`... To accommodate those variations, we had originally introduced an `ExecutionMonad b` type family in `BackendExecute`, allowing each backend to describe its own stack. It was then up to that backend's `BackendTransport` instance to implement running said stack, and converting the result back into our main app monad.
However, this was not without complications: `TraceT` is one of them: as it usually needs to be on the top of the stack, converting from one stack to the other implies the use `interpTraceT`, which is quite monstrous. Furthermore, as part of the Entitlement Services work, we're trying to move to a "Services" architecture in which the entire engine runs in one base monad, that delegates features and dependencies to monad constraints; and as a result we'd like to minimize the number of different monad stacks we have to maintain and translate from and to in the codebase.
To improve things, this PR changes `ExecutionMonad b` from an _absolute_ stack to a _relative_ one: i.e.: what needs to be stacked on top of our base monad for the execution. In `Transport`, we then only need to pop the top of the stack, and voila. This greatly simplifies the implementation of the backends, as there's no longer any need to do any stack transformation: MySQL's implementation becomes a `runIdentityT`! This also removes most mentions of `TraceT` from the execution code since it's no longer required: we can rely on the base monad's existing `MonadTrace` constraint.
To continue encapsulating monadic actions in `DBStepInfo` and avoid threading a bunch of `forall` all over the place, this PR introduces a small local helper: `OnBaseMonad`. One only downside of all this is that this requires adding `MonadBaseControl IO m` constraint all over the place: previously, we would run directly on `IO` and lift, and would therefore not need to bring that constraint all the way.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7789
GitOrigin-RevId: e9b2e431c5c47fa9851abf87545c0415ff6d1a12
2023-02-09 17:38:33 +03:00
Tx . TxET QErr m ( Text , Int )
2022-04-28 22:33:33 +03:00
buildInsertResponseTx stringifyNum withAlias insert queryTags = do
2022-01-06 12:49:03 +03:00
-- Generate a SQL SELECT statement which outputs the mutation response using the #inserted
2022-03-10 13:33:55 +03:00
mutationOutputSelect <- runFromIr $ mkMutationOutputSelect stringifyNum withAlias $ _aiOutput insert
2022-01-06 12:49:03 +03:00
-- The check constraint is translated to boolean expression
2022-04-01 09:43:05 +03:00
let checkCondition = fst $ _aiCheckCondition $ _aiData insert
2022-03-10 13:33:55 +03:00
checkBoolExp <- runFromIr $ runReaderT ( fromGBoolExp checkCondition ) ( EntityAlias withAlias )
2022-01-06 12:49:03 +03:00
let withSelect =
emptySelect
{ selectProjections = [ StarProjection ] ,
selectFrom = Just $ FromTempTable $ Aliased tempTableNameInserted " inserted_alias "
}
-- SELECT (<mutation_output_select>) AS [mutation_response], (<check_constraint_select>) AS [check_constraint_select]
mutationOutputCheckConstraintSelect = selectMutationOutputAndCheckCondition withAlias mutationOutputSelect checkBoolExp
-- WITH "with_alias" AS (<table_select>)
-- SELECT (<mutation_output_select>) AS [mutation_response], (<check_constraint_select>) AS [check_constraint_select]
finalSelect = mutationOutputCheckConstraintSelect { selectWith = Just $ With $ pure $ Aliased withSelect withAlias }
-- Execute SELECT query to fetch mutation response and check constraint result
2022-04-28 22:33:33 +03:00
let selectQuery = toQueryFlat ( TQ . fromSelect finalSelect )
Tx . singleRowQueryE defaultMSSQLTxErrorHandler ( selectQuery ` withQueryTags ` queryTags )