mirror of
https://github.com/hasura/graphql-engine.git
synced 2025-01-05 22:34:22 +03:00
Tidy up MSSQL.FromIr
## Description We go through the module `Hasura.Backends.MSSQL.FromIr` and split it into separate self-contained units, which we document. Note that this PR has a slightly opinionated follow-up PR #3909 . ### Related Issues Fix #3666 ### Solution and Design The module `FromIr` has given rise to: * `FromIr.Expression` * `FromIr.Query` * `FromIr.Delete` * `FromIr.Insert` * `FromIr.Update` * `FromIr.SelectIntoTempTable` And `Execute.MutationResponse` has become `FromIr.MutationResponse` (after some slight adaptation of types). PR-URL: https://github.com/hasura/graphql-engine-mono/pull/3908 GitOrigin-RevId: 364acf1bcdf74f2e19464c31cdded12bd8e9aa59
This commit is contained in:
parent
2ff0f25e08
commit
4ccc830bb8
@ -386,11 +386,18 @@ library
|
|||||||
, Hasura.Backends.MSSQL.DDL.RunSQL
|
, Hasura.Backends.MSSQL.DDL.RunSQL
|
||||||
, Hasura.Backends.MSSQL.DDL.Source
|
, Hasura.Backends.MSSQL.DDL.Source
|
||||||
, Hasura.Backends.MSSQL.DDL.Source.Version
|
, Hasura.Backends.MSSQL.DDL.Source.Version
|
||||||
, Hasura.Backends.MSSQL.Execute.MutationResponse
|
|
||||||
, Hasura.Backends.MSSQL.Execute.Delete
|
, Hasura.Backends.MSSQL.Execute.Delete
|
||||||
, Hasura.Backends.MSSQL.Execute.Insert
|
, Hasura.Backends.MSSQL.Execute.Insert
|
||||||
, Hasura.Backends.MSSQL.Execute.Update
|
, Hasura.Backends.MSSQL.Execute.Update
|
||||||
, Hasura.Backends.MSSQL.FromIr
|
, Hasura.Backends.MSSQL.FromIr
|
||||||
|
, Hasura.Backends.MSSQL.FromIr.Constants
|
||||||
|
, Hasura.Backends.MSSQL.FromIr.Delete
|
||||||
|
, Hasura.Backends.MSSQL.FromIr.Expression
|
||||||
|
, Hasura.Backends.MSSQL.FromIr.Insert
|
||||||
|
, Hasura.Backends.MSSQL.FromIr.MutationResponse
|
||||||
|
, Hasura.Backends.MSSQL.FromIr.Query
|
||||||
|
, Hasura.Backends.MSSQL.FromIr.SelectIntoTempTable
|
||||||
|
, Hasura.Backends.MSSQL.FromIr.Update
|
||||||
, Hasura.Backends.MSSQL.Instances.API
|
, Hasura.Backends.MSSQL.Instances.API
|
||||||
, Hasura.Backends.MSSQL.Instances.Execute
|
, Hasura.Backends.MSSQL.Instances.Execute
|
||||||
, Hasura.Backends.MSSQL.Instances.Metadata
|
, Hasura.Backends.MSSQL.Instances.Metadata
|
||||||
|
@ -9,11 +9,13 @@ module Hasura.Backends.MSSQL.Execute.Delete
|
|||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Control.Monad.Validate qualified as V
|
|
||||||
import Database.MSSQL.Transaction qualified as Tx
|
import Database.MSSQL.Transaction qualified as Tx
|
||||||
import Hasura.Backends.MSSQL.Connection
|
import Hasura.Backends.MSSQL.Connection
|
||||||
import Hasura.Backends.MSSQL.Execute.MutationResponse
|
|
||||||
import Hasura.Backends.MSSQL.FromIr as TSQL
|
import Hasura.Backends.MSSQL.FromIr as TSQL
|
||||||
|
import Hasura.Backends.MSSQL.FromIr.Constants (tempTableNameDeleted)
|
||||||
|
import Hasura.Backends.MSSQL.FromIr.Delete qualified as TSQL
|
||||||
|
import Hasura.Backends.MSSQL.FromIr.MutationResponse
|
||||||
|
import Hasura.Backends.MSSQL.FromIr.SelectIntoTempTable qualified as TSQL
|
||||||
import Hasura.Backends.MSSQL.Plan
|
import Hasura.Backends.MSSQL.Plan
|
||||||
import Hasura.Backends.MSSQL.SQL.Error
|
import Hasura.Backends.MSSQL.SQL.Error
|
||||||
import Hasura.Backends.MSSQL.ToQuery as TQ
|
import Hasura.Backends.MSSQL.ToQuery as TQ
|
||||||
@ -67,10 +69,11 @@ buildDeleteTx deleteOperation stringifyNum = do
|
|||||||
-- Create a temp table
|
-- Create a temp table
|
||||||
Tx.unitQueryE defaultMSSQLTxErrorHandler createInsertedTempTableQuery
|
Tx.unitQueryE defaultMSSQLTxErrorHandler createInsertedTempTableQuery
|
||||||
let deleteQuery = TQ.fromDelete <$> TSQL.fromDelete deleteOperation
|
let deleteQuery = TQ.fromDelete <$> TSQL.fromDelete deleteOperation
|
||||||
deleteQueryValidated <- toQueryFlat <$> V.runValidate (runFromIr deleteQuery) `onLeft` (throw500 . tshow)
|
deleteQueryValidated <- toQueryFlat <$> runFromIr deleteQuery
|
||||||
-- Execute DELETE statement
|
-- Execute DELETE statement
|
||||||
Tx.unitQueryE mutationMSSQLTxErrorHandler deleteQueryValidated
|
Tx.unitQueryE mutationMSSQLTxErrorHandler deleteQueryValidated
|
||||||
mutationOutputSelect <- mkMutationOutputSelect stringifyNum withAlias $ _adOutput deleteOperation
|
mutationOutputSelect <- runFromIr $ mkMutationOutputSelect stringifyNum withAlias $ _adOutput deleteOperation
|
||||||
|
|
||||||
let withSelect =
|
let withSelect =
|
||||||
emptySelect
|
emptySelect
|
||||||
{ selectProjections = [StarProjection],
|
{ selectProjections = [StarProjection],
|
||||||
|
@ -9,11 +9,15 @@ module Hasura.Backends.MSSQL.Execute.Insert
|
|||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Control.Monad.Validate qualified as V
|
|
||||||
import Database.MSSQL.Transaction qualified as Tx
|
import Database.MSSQL.Transaction qualified as Tx
|
||||||
import Hasura.Backends.MSSQL.Connection
|
import Hasura.Backends.MSSQL.Connection
|
||||||
import Hasura.Backends.MSSQL.Execute.MutationResponse
|
|
||||||
import Hasura.Backends.MSSQL.FromIr as TSQL
|
import Hasura.Backends.MSSQL.FromIr as TSQL
|
||||||
|
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
|
||||||
import Hasura.Backends.MSSQL.Plan
|
import Hasura.Backends.MSSQL.Plan
|
||||||
import Hasura.Backends.MSSQL.SQL.Error
|
import Hasura.Backends.MSSQL.SQL.Error
|
||||||
import Hasura.Backends.MSSQL.ToQuery as TQ
|
import Hasura.Backends.MSSQL.ToQuery as TQ
|
||||||
@ -196,10 +200,7 @@ buildUpsertTx tableName insert ifMatched = do
|
|||||||
Tx.unitQueryE mutationMSSQLTxErrorHandler insertValuesIntoTempTableQuery
|
Tx.unitQueryE mutationMSSQLTxErrorHandler insertValuesIntoTempTableQuery
|
||||||
|
|
||||||
-- Run the MERGE query and store the mutated rows in #inserted temporary table
|
-- Run the MERGE query and store the mutated rows in #inserted temporary table
|
||||||
merge <-
|
merge <- runFromIr (toMerge tableName (_aiInsObj $ _aiData insert) allTableColumns ifMatched)
|
||||||
(V.runValidate . runFromIr)
|
|
||||||
(toMerge tableName (_aiInsObj $ _aiData insert) allTableColumns ifMatched)
|
|
||||||
`onLeft` (throw500 . tshow)
|
|
||||||
let mergeQuery = toQueryFlat $ TQ.fromMerge merge
|
let mergeQuery = toQueryFlat $ TQ.fromMerge merge
|
||||||
Tx.unitQueryE mutationMSSQLTxErrorHandler mergeQuery
|
Tx.unitQueryE mutationMSSQLTxErrorHandler mergeQuery
|
||||||
|
|
||||||
@ -210,13 +211,11 @@ buildUpsertTx tableName insert ifMatched = do
|
|||||||
buildInsertResponseTx :: StringifyNumbers -> Text -> AnnInsert 'MSSQL Void Expression -> Tx.TxET QErr IO (Text, Int)
|
buildInsertResponseTx :: StringifyNumbers -> Text -> AnnInsert 'MSSQL Void Expression -> Tx.TxET QErr IO (Text, Int)
|
||||||
buildInsertResponseTx stringifyNum withAlias insert = do
|
buildInsertResponseTx stringifyNum withAlias insert = do
|
||||||
-- Generate a SQL SELECT statement which outputs the mutation response using the #inserted
|
-- Generate a SQL SELECT statement which outputs the mutation response using the #inserted
|
||||||
mutationOutputSelect <- mkMutationOutputSelect stringifyNum withAlias $ _aiOutput insert
|
mutationOutputSelect <- runFromIr $ mkMutationOutputSelect stringifyNum withAlias $ _aiOutput insert
|
||||||
|
|
||||||
-- The check constraint is translated to boolean expression
|
-- The check constraint is translated to boolean expression
|
||||||
let checkCondition = fst $ _aiCheckCond $ _aiData insert
|
let checkCondition = fst $ _aiCheckCond $ _aiData insert
|
||||||
checkBoolExp <-
|
checkBoolExp <- runFromIr $ runReaderT (fromGBoolExp checkCondition) (EntityAlias withAlias)
|
||||||
V.runValidate (runFromIr $ runReaderT (fromGBoolExp checkCondition) (EntityAlias withAlias))
|
|
||||||
`onLeft` (throw500 . tshow)
|
|
||||||
|
|
||||||
let withSelect =
|
let withSelect =
|
||||||
emptySelect
|
emptySelect
|
||||||
|
@ -1,104 +0,0 @@
|
|||||||
{-# OPTIONS_HADDOCK ignore-exports #-}
|
|
||||||
|
|
||||||
-- | Defines common functionality for building MSSQL execution plans for IR ASTs.
|
|
||||||
module Hasura.Backends.MSSQL.Execute.MutationResponse
|
|
||||||
( mkMutationOutputSelect,
|
|
||||||
selectMutationOutputAndCheckCondition,
|
|
||||||
)
|
|
||||||
where
|
|
||||||
|
|
||||||
import Control.Monad.Validate qualified as V
|
|
||||||
import Database.ODBC.SQLServer qualified as ODBC
|
|
||||||
import Hasura.Backends.MSSQL.FromIr as TSQL
|
|
||||||
import Hasura.Backends.MSSQL.Types.Internal as TSQL
|
|
||||||
import Hasura.Base.Error
|
|
||||||
import Hasura.Prelude
|
|
||||||
import Hasura.RQL.IR
|
|
||||||
import Hasura.RQL.IR qualified as IR
|
|
||||||
import Hasura.RQL.Types
|
|
||||||
|
|
||||||
-- ** Mutation response
|
|
||||||
|
|
||||||
-- | Generate a SQL SELECT statement which outputs the mutation response
|
|
||||||
--
|
|
||||||
-- For multi row inserts:
|
|
||||||
-- SELECT (SELECT COUNT(*) FROM [with_alias]) AS [affected_rows], (select_from_returning) AS [returning] FOR JSON PATH, INCLUDE_NULL_VALUES, WITHOUT_ARRAY_WRAPPER
|
|
||||||
--
|
|
||||||
-- For single row insert: the selection set is translated to SQL query using @'mkSQLSelect'
|
|
||||||
mkMutationOutputSelect ::
|
|
||||||
(MonadError QErr m) =>
|
|
||||||
StringifyNumbers ->
|
|
||||||
Text ->
|
|
||||||
MutationOutputG 'MSSQL Void Expression ->
|
|
||||||
m Select
|
|
||||||
mkMutationOutputSelect stringifyNum withAlias = \case
|
|
||||||
IR.MOutMultirowFields multiRowFields -> do
|
|
||||||
projections <- forM multiRowFields $ \(fieldName, field') -> do
|
|
||||||
let mkProjection = ExpressionProjection . flip Aliased (getFieldNameTxt fieldName) . SelectExpression
|
|
||||||
mkProjection <$> case field' of
|
|
||||||
IR.MCount -> pure $ countSelect withAlias
|
|
||||||
IR.MExp t -> pure $ textSelect t
|
|
||||||
IR.MRet returningFields -> mkSelect stringifyNum withAlias JASMultipleRows returningFields
|
|
||||||
let forJson = JsonFor $ ForJson JsonSingleton NoRoot
|
|
||||||
pure emptySelect {selectFor = forJson, selectProjections = projections}
|
|
||||||
IR.MOutSinglerowObject singleRowField -> mkSelect stringifyNum withAlias JASSingleObject singleRowField
|
|
||||||
|
|
||||||
-- | Generate a SQL SELECT statement which outputs the mutation response and check constraint result
|
|
||||||
--
|
|
||||||
-- The check constraint boolean expression is evaluated on mutated rows in a CASE expression so that
|
|
||||||
-- the int value "0" is returned when check constraint is true otherwise the int value "1" is returned.
|
|
||||||
-- We use "SUM" aggregation on the returned value and if check constraint on any row is not met, the summed
|
|
||||||
-- value will not equal to "0" (always > 1).
|
|
||||||
--
|
|
||||||
-- <check_constraint_select> :=
|
|
||||||
-- SELECT SUM(CASE WHEN <check_boolean_expression> THEN 0 ELSE 1 END) FROM [with_alias]
|
|
||||||
--
|
|
||||||
-- <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
|
|
||||||
--
|
|
||||||
-- SELECT (<mutation_output_select>) AS [mutation_response], (<check_constraint_select>) AS [check_constraint_select]
|
|
||||||
selectMutationOutputAndCheckCondition :: Text -> Select -> Expression -> Select
|
|
||||||
selectMutationOutputAndCheckCondition alias mutationOutputSelect checkBoolExp =
|
|
||||||
let mutationOutputProjection =
|
|
||||||
ExpressionProjection $ Aliased (SelectExpression mutationOutputSelect) "mutation_response"
|
|
||||||
checkConstraintProjection =
|
|
||||||
-- apply ISNULL() to avoid check constraint select statement yielding empty rows
|
|
||||||
ExpressionProjection $
|
|
||||||
Aliased (FunctionApplicationExpression $ FunExpISNULL (SelectExpression checkConstraintSelect) (ValueExpression (ODBC.IntValue 0))) "check_constraint_select"
|
|
||||||
in emptySelect {selectProjections = [mutationOutputProjection, checkConstraintProjection]}
|
|
||||||
where
|
|
||||||
checkConstraintSelect =
|
|
||||||
let zeroValue = ValueExpression $ ODBC.IntValue 0
|
|
||||||
oneValue = ValueExpression $ ODBC.IntValue 1
|
|
||||||
caseExpression = ConditionalExpression checkBoolExp zeroValue oneValue
|
|
||||||
sumAggregate = OpAggregate "SUM" [caseExpression]
|
|
||||||
in emptySelect
|
|
||||||
{ selectProjections = [AggregateProjection (Aliased sumAggregate "check")],
|
|
||||||
selectFrom = Just $ TSQL.FromIdentifier alias
|
|
||||||
}
|
|
||||||
|
|
||||||
mkSelect ::
|
|
||||||
MonadError QErr m =>
|
|
||||||
StringifyNumbers ->
|
|
||||||
Text ->
|
|
||||||
JsonAggSelect ->
|
|
||||||
Fields (AnnFieldG 'MSSQL Void Expression) ->
|
|
||||||
m Select
|
|
||||||
mkSelect stringifyNum withAlias jsonAggSelect annFields = do
|
|
||||||
let annSelect = IR.AnnSelectG annFields (IR.FromIdentifier $ FIIdentifier withAlias) IR.noTablePermissions IR.noSelectArgs stringifyNum
|
|
||||||
V.runValidate (runFromIr $ mkSQLSelect jsonAggSelect annSelect) `onLeft` (throw500 . tshow)
|
|
||||||
|
|
||||||
-- SELECT COUNT(*) AS "count" FROM [with_alias]
|
|
||||||
countSelect :: Text -> Select
|
|
||||||
countSelect withAlias =
|
|
||||||
let countProjection = AggregateProjection $ Aliased (CountAggregate StarCountable) "count"
|
|
||||||
in emptySelect
|
|
||||||
{ selectProjections = [countProjection],
|
|
||||||
selectFrom = Just $ TSQL.FromIdentifier withAlias
|
|
||||||
}
|
|
||||||
|
|
||||||
-- SELECT '<text-value>' AS "exp"
|
|
||||||
textSelect :: Text -> Select
|
|
||||||
textSelect t =
|
|
||||||
let textProjection = ExpressionProjection $ Aliased (ValueExpression (ODBC.TextValue t)) "exp"
|
|
||||||
in emptySelect {selectProjections = [textProjection]}
|
|
@ -9,11 +9,14 @@ module Hasura.Backends.MSSQL.Execute.Update
|
|||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Control.Monad.Validate qualified as V
|
|
||||||
import Database.MSSQL.Transaction qualified as Tx
|
import Database.MSSQL.Transaction qualified as Tx
|
||||||
import Hasura.Backends.MSSQL.Connection
|
import Hasura.Backends.MSSQL.Connection
|
||||||
import Hasura.Backends.MSSQL.Execute.MutationResponse
|
|
||||||
import Hasura.Backends.MSSQL.FromIr as TSQL
|
import Hasura.Backends.MSSQL.FromIr as TSQL
|
||||||
|
import Hasura.Backends.MSSQL.FromIr.Constants (tempTableNameUpdated)
|
||||||
|
import Hasura.Backends.MSSQL.FromIr.Expression (fromGBoolExp)
|
||||||
|
import Hasura.Backends.MSSQL.FromIr.MutationResponse
|
||||||
|
import Hasura.Backends.MSSQL.FromIr.SelectIntoTempTable qualified as TSQL
|
||||||
|
import Hasura.Backends.MSSQL.FromIr.Update qualified as TSQL
|
||||||
import Hasura.Backends.MSSQL.Plan
|
import Hasura.Backends.MSSQL.Plan
|
||||||
import Hasura.Backends.MSSQL.SQL.Error
|
import Hasura.Backends.MSSQL.SQL.Error
|
||||||
import Hasura.Backends.MSSQL.ToQuery as TQ
|
import Hasura.Backends.MSSQL.ToQuery as TQ
|
||||||
@ -72,15 +75,13 @@ buildUpdateTx updateOperation stringifyNum = do
|
|||||||
-- Create a temp table
|
-- Create a temp table
|
||||||
Tx.unitQueryE defaultMSSQLTxErrorHandler createInsertedTempTableQuery
|
Tx.unitQueryE defaultMSSQLTxErrorHandler createInsertedTempTableQuery
|
||||||
let updateQuery = TQ.fromUpdate <$> TSQL.fromUpdate updateOperation
|
let updateQuery = TQ.fromUpdate <$> TSQL.fromUpdate updateOperation
|
||||||
updateQueryValidated <- toQueryFlat <$> V.runValidate (runFromIr updateQuery) `onLeft` (throw500 . tshow)
|
updateQueryValidated <- toQueryFlat <$> runFromIr updateQuery
|
||||||
-- Execute UPDATE statement
|
-- Execute UPDATE statement
|
||||||
Tx.unitQueryE mutationMSSQLTxErrorHandler updateQueryValidated
|
Tx.unitQueryE mutationMSSQLTxErrorHandler updateQueryValidated
|
||||||
mutationOutputSelect <- mkMutationOutputSelect stringifyNum withAlias $ _auOutput updateOperation
|
mutationOutputSelect <- runFromIr $ mkMutationOutputSelect stringifyNum withAlias $ _auOutput updateOperation
|
||||||
let checkCondition = _auCheck updateOperation
|
let checkCondition = _auCheck updateOperation
|
||||||
-- The check constraint is translated to boolean expression
|
-- The check constraint is translated to boolean expression
|
||||||
checkBoolExp <-
|
checkBoolExp <- runFromIr $ runReaderT (fromGBoolExp checkCondition) (EntityAlias withAlias)
|
||||||
V.runValidate (runFromIr $ runReaderT (fromGBoolExp checkCondition) (EntityAlias withAlias))
|
|
||||||
`onLeft` (throw500 . tshow)
|
|
||||||
|
|
||||||
let withSelect =
|
let withSelect =
|
||||||
emptySelect
|
emptySelect
|
||||||
|
File diff suppressed because it is too large
Load Diff
56
server/src-lib/Hasura/Backends/MSSQL/FromIr/Constants.hs
Normal file
56
server/src-lib/Hasura/Backends/MSSQL/FromIr/Constants.hs
Normal file
@ -0,0 +1,56 @@
|
|||||||
|
-- | This module provides constants that are either:
|
||||||
|
--
|
||||||
|
-- * Simply in common user
|
||||||
|
-- * Define names that that multiple pieces of code reference.
|
||||||
|
module Hasura.Backends.MSSQL.FromIr.Constants
|
||||||
|
( trueExpression,
|
||||||
|
nullExpression,
|
||||||
|
emptyArrayExpression,
|
||||||
|
jsonFieldName,
|
||||||
|
aggSubselectName,
|
||||||
|
existsFieldName,
|
||||||
|
aggFieldName,
|
||||||
|
tempTableNameInserted,
|
||||||
|
tempTableNameValues,
|
||||||
|
tempTableNameDeleted,
|
||||||
|
tempTableNameUpdated,
|
||||||
|
)
|
||||||
|
where
|
||||||
|
|
||||||
|
import Database.ODBC.SQLServer qualified as ODBC
|
||||||
|
import Hasura.Backends.MSSQL.Instances.Types ()
|
||||||
|
import Hasura.Backends.MSSQL.Types.Internal as TSQL
|
||||||
|
import Hasura.Prelude
|
||||||
|
|
||||||
|
trueExpression :: Expression
|
||||||
|
trueExpression = ValueExpression (ODBC.BoolValue True)
|
||||||
|
|
||||||
|
nullExpression :: Expression
|
||||||
|
nullExpression = ValueExpression $ ODBC.TextValue "null"
|
||||||
|
|
||||||
|
emptyArrayExpression :: Expression
|
||||||
|
emptyArrayExpression = ValueExpression $ ODBC.TextValue "[]"
|
||||||
|
|
||||||
|
jsonFieldName :: Text
|
||||||
|
jsonFieldName = "json"
|
||||||
|
|
||||||
|
aggSubselectName :: Text
|
||||||
|
aggSubselectName = "agg_sub"
|
||||||
|
|
||||||
|
existsFieldName :: Text
|
||||||
|
existsFieldName = "exists_placeholder"
|
||||||
|
|
||||||
|
aggFieldName :: Text
|
||||||
|
aggFieldName = "agg"
|
||||||
|
|
||||||
|
tempTableNameInserted :: TempTableName
|
||||||
|
tempTableNameInserted = TempTableName "inserted"
|
||||||
|
|
||||||
|
tempTableNameValues :: TempTableName
|
||||||
|
tempTableNameValues = TempTableName "values"
|
||||||
|
|
||||||
|
tempTableNameDeleted :: TempTableName
|
||||||
|
tempTableNameDeleted = TempTableName "deleted"
|
||||||
|
|
||||||
|
tempTableNameUpdated :: TempTableName
|
||||||
|
tempTableNameUpdated = TempTableName "updated"
|
35
server/src-lib/Hasura/Backends/MSSQL/FromIr/Delete.hs
Normal file
35
server/src-lib/Hasura/Backends/MSSQL/FromIr/Delete.hs
Normal file
@ -0,0 +1,35 @@
|
|||||||
|
-- | This module defines the translation function for delete mutations.
|
||||||
|
module Hasura.Backends.MSSQL.FromIr.Delete (fromDelete) where
|
||||||
|
|
||||||
|
import Hasura.Backends.MSSQL.FromIr (FromIr, NameTemplate (..), generateAlias)
|
||||||
|
import Hasura.Backends.MSSQL.FromIr.Constants (tempTableNameDeleted)
|
||||||
|
import Hasura.Backends.MSSQL.FromIr.Expression (fromGBoolExp)
|
||||||
|
import Hasura.Backends.MSSQL.Instances.Types ()
|
||||||
|
import Hasura.Backends.MSSQL.Types.Internal as TSQL
|
||||||
|
import Hasura.Prelude
|
||||||
|
import Hasura.RQL.IR qualified as IR
|
||||||
|
import Hasura.RQL.Types.Column qualified as IR
|
||||||
|
import Hasura.SQL.Backend
|
||||||
|
import Language.GraphQL.Draft.Syntax (unName)
|
||||||
|
|
||||||
|
fromDelete :: IR.AnnDel 'MSSQL -> FromIr Delete
|
||||||
|
fromDelete (IR.AnnDel table (permFilter, whereClause) _ allColumns) = do
|
||||||
|
tableAlias <- generateAlias (TableTemplate (tableName table))
|
||||||
|
runReaderT
|
||||||
|
( do
|
||||||
|
permissionsFilter <- fromGBoolExp permFilter
|
||||||
|
whereExpression <- fromGBoolExp whereClause
|
||||||
|
let columnNames = map (ColumnName . unName . IR.ciName) allColumns
|
||||||
|
pure
|
||||||
|
Delete
|
||||||
|
{ deleteTable =
|
||||||
|
Aliased
|
||||||
|
{ aliasedAlias = tableAlias,
|
||||||
|
aliasedThing = table
|
||||||
|
},
|
||||||
|
deleteOutput = Output Deleted (map OutputColumn columnNames),
|
||||||
|
deleteTempTable = TempTable tempTableNameDeleted columnNames,
|
||||||
|
deleteWhere = Where [permissionsFilter, whereExpression]
|
||||||
|
}
|
||||||
|
)
|
||||||
|
(EntityAlias tableAlias)
|
217
server/src-lib/Hasura/Backends/MSSQL/FromIr/Expression.hs
Normal file
217
server/src-lib/Hasura/Backends/MSSQL/FromIr/Expression.hs
Normal file
@ -0,0 +1,217 @@
|
|||||||
|
-- | This module translates the IR of boolean expressions into TSQL boolean
|
||||||
|
-- expressions.
|
||||||
|
--
|
||||||
|
-- Boolean expressions typically arise from permissions and where-clause
|
||||||
|
-- filters.
|
||||||
|
module Hasura.Backends.MSSQL.FromIr.Expression
|
||||||
|
( fromGBoolExp,
|
||||||
|
)
|
||||||
|
where
|
||||||
|
|
||||||
|
import Control.Monad.Validate
|
||||||
|
import Data.HashMap.Strict qualified as HM
|
||||||
|
import Hasura.Backends.MSSQL.FromIr
|
||||||
|
( Error (UnsupportedOpExpG),
|
||||||
|
FromIr,
|
||||||
|
NameTemplate (TableTemplate),
|
||||||
|
generateAlias,
|
||||||
|
)
|
||||||
|
import Hasura.Backends.MSSQL.FromIr.Constants (existsFieldName, trueExpression)
|
||||||
|
import Hasura.Backends.MSSQL.Instances.Types ()
|
||||||
|
import Hasura.Backends.MSSQL.Types.Internal as TSQL
|
||||||
|
import Hasura.Prelude
|
||||||
|
import Hasura.RQL.IR qualified as IR
|
||||||
|
import Hasura.RQL.Types.Column qualified as IR
|
||||||
|
import Hasura.RQL.Types.Relationships.Local qualified as IR
|
||||||
|
import Hasura.SQL.Backend
|
||||||
|
|
||||||
|
-- | Translate boolean expressions into TSQL 'Expression's.
|
||||||
|
--
|
||||||
|
-- The `IR.AnnBoolExpFld` references fields and columns. The entity (e.g. table)
|
||||||
|
-- that binds these columns is supplied in the `ReaderT EntityAlias`
|
||||||
|
-- environment, such that the columns can be referred to unambiguously.
|
||||||
|
fromGBoolExp ::
|
||||||
|
IR.GBoolExp 'MSSQL (IR.AnnBoolExpFld 'MSSQL Expression) ->
|
||||||
|
ReaderT EntityAlias FromIr Expression
|
||||||
|
fromGBoolExp =
|
||||||
|
\case
|
||||||
|
IR.BoolAnd expressions ->
|
||||||
|
fmap AndExpression (traverse fromGBoolExp expressions)
|
||||||
|
IR.BoolOr expressions ->
|
||||||
|
fmap OrExpression (traverse fromGBoolExp expressions)
|
||||||
|
IR.BoolNot expression ->
|
||||||
|
fmap NotExpression (fromGBoolExp expression)
|
||||||
|
IR.BoolExists gExists ->
|
||||||
|
fromGExists gExists
|
||||||
|
IR.BoolFld expression ->
|
||||||
|
fromAnnBoolExpFld expression
|
||||||
|
where
|
||||||
|
fromGExists :: IR.GExists 'MSSQL (IR.AnnBoolExpFld 'MSSQL Expression) -> ReaderT EntityAlias FromIr Expression
|
||||||
|
fromGExists IR.GExists {_geTable, _geWhere} = do
|
||||||
|
selectFrom <- lift (aliasQualifiedTable _geTable)
|
||||||
|
scopedTo selectFrom $ do
|
||||||
|
whereExpression <- fromGBoolExp _geWhere
|
||||||
|
pure $
|
||||||
|
ExistsExpression $
|
||||||
|
emptySelect
|
||||||
|
{ selectOrderBy = Nothing,
|
||||||
|
selectProjections =
|
||||||
|
[ ExpressionProjection
|
||||||
|
( Aliased
|
||||||
|
{ aliasedThing = trueExpression,
|
||||||
|
aliasedAlias = existsFieldName
|
||||||
|
}
|
||||||
|
)
|
||||||
|
],
|
||||||
|
selectFrom = Just selectFrom,
|
||||||
|
selectJoins = mempty,
|
||||||
|
selectWhere = Where [whereExpression],
|
||||||
|
selectTop = NoTop,
|
||||||
|
selectFor = NoFor,
|
||||||
|
selectOffset = Nothing
|
||||||
|
}
|
||||||
|
|
||||||
|
-- | Translate boolean expressions into TSQL 'Expression's.
|
||||||
|
--
|
||||||
|
-- The `IR.AnnBoolExpFld` references fields and columns. The entity (e.g. table)
|
||||||
|
-- that binds these columns is supplied in the `ReaderT EntityAlias`
|
||||||
|
-- environment, such that the columns can be referred to unambiguously.
|
||||||
|
fromAnnBoolExpFld ::
|
||||||
|
IR.AnnBoolExpFld 'MSSQL Expression ->
|
||||||
|
ReaderT EntityAlias FromIr Expression
|
||||||
|
fromAnnBoolExpFld =
|
||||||
|
\case
|
||||||
|
IR.AVColumn columnInfo opExpGs -> do
|
||||||
|
expressions <- traverse (fromOpExpG columnInfo) opExpGs
|
||||||
|
pure (AndExpression expressions)
|
||||||
|
IR.AVRelationship IR.RelInfo {riMapping = mapping, riRTable = table} annBoolExp -> do
|
||||||
|
selectFrom <- lift (aliasQualifiedTable table)
|
||||||
|
mappingExpression <- translateMapping selectFrom mapping
|
||||||
|
whereExpression <- scopedTo selectFrom (fromGBoolExp annBoolExp)
|
||||||
|
pure
|
||||||
|
( ExistsExpression
|
||||||
|
emptySelect
|
||||||
|
{ selectOrderBy = Nothing,
|
||||||
|
selectProjections =
|
||||||
|
[ ExpressionProjection
|
||||||
|
( Aliased
|
||||||
|
{ aliasedThing = trueExpression,
|
||||||
|
aliasedAlias = existsFieldName
|
||||||
|
}
|
||||||
|
)
|
||||||
|
],
|
||||||
|
selectFrom = Just selectFrom,
|
||||||
|
selectJoins = mempty,
|
||||||
|
selectWhere = Where (mappingExpression <> [whereExpression]),
|
||||||
|
selectTop = NoTop,
|
||||||
|
selectFor = NoFor,
|
||||||
|
selectOffset = Nothing
|
||||||
|
}
|
||||||
|
)
|
||||||
|
where
|
||||||
|
-- Translate a relationship field mapping into column equality comparisons.
|
||||||
|
translateMapping ::
|
||||||
|
From ->
|
||||||
|
HashMap ColumnName ColumnName ->
|
||||||
|
ReaderT EntityAlias FromIr [Expression]
|
||||||
|
translateMapping localFrom =
|
||||||
|
traverse
|
||||||
|
( \(remoteColumn, localColumn) -> do
|
||||||
|
localFieldName <- scopedTo localFrom (fromColumn localColumn)
|
||||||
|
remoteFieldName <- fromColumn remoteColumn
|
||||||
|
pure
|
||||||
|
( OpExpression
|
||||||
|
TSQL.EQ'
|
||||||
|
(ColumnExpression localFieldName)
|
||||||
|
(ColumnExpression remoteFieldName)
|
||||||
|
)
|
||||||
|
)
|
||||||
|
. HM.toList
|
||||||
|
|
||||||
|
-- | Scope a translation action to the table bound in a FROM clause.
|
||||||
|
scopedTo :: From -> ReaderT EntityAlias FromIr a -> ReaderT EntityAlias FromIr a
|
||||||
|
scopedTo from = local (const (fromAlias from))
|
||||||
|
|
||||||
|
-- | Translate a column reference occurring in a boolean expression into an
|
||||||
|
-- equivalent 'Expression'.
|
||||||
|
--
|
||||||
|
-- Different text types support different operators. Therefore we cast some text
|
||||||
|
-- types to "varchar(max)", which supports the most operators.
|
||||||
|
fromColumnInfo :: IR.ColumnInfo 'MSSQL -> ReaderT EntityAlias FromIr Expression
|
||||||
|
fromColumnInfo IR.ColumnInfo {ciColumn = column, ciType} = do
|
||||||
|
fieldName <- TSQL.columnNameToFieldName column <$> ask
|
||||||
|
if shouldCastToVarcharMax ciType
|
||||||
|
then pure (CastExpression (ColumnExpression fieldName) WvarcharType DataLengthMax)
|
||||||
|
else pure (ColumnExpression fieldName)
|
||||||
|
where
|
||||||
|
shouldCastToVarcharMax :: IR.ColumnType 'MSSQL -> Bool
|
||||||
|
shouldCastToVarcharMax typ =
|
||||||
|
typ == IR.ColumnScalar TextType || typ == IR.ColumnScalar WtextType
|
||||||
|
|
||||||
|
-- | Get FieldSource from a TAFExp type table aggregate field
|
||||||
|
fromColumn :: ColumnName -> ReaderT EntityAlias FromIr FieldName
|
||||||
|
fromColumn column = columnNameToFieldName column <$> ask
|
||||||
|
|
||||||
|
-- | Translate a single `IR.OpExpG` operation on a column into an expression.
|
||||||
|
fromOpExpG :: IR.ColumnInfo 'MSSQL -> IR.OpExpG 'MSSQL Expression -> ReaderT EntityAlias FromIr Expression
|
||||||
|
fromOpExpG columnInfo op = do
|
||||||
|
column <- fromColumnInfo columnInfo
|
||||||
|
case op of
|
||||||
|
IR.ANISNULL -> pure $ TSQL.IsNullExpression column
|
||||||
|
IR.ANISNOTNULL -> pure $ TSQL.IsNotNullExpression column
|
||||||
|
IR.AEQ False val -> pure $ nullableBoolEquality column val
|
||||||
|
IR.AEQ True val -> pure $ OpExpression TSQL.EQ' column val
|
||||||
|
IR.ANE False val -> pure $ nullableBoolInequality column val
|
||||||
|
IR.ANE True val -> pure $ OpExpression TSQL.NEQ' column val
|
||||||
|
IR.AGT val -> pure $ OpExpression TSQL.GT column val
|
||||||
|
IR.ALT val -> pure $ OpExpression TSQL.LT column val
|
||||||
|
IR.AGTE val -> pure $ OpExpression TSQL.GTE column val
|
||||||
|
IR.ALTE val -> pure $ OpExpression TSQL.LTE column val
|
||||||
|
IR.AIN val -> pure $ OpExpression TSQL.IN column val
|
||||||
|
IR.ANIN val -> pure $ OpExpression TSQL.NIN column val
|
||||||
|
IR.ALIKE val -> pure $ OpExpression TSQL.LIKE column val
|
||||||
|
IR.ANLIKE val -> pure $ OpExpression TSQL.NLIKE column val
|
||||||
|
IR.ABackendSpecific o -> case o of
|
||||||
|
ASTContains val -> pure $ TSQL.STOpExpression TSQL.STContains column val
|
||||||
|
ASTCrosses val -> pure $ TSQL.STOpExpression TSQL.STCrosses column val
|
||||||
|
ASTEquals val -> pure $ TSQL.STOpExpression TSQL.STEquals column val
|
||||||
|
ASTIntersects val -> pure $ TSQL.STOpExpression TSQL.STIntersects column val
|
||||||
|
ASTOverlaps val -> pure $ TSQL.STOpExpression TSQL.STOverlaps column val
|
||||||
|
ASTTouches val -> pure $ TSQL.STOpExpression TSQL.STTouches column val
|
||||||
|
ASTWithin val -> pure $ TSQL.STOpExpression TSQL.STWithin column val
|
||||||
|
-- As of March 2021, only geometry/geography casts are supported
|
||||||
|
IR.ACast _casts -> refute (pure (UnsupportedOpExpG op)) -- mkCastsExp casts
|
||||||
|
|
||||||
|
-- We do not yet support column names in permissions
|
||||||
|
IR.CEQ _rhsCol -> refute (pure (UnsupportedOpExpG op)) -- S.BECompare S.SEQ lhs $ mkQCol rhsCol
|
||||||
|
IR.CNE _rhsCol -> refute (pure (UnsupportedOpExpG op)) -- S.BECompare S.SNE lhs $ mkQCol rhsCol
|
||||||
|
IR.CGT _rhsCol -> refute (pure (UnsupportedOpExpG op)) -- S.BECompare S.SGT lhs $ mkQCol rhsCol
|
||||||
|
IR.CLT _rhsCol -> refute (pure (UnsupportedOpExpG op)) -- S.BECompare S.SLT lhs $ mkQCol rhsCol
|
||||||
|
IR.CGTE _rhsCol -> refute (pure (UnsupportedOpExpG op)) -- S.BECompare S.SGTE lhs $ mkQCol rhsCol
|
||||||
|
IR.CLTE _rhsCol -> refute (pure (UnsupportedOpExpG op)) -- S.BECompare S.SLTE lhs $ mkQCol rhsCol
|
||||||
|
|
||||||
|
nullableBoolEquality :: Expression -> Expression -> Expression
|
||||||
|
nullableBoolEquality x y =
|
||||||
|
OrExpression
|
||||||
|
[ OpExpression TSQL.EQ' x y,
|
||||||
|
AndExpression [IsNullExpression x, IsNullExpression y]
|
||||||
|
]
|
||||||
|
|
||||||
|
nullableBoolInequality :: Expression -> Expression -> Expression
|
||||||
|
nullableBoolInequality x y =
|
||||||
|
OrExpression
|
||||||
|
[ OpExpression TSQL.NEQ' x y,
|
||||||
|
AndExpression [IsNotNullExpression x, IsNullExpression y]
|
||||||
|
]
|
||||||
|
|
||||||
|
aliasQualifiedTable :: TableName -> FromIr From
|
||||||
|
aliasQualifiedTable schemadTableName@(TableName {tableName}) = do
|
||||||
|
alias <- generateAlias (TableTemplate tableName)
|
||||||
|
pure
|
||||||
|
( FromQualifiedTable
|
||||||
|
( Aliased
|
||||||
|
{ aliasedThing = schemadTableName,
|
||||||
|
aliasedAlias = alias
|
||||||
|
}
|
||||||
|
)
|
||||||
|
)
|
117
server/src-lib/Hasura/Backends/MSSQL/FromIr/Insert.hs
Normal file
117
server/src-lib/Hasura/Backends/MSSQL/FromIr/Insert.hs
Normal file
@ -0,0 +1,117 @@
|
|||||||
|
-- | This module defines the translation functions for insert and upsert
|
||||||
|
-- mutations.
|
||||||
|
module Hasura.Backends.MSSQL.FromIr.Insert
|
||||||
|
( fromInsert,
|
||||||
|
toMerge,
|
||||||
|
toInsertValuesIntoTempTable,
|
||||||
|
)
|
||||||
|
where
|
||||||
|
|
||||||
|
import Data.Containers.ListUtils (nubOrd)
|
||||||
|
import Data.HashMap.Strict qualified as HM
|
||||||
|
import Hasura.Backends.MSSQL.FromIr (FromIr)
|
||||||
|
import Hasura.Backends.MSSQL.FromIr.Constants (tempTableNameInserted, tempTableNameValues)
|
||||||
|
import Hasura.Backends.MSSQL.FromIr.Expression (fromGBoolExp)
|
||||||
|
import Hasura.Backends.MSSQL.Instances.Types ()
|
||||||
|
import Hasura.Backends.MSSQL.Types.Insert (IfMatched (..))
|
||||||
|
import Hasura.Backends.MSSQL.Types.Internal as TSQL
|
||||||
|
import Hasura.Prelude
|
||||||
|
import Hasura.RQL.IR qualified as IR
|
||||||
|
import Hasura.RQL.Types.Column qualified as IR
|
||||||
|
import Hasura.SQL.Backend
|
||||||
|
import Language.GraphQL.Draft.Syntax (unName)
|
||||||
|
|
||||||
|
fromInsert :: IR.AnnInsert 'MSSQL Void Expression -> Insert
|
||||||
|
fromInsert IR.AnnInsert {..} =
|
||||||
|
let IR.AnnIns {..} = _aiData
|
||||||
|
insertRows = normalizeInsertRows $ map (IR.getInsertColumns) _aiInsObj
|
||||||
|
insertColumnNames = maybe [] (map fst) $ listToMaybe insertRows
|
||||||
|
insertValues = map (Values . map snd) insertRows
|
||||||
|
allColumnNames = map (ColumnName . unName . IR.ciName) _aiTableCols
|
||||||
|
insertOutput = Output Inserted $ map OutputColumn allColumnNames
|
||||||
|
tempTable = TempTable tempTableNameInserted allColumnNames
|
||||||
|
in Insert _aiTableName insertColumnNames insertOutput tempTable insertValues
|
||||||
|
|
||||||
|
-- | Normalize a row by adding missing columns with @DEFAULT@ value and sort by
|
||||||
|
-- column name to make sure all rows are consistent in column values and order.
|
||||||
|
--
|
||||||
|
-- Example: A table "author" is defined as:
|
||||||
|
--
|
||||||
|
-- > CREATE TABLE author ([id] INTEGER NOT NULL PRIMARY KEY, name TEXT NOT NULL, age INTEGER)
|
||||||
|
--
|
||||||
|
-- Consider the following mutation:
|
||||||
|
--
|
||||||
|
-- > mutation {
|
||||||
|
-- > insert_author(
|
||||||
|
-- > objects: [{id: 1, name: "Foo", age: 21}, {id: 2, name: "Bar"}]
|
||||||
|
-- > ){
|
||||||
|
-- > affected_rows
|
||||||
|
-- > }
|
||||||
|
-- > }
|
||||||
|
--
|
||||||
|
-- We consider @DEFAULT@ value for @age@ column which is missing in second
|
||||||
|
-- insert row.
|
||||||
|
--
|
||||||
|
-- The corresponding @INSERT@ statement looks like:
|
||||||
|
--
|
||||||
|
-- > INSERT INTO author (id, name, age)
|
||||||
|
-- > OUTPUT INSERTED.id
|
||||||
|
-- > VALUES (1, 'Foo', 21), (2, 'Bar', DEFAULT)
|
||||||
|
normalizeInsertRows ::
|
||||||
|
[[(Column 'MSSQL, Expression)]] ->
|
||||||
|
[[(Column 'MSSQL, Expression)]]
|
||||||
|
normalizeInsertRows insertRows =
|
||||||
|
let insertColumns = nubOrd (concatMap (map fst) insertRows)
|
||||||
|
allColumnsWithDefaultValue = map (,DefaultExpression) $ insertColumns
|
||||||
|
addMissingColumns insertRow =
|
||||||
|
HM.toList $ HM.fromList insertRow `HM.union` HM.fromList allColumnsWithDefaultValue
|
||||||
|
sortByColumn = sortBy (\l r -> compare (fst l) (fst r))
|
||||||
|
in map (sortByColumn . addMissingColumns) insertRows
|
||||||
|
|
||||||
|
-- | Construct a MERGE statement from AnnInsert information.
|
||||||
|
-- A MERGE statement is responsible for actually inserting and/or updating
|
||||||
|
-- the data in the table.
|
||||||
|
toMerge ::
|
||||||
|
TableName ->
|
||||||
|
[IR.AnnotatedInsertRow 'MSSQL Expression] ->
|
||||||
|
[IR.ColumnInfo 'MSSQL] ->
|
||||||
|
IfMatched Expression ->
|
||||||
|
FromIr Merge
|
||||||
|
toMerge tableName insertRows allColumns IfMatched {..} = do
|
||||||
|
let normalizedInsertRows = normalizeInsertRows $ map (IR.getInsertColumns) insertRows
|
||||||
|
insertColumnNames = maybe [] (map fst) $ listToMaybe normalizedInsertRows
|
||||||
|
allColumnNames = map (ColumnName . unName . IR.ciName) allColumns
|
||||||
|
|
||||||
|
matchConditions <-
|
||||||
|
flip runReaderT (EntityAlias "target") $ -- the table is aliased as "target" in MERGE sql
|
||||||
|
fromGBoolExp _imConditions
|
||||||
|
|
||||||
|
pure $
|
||||||
|
Merge
|
||||||
|
{ mergeTargetTable = tableName,
|
||||||
|
mergeUsing = MergeUsing tempTableNameValues insertColumnNames,
|
||||||
|
mergeOn = MergeOn _imMatchColumns,
|
||||||
|
mergeWhenMatched = MergeWhenMatched _imUpdateColumns matchConditions _imColumnPresets,
|
||||||
|
mergeWhenNotMatched = MergeWhenNotMatched insertColumnNames,
|
||||||
|
mergeInsertOutput = Output Inserted $ map OutputColumn allColumnNames,
|
||||||
|
mergeOutputTempTable = TempTable tempTableNameInserted allColumnNames
|
||||||
|
}
|
||||||
|
|
||||||
|
-- | As part of an INSERT/UPSERT process, insert VALUES into a temporary table.
|
||||||
|
-- The content of the temporary table will later be inserted into the original table
|
||||||
|
-- using a MERGE statement.
|
||||||
|
--
|
||||||
|
-- We insert the values into a temporary table first in order to replace the missing
|
||||||
|
-- fields with @DEFAULT@ in @normalizeInsertRows@, and we can't do that in a
|
||||||
|
-- MERGE statement directly.
|
||||||
|
toInsertValuesIntoTempTable :: TempTableName -> IR.AnnInsert 'MSSQL Void Expression -> InsertValuesIntoTempTable
|
||||||
|
toInsertValuesIntoTempTable tempTable IR.AnnInsert {..} =
|
||||||
|
let IR.AnnIns {..} = _aiData
|
||||||
|
insertRows = normalizeInsertRows $ map IR.getInsertColumns _aiInsObj
|
||||||
|
insertColumnNames = maybe [] (map fst) $ listToMaybe insertRows
|
||||||
|
insertValues = map (Values . map snd) insertRows
|
||||||
|
in InsertValuesIntoTempTable
|
||||||
|
{ ivittTempTableName = tempTable,
|
||||||
|
ivittColumns = insertColumnNames,
|
||||||
|
ivittValues = insertValues
|
||||||
|
}
|
119
server/src-lib/Hasura/Backends/MSSQL/FromIr/MutationResponse.hs
Normal file
119
server/src-lib/Hasura/Backends/MSSQL/FromIr/MutationResponse.hs
Normal file
@ -0,0 +1,119 @@
|
|||||||
|
-- | This module defines translation functions that yield the results of
|
||||||
|
-- mutation requests that return the data of rows that were affected.
|
||||||
|
module Hasura.Backends.MSSQL.FromIr.MutationResponse
|
||||||
|
( mkMutationOutputSelect,
|
||||||
|
selectMutationOutputAndCheckCondition,
|
||||||
|
)
|
||||||
|
where
|
||||||
|
|
||||||
|
import Database.ODBC.SQLServer qualified as ODBC
|
||||||
|
import Hasura.Backends.MSSQL.FromIr (FromIr)
|
||||||
|
import Hasura.Backends.MSSQL.FromIr.Query (fromSelect)
|
||||||
|
import Hasura.Backends.MSSQL.Instances.Types ()
|
||||||
|
import Hasura.Backends.MSSQL.Types.Internal as TSQL
|
||||||
|
import Hasura.Prelude
|
||||||
|
import Hasura.RQL.IR qualified as IR
|
||||||
|
import Hasura.RQL.IR.Returning (MutationOutputG)
|
||||||
|
import Hasura.RQL.Types.Common qualified as IR
|
||||||
|
import Hasura.SQL.Backend
|
||||||
|
|
||||||
|
-- | Generate a SQL SELECT statement which outputs the mutation response
|
||||||
|
--
|
||||||
|
-- For multi row inserts:
|
||||||
|
--
|
||||||
|
-- SELECT
|
||||||
|
-- (SELECT COUNT(*) FROM [with_alias]) AS [affected_rows],
|
||||||
|
-- (select_from_returning) AS [returning]
|
||||||
|
-- FOR JSON PATH, INCLUDE_NULL_VALUES, WITHOUT_ARRAY_WRAPPER
|
||||||
|
--
|
||||||
|
-- For single row insert: the selection set is translated to SQL query using @'fromSelect'
|
||||||
|
mkMutationOutputSelect ::
|
||||||
|
IR.StringifyNumbers ->
|
||||||
|
Text ->
|
||||||
|
MutationOutputG 'MSSQL Void Expression ->
|
||||||
|
FromIr Select
|
||||||
|
mkMutationOutputSelect stringifyNum withAlias = \case
|
||||||
|
IR.MOutMultirowFields multiRowFields -> do
|
||||||
|
projections <- forM multiRowFields $ \(fieldName, field') -> do
|
||||||
|
let mkProjection = ExpressionProjection . flip Aliased (IR.getFieldNameTxt fieldName) . SelectExpression
|
||||||
|
mkProjection <$> case field' of
|
||||||
|
IR.MCount -> pure $ countSelect
|
||||||
|
IR.MExp t -> pure $ textSelect t
|
||||||
|
IR.MRet returningFields -> mkSelect IR.JASMultipleRows returningFields
|
||||||
|
let forJson = JsonFor $ ForJson JsonSingleton NoRoot
|
||||||
|
pure emptySelect {selectFor = forJson, selectProjections = projections}
|
||||||
|
IR.MOutSinglerowObject singleRowField -> mkSelect IR.JASSingleObject singleRowField
|
||||||
|
where
|
||||||
|
mkSelect ::
|
||||||
|
IR.JsonAggSelect ->
|
||||||
|
IR.Fields (IR.AnnFieldG 'MSSQL Void Expression) ->
|
||||||
|
FromIr Select
|
||||||
|
mkSelect jsonAggSelect annFields = do
|
||||||
|
let annSelect = IR.AnnSelectG annFields (IR.FromIdentifier $ IR.FIIdentifier withAlias) IR.noTablePermissions IR.noSelectArgs stringifyNum
|
||||||
|
fromSelect jsonAggSelect annSelect
|
||||||
|
|
||||||
|
-- SELECT COUNT(*) AS "count" FROM [with_alias]
|
||||||
|
countSelect :: Select
|
||||||
|
countSelect =
|
||||||
|
let countProjection = AggregateProjection $ Aliased (CountAggregate StarCountable) "count"
|
||||||
|
in emptySelect
|
||||||
|
{ selectProjections = [countProjection],
|
||||||
|
selectFrom = Just $ TSQL.FromIdentifier withAlias
|
||||||
|
}
|
||||||
|
|
||||||
|
-- SELECT '<text-value>' AS "exp"
|
||||||
|
textSelect :: Text -> Select
|
||||||
|
textSelect t =
|
||||||
|
let textProjection = ExpressionProjection $ Aliased (ValueExpression (ODBC.TextValue t)) "exp"
|
||||||
|
in emptySelect {selectProjections = [textProjection]}
|
||||||
|
|
||||||
|
-- | Generate a SQL SELECT statement which outputs both mutation response and
|
||||||
|
-- check constraint result.
|
||||||
|
--
|
||||||
|
-- A @check constraint@ applies to the data that has been changed, while
|
||||||
|
-- @permissions@ filter the data that is made available.
|
||||||
|
--
|
||||||
|
-- This function applies to @insert@ and @update@ mutations.
|
||||||
|
--
|
||||||
|
-- The check constraint boolean expression is evaluated on mutated rows in a
|
||||||
|
-- CASE expression so that the int value "0" is returned when check constraint
|
||||||
|
-- is true otherwise the int value "1" is returned. We use "SUM" aggregation on
|
||||||
|
-- the returned value and if check constraint on any row is not met, the summed
|
||||||
|
-- value will not equal to "0" (always > 1).
|
||||||
|
--
|
||||||
|
-- <check_constraint_select> :=
|
||||||
|
-- SELECT
|
||||||
|
-- SUM(CASE WHEN <check_boolean_expression>
|
||||||
|
-- THEN 0
|
||||||
|
-- ELSE 1
|
||||||
|
-- END)
|
||||||
|
-- FROM [with_alias]
|
||||||
|
--
|
||||||
|
-- <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
|
||||||
|
--
|
||||||
|
-- SELECT
|
||||||
|
-- (<mutation_output_select>) AS [mutation_response],
|
||||||
|
-- (<check_constraint_select>) AS [check_constraint_select]
|
||||||
|
selectMutationOutputAndCheckCondition :: Text -> Select -> Expression -> Select
|
||||||
|
selectMutationOutputAndCheckCondition alias mutationOutputSelect checkBoolExp =
|
||||||
|
let mutationOutputProjection =
|
||||||
|
ExpressionProjection $ Aliased (SelectExpression mutationOutputSelect) "mutation_response"
|
||||||
|
checkConstraintProjection =
|
||||||
|
-- apply ISNULL() to avoid check constraint select statement yielding empty rows
|
||||||
|
ExpressionProjection $
|
||||||
|
Aliased (FunctionApplicationExpression $ FunExpISNULL (SelectExpression checkConstraintSelect) (ValueExpression (ODBC.IntValue 0))) "check_constraint_select"
|
||||||
|
in emptySelect {selectProjections = [mutationOutputProjection, checkConstraintProjection]}
|
||||||
|
where
|
||||||
|
checkConstraintSelect =
|
||||||
|
let zeroValue = ValueExpression $ ODBC.IntValue 0
|
||||||
|
oneValue = ValueExpression $ ODBC.IntValue 1
|
||||||
|
caseExpression = ConditionalExpression checkBoolExp zeroValue oneValue
|
||||||
|
sumAggregate = OpAggregate "SUM" [caseExpression]
|
||||||
|
in emptySelect
|
||||||
|
{ selectProjections = [AggregateProjection (Aliased sumAggregate "check")],
|
||||||
|
selectFrom = Just $ TSQL.FromIdentifier alias
|
||||||
|
}
|
1021
server/src-lib/Hasura/Backends/MSSQL/FromIr/Query.hs
Normal file
1021
server/src-lib/Hasura/Backends/MSSQL/FromIr/Query.hs
Normal file
File diff suppressed because it is too large
Load Diff
@ -0,0 +1,40 @@
|
|||||||
|
-- | This module contains supporting definitions for building temporary tables
|
||||||
|
-- based off of the schema of other tables. This is used in mutations to capture
|
||||||
|
-- the data of rows that are affected.
|
||||||
|
module Hasura.Backends.MSSQL.FromIr.SelectIntoTempTable
|
||||||
|
( toSelectIntoTempTable,
|
||||||
|
)
|
||||||
|
where
|
||||||
|
|
||||||
|
import Hasura.Backends.MSSQL.Instances.Types ()
|
||||||
|
import Hasura.Backends.MSSQL.Types.Internal as TSQL
|
||||||
|
import Hasura.Prelude
|
||||||
|
import Hasura.RQL.Types.Column qualified as IR
|
||||||
|
import Hasura.SQL.Backend
|
||||||
|
import Language.GraphQL.Draft.Syntax (unName)
|
||||||
|
|
||||||
|
-- | Create a temporary table with the same schema as the given table.
|
||||||
|
toSelectIntoTempTable :: TempTableName -> TableName -> [IR.ColumnInfo 'MSSQL] -> SITTConstraints -> SelectIntoTempTable
|
||||||
|
toSelectIntoTempTable tempTableName fromTable allColumns withConstraints = do
|
||||||
|
SelectIntoTempTable
|
||||||
|
{ sittTempTableName = tempTableName,
|
||||||
|
sittColumns = map columnInfoToUnifiedColumn allColumns,
|
||||||
|
sittFromTableName = fromTable,
|
||||||
|
sittConstraints = withConstraints
|
||||||
|
}
|
||||||
|
|
||||||
|
-- | Extracts the type and column name of a ColumnInfo
|
||||||
|
columnInfoToUnifiedColumn :: IR.ColumnInfo 'MSSQL -> UnifiedColumn
|
||||||
|
columnInfoToUnifiedColumn colInfo =
|
||||||
|
case IR.ciType colInfo of
|
||||||
|
IR.ColumnScalar t ->
|
||||||
|
UnifiedColumn
|
||||||
|
{ name = unName $ IR.ciName colInfo,
|
||||||
|
type' = t
|
||||||
|
}
|
||||||
|
-- Enum values are represented as text value so they will always be of type text
|
||||||
|
IR.ColumnEnumReference {} ->
|
||||||
|
UnifiedColumn
|
||||||
|
{ name = unName $ IR.ciName colInfo,
|
||||||
|
type' = TextType
|
||||||
|
}
|
44
server/src-lib/Hasura/Backends/MSSQL/FromIr/Update.hs
Normal file
44
server/src-lib/Hasura/Backends/MSSQL/FromIr/Update.hs
Normal file
@ -0,0 +1,44 @@
|
|||||||
|
-- | This module defines the translation functions for update mutations.
|
||||||
|
module Hasura.Backends.MSSQL.FromIr.Update
|
||||||
|
( fromUpdate,
|
||||||
|
)
|
||||||
|
where
|
||||||
|
|
||||||
|
import Hasura.Backends.MSSQL.FromIr
|
||||||
|
( FromIr,
|
||||||
|
NameTemplate (TableTemplate),
|
||||||
|
generateAlias,
|
||||||
|
)
|
||||||
|
import Hasura.Backends.MSSQL.FromIr.Constants (tempTableNameUpdated)
|
||||||
|
import Hasura.Backends.MSSQL.FromIr.Expression (fromGBoolExp)
|
||||||
|
import Hasura.Backends.MSSQL.Instances.Types ()
|
||||||
|
import Hasura.Backends.MSSQL.Types.Internal as TSQL
|
||||||
|
import Hasura.Backends.MSSQL.Types.Update as TSQL (BackendUpdate (..), Update (..))
|
||||||
|
import Hasura.Prelude
|
||||||
|
import Hasura.RQL.IR qualified as IR
|
||||||
|
import Hasura.RQL.Types.Column qualified as IR
|
||||||
|
import Hasura.SQL.Backend
|
||||||
|
import Language.GraphQL.Draft.Syntax (unName)
|
||||||
|
|
||||||
|
fromUpdate :: IR.AnnotatedUpdate 'MSSQL -> FromIr Update
|
||||||
|
fromUpdate (IR.AnnotatedUpdateG table (permFilter, whereClause) _ backendUpdate _ allColumns) = do
|
||||||
|
tableAlias <- generateAlias (TableTemplate (tableName table))
|
||||||
|
runReaderT
|
||||||
|
( do
|
||||||
|
permissionsFilter <- fromGBoolExp permFilter
|
||||||
|
whereExpression <- fromGBoolExp whereClause
|
||||||
|
let columnNames = map (ColumnName . unName . IR.ciName) allColumns
|
||||||
|
pure
|
||||||
|
Update
|
||||||
|
{ updateTable =
|
||||||
|
Aliased
|
||||||
|
{ aliasedAlias = tableAlias,
|
||||||
|
aliasedThing = table
|
||||||
|
},
|
||||||
|
updateSet = updateOperations backendUpdate,
|
||||||
|
updateOutput = Output Inserted (map OutputColumn columnNames),
|
||||||
|
updateTempTable = TempTable tempTableNameUpdated columnNames,
|
||||||
|
updateWhere = Where [permissionsFilter, whereExpression]
|
||||||
|
}
|
||||||
|
)
|
||||||
|
(EntityAlias tableAlias)
|
@ -28,7 +28,7 @@ import Hasura.Backends.MSSQL.Connection
|
|||||||
import Hasura.Backends.MSSQL.Execute.Delete
|
import Hasura.Backends.MSSQL.Execute.Delete
|
||||||
import Hasura.Backends.MSSQL.Execute.Insert
|
import Hasura.Backends.MSSQL.Execute.Insert
|
||||||
import Hasura.Backends.MSSQL.Execute.Update
|
import Hasura.Backends.MSSQL.Execute.Update
|
||||||
import Hasura.Backends.MSSQL.FromIr as TSQL
|
import Hasura.Backends.MSSQL.FromIr.Constants (jsonFieldName)
|
||||||
import Hasura.Backends.MSSQL.Plan
|
import Hasura.Backends.MSSQL.Plan
|
||||||
import Hasura.Backends.MSSQL.SQL.Error
|
import Hasura.Backends.MSSQL.SQL.Error
|
||||||
import Hasura.Backends.MSSQL.SQL.Value (txtEncodedColVal)
|
import Hasura.Backends.MSSQL.SQL.Value (txtEncodedColVal)
|
||||||
@ -184,7 +184,7 @@ multiplexRootReselect variables rootReselect =
|
|||||||
ColumnExpression
|
ColumnExpression
|
||||||
( TSQL.FieldName
|
( TSQL.FieldName
|
||||||
{ fieldNameEntity = resultAlias,
|
{ fieldNameEntity = resultAlias,
|
||||||
fieldName = TSQL.jsonFieldName
|
fieldName = jsonFieldName
|
||||||
}
|
}
|
||||||
),
|
),
|
||||||
aliasedAlias = resultAlias
|
aliasedAlias = resultAlias
|
||||||
@ -213,7 +213,7 @@ multiplexRootReselect variables rootReselect =
|
|||||||
joinJoinAlias =
|
joinJoinAlias =
|
||||||
JoinAlias
|
JoinAlias
|
||||||
{ joinAliasEntity = resultAlias,
|
{ joinAliasEntity = resultAlias,
|
||||||
joinAliasField = Just TSQL.jsonFieldName
|
joinAliasField = Just jsonFieldName
|
||||||
}
|
}
|
||||||
}
|
}
|
||||||
],
|
],
|
||||||
|
@ -19,7 +19,6 @@ where
|
|||||||
-- , planSubscription
|
-- , planSubscription
|
||||||
-- ) where
|
-- ) where
|
||||||
|
|
||||||
import Control.Monad.Validate
|
|
||||||
import Data.Aeson qualified as J
|
import Data.Aeson qualified as J
|
||||||
import Data.ByteString.Lazy (toStrict)
|
import Data.ByteString.Lazy (toStrict)
|
||||||
import Data.HashMap.Strict qualified as HM
|
import Data.HashMap.Strict qualified as HM
|
||||||
@ -29,6 +28,7 @@ import Data.Text qualified as T
|
|||||||
import Data.Text.Extended
|
import Data.Text.Extended
|
||||||
import Database.ODBC.SQLServer qualified as ODBC
|
import Database.ODBC.SQLServer qualified as ODBC
|
||||||
import Hasura.Backends.MSSQL.FromIr
|
import Hasura.Backends.MSSQL.FromIr
|
||||||
|
import Hasura.Backends.MSSQL.FromIr.Query (fromQueryRootField)
|
||||||
import Hasura.Backends.MSSQL.Types.Internal
|
import Hasura.Backends.MSSQL.Types.Internal
|
||||||
import Hasura.Base.Error
|
import Hasura.Base.Error
|
||||||
import Hasura.GraphQL.Parser qualified as GraphQL
|
import Hasura.GraphQL.Parser qualified as GraphQL
|
||||||
@ -50,8 +50,7 @@ planQuery ::
|
|||||||
m Select
|
m Select
|
||||||
planQuery sessionVariables queryDB = do
|
planQuery sessionVariables queryDB = do
|
||||||
rootField <- traverse (prepareValueQuery sessionVariables) queryDB
|
rootField <- traverse (prepareValueQuery sessionVariables) queryDB
|
||||||
runValidate (runFromIr (fromRootField rootField))
|
runFromIr (fromQueryRootField rootField)
|
||||||
`onLeft` (throw400 NotSupported . tshow)
|
|
||||||
|
|
||||||
-- | Prepare a value without any query planning; we just execute the
|
-- | Prepare a value without any query planning; we just execute the
|
||||||
-- query with the values embedded.
|
-- query with the values embedded.
|
||||||
@ -97,9 +96,7 @@ planSubscription unpreparedMap sessionVariables = do
|
|||||||
unpreparedMap
|
unpreparedMap
|
||||||
)
|
)
|
||||||
emptyPrepareState
|
emptyPrepareState
|
||||||
selectMap <-
|
selectMap <- runFromIr (traverse fromQueryRootField rootFieldMap)
|
||||||
runValidate (runFromIr (traverse fromRootField rootFieldMap))
|
|
||||||
`onLeft` (throw400 NotSupported . tshow)
|
|
||||||
pure (collapseMap selectMap, prepareState)
|
pure (collapseMap selectMap, prepareState)
|
||||||
|
|
||||||
-- Plan a query without prepare/exec.
|
-- Plan a query without prepare/exec.
|
||||||
|
@ -20,6 +20,7 @@ module Hasura.Backends.MSSQL.Types.Internal
|
|||||||
BooleanOperators (..),
|
BooleanOperators (..),
|
||||||
Column,
|
Column,
|
||||||
ColumnName (..),
|
ColumnName (..),
|
||||||
|
columnNameToFieldName,
|
||||||
ColumnType,
|
ColumnType,
|
||||||
Comment (..),
|
Comment (..),
|
||||||
Countable (..),
|
Countable (..),
|
||||||
@ -27,6 +28,7 @@ module Hasura.Backends.MSSQL.Types.Internal
|
|||||||
Delete (..),
|
Delete (..),
|
||||||
DeleteOutput,
|
DeleteOutput,
|
||||||
EntityAlias (..),
|
EntityAlias (..),
|
||||||
|
fromAlias,
|
||||||
Expression (..),
|
Expression (..),
|
||||||
FieldName (..),
|
FieldName (..),
|
||||||
For (..),
|
For (..),
|
||||||
@ -93,10 +95,6 @@ module Hasura.Backends.MSSQL.Types.Internal
|
|||||||
scalarTypeDBName,
|
scalarTypeDBName,
|
||||||
snakeCaseTableName,
|
snakeCaseTableName,
|
||||||
stringTypes,
|
stringTypes,
|
||||||
tempTableNameInserted,
|
|
||||||
tempTableNameValues,
|
|
||||||
tempTableNameDeleted,
|
|
||||||
tempTableNameUpdated,
|
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
@ -297,18 +295,6 @@ data InsertValuesIntoTempTable = InsertValuesIntoTempTable
|
|||||||
-- | A temporary table name is prepended by a hash-sign
|
-- | A temporary table name is prepended by a hash-sign
|
||||||
newtype TempTableName = TempTableName Text
|
newtype TempTableName = TempTableName Text
|
||||||
|
|
||||||
tempTableNameInserted :: TempTableName
|
|
||||||
tempTableNameInserted = TempTableName "inserted"
|
|
||||||
|
|
||||||
tempTableNameValues :: TempTableName
|
|
||||||
tempTableNameValues = TempTableName "values"
|
|
||||||
|
|
||||||
tempTableNameDeleted :: TempTableName
|
|
||||||
tempTableNameDeleted = TempTableName "deleted"
|
|
||||||
|
|
||||||
tempTableNameUpdated :: TempTableName
|
|
||||||
tempTableNameUpdated = TempTableName "updated"
|
|
||||||
|
|
||||||
-- | A name of a regular table or temporary table
|
-- | A name of a regular table or temporary table
|
||||||
data SomeTableName
|
data SomeTableName
|
||||||
= RegularTableName TableName
|
= RegularTableName TableName
|
||||||
@ -453,6 +439,14 @@ data From
|
|||||||
| FromIdentifier Text
|
| FromIdentifier Text
|
||||||
| FromTempTable (Aliased TempTableName)
|
| FromTempTable (Aliased TempTableName)
|
||||||
|
|
||||||
|
-- | Extract the name bound in a 'From' clause as an 'EntityAlias'.
|
||||||
|
fromAlias :: From -> EntityAlias
|
||||||
|
fromAlias (FromQualifiedTable Aliased {aliasedAlias}) = EntityAlias aliasedAlias
|
||||||
|
fromAlias (FromOpenJson Aliased {aliasedAlias}) = EntityAlias aliasedAlias
|
||||||
|
fromAlias (FromSelect Aliased {aliasedAlias}) = EntityAlias aliasedAlias
|
||||||
|
fromAlias (FromIdentifier identifier) = EntityAlias identifier
|
||||||
|
fromAlias (FromTempTable Aliased {aliasedAlias}) = EntityAlias aliasedAlias
|
||||||
|
|
||||||
data OpenJson = OpenJson
|
data OpenJson = OpenJson
|
||||||
{ openJsonExpression :: Expression,
|
{ openJsonExpression :: Expression,
|
||||||
openJsonWith :: Maybe (NonEmpty JsonFieldSpec)
|
openJsonWith :: Maybe (NonEmpty JsonFieldSpec)
|
||||||
@ -488,6 +482,10 @@ newtype EntityAlias = EntityAlias
|
|||||||
{ entityAliasText :: Text
|
{ entityAliasText :: Text
|
||||||
}
|
}
|
||||||
|
|
||||||
|
columnNameToFieldName :: ColumnName -> EntityAlias -> FieldName
|
||||||
|
columnNameToFieldName (ColumnName fieldName) EntityAlias {entityAliasText = fieldNameEntity} =
|
||||||
|
FieldName {fieldName, fieldNameEntity}
|
||||||
|
|
||||||
data Op
|
data Op
|
||||||
= LT
|
= LT
|
||||||
| LTE
|
| LTE
|
||||||
|
Loading…
Reference in New Issue
Block a user