mirror of
https://github.com/hasura/graphql-engine.git
synced 2024-12-14 17:02:49 +03:00
cleanup(sqlserver): remove QueryWithDDL
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/8834 GitOrigin-RevId: b31fba44bb67a16bcc1901ce51ce4ab1c6797f23
This commit is contained in:
parent
ffa3f5e3cc
commit
a5043ab215
@ -77,11 +77,11 @@ buildDeleteTx deleteOperation stringifyNum queryTags = do
|
||||
-- Create a temp table
|
||||
Tx.unitQueryE defaultMSSQLTxErrorHandler (createInsertedTempTableQuery `withQueryTags` queryTags)
|
||||
let deleteQuery = TQ.fromDelete <$> TSQL.fromDelete deleteOperation
|
||||
deleteQueryValidated <- toQueryFlat . qwdQuery <$> runFromIrDiscardCTEs deleteQuery
|
||||
deleteQueryValidated <- toQueryFlat <$> runFromIrDiscardCTEs deleteQuery
|
||||
|
||||
-- Execute DELETE statement
|
||||
Tx.unitQueryE mutationMSSQLTxErrorHandler (deleteQueryValidated `withQueryTags` queryTags)
|
||||
mutationOutputSelect <- qwdQuery <$> runFromIrUseCTEs (mkMutationOutputSelect stringifyNum withAlias $ _adOutput deleteOperation)
|
||||
mutationOutputSelect <- runFromIrUseCTEs (mkMutationOutputSelect stringifyNum withAlias $ _adOutput deleteOperation)
|
||||
|
||||
let withSelect =
|
||||
emptySelect
|
||||
|
@ -227,7 +227,7 @@ buildUpsertTx tableName insert ifMatched queryTags = do
|
||||
Tx.unitQueryE mutationMSSQLTxErrorHandler (insertValuesIntoTempTableQuery `withQueryTags` queryTags)
|
||||
|
||||
-- Run the MERGE query and store the mutated rows in #inserted temporary table
|
||||
merge <- qwdQuery <$> runFromIrDiscardCTEs (toMerge tableName (_aiInsertObject $ _aiData insert) allTableColumns ifMatched)
|
||||
merge <- runFromIrDiscardCTEs (toMerge tableName (_aiInsertObject $ _aiData insert) allTableColumns ifMatched)
|
||||
let mergeQuery = toQueryFlat $ TQ.fromMerge merge
|
||||
Tx.unitQueryE mutationMSSQLTxErrorHandler (mergeQuery `withQueryTags` queryTags)
|
||||
|
||||
@ -244,11 +244,11 @@ buildInsertResponseTx ::
|
||||
Tx.TxET QErr m (Text, Int)
|
||||
buildInsertResponseTx stringifyNum withAlias insert queryTags = do
|
||||
-- Generate a SQL SELECT statement which outputs the mutation response using the #inserted
|
||||
mutationOutputSelect <- qwdQuery <$> runFromIrUseCTEs (mkMutationOutputSelect stringifyNum withAlias $ _aiOutput insert)
|
||||
mutationOutputSelect <- runFromIrUseCTEs (mkMutationOutputSelect stringifyNum withAlias $ _aiOutput insert)
|
||||
|
||||
-- The check constraint is translated to boolean expression
|
||||
let checkCondition = fst $ _aiCheckCondition $ _aiData insert
|
||||
checkBoolExp <- qwdQuery <$> runFromIrDiscardCTEs (runReaderT (fromGBoolExp checkCondition) (EntityAlias withAlias))
|
||||
checkBoolExp <- runFromIrDiscardCTEs (runReaderT (fromGBoolExp checkCondition) (EntityAlias withAlias))
|
||||
|
||||
let withSelect =
|
||||
emptySelect
|
||||
|
@ -82,15 +82,15 @@ buildUpdateTx updateOperation stringifyNum queryTags = do
|
||||
-- Create a temp table
|
||||
Tx.unitQueryE defaultMSSQLTxErrorHandler (createInsertedTempTableQuery `withQueryTags` queryTags)
|
||||
let updateQuery = TQ.fromUpdate <$> TSQL.fromUpdate updateOperation
|
||||
updateQueryValidated <- toQueryFlat . qwdQuery <$> runFromIrDiscardCTEs updateQuery
|
||||
updateQueryValidated <- toQueryFlat <$> runFromIrDiscardCTEs updateQuery
|
||||
|
||||
-- Execute UPDATE statement
|
||||
Tx.unitQueryE mutationMSSQLTxErrorHandler (updateQueryValidated `withQueryTags` queryTags)
|
||||
mutationOutputSelect <- qwdQuery <$> runFromIrUseCTEs (mkMutationOutputSelect stringifyNum withAlias $ _auOutput updateOperation)
|
||||
mutationOutputSelect <- runFromIrUseCTEs (mkMutationOutputSelect stringifyNum withAlias $ _auOutput updateOperation)
|
||||
let checkCondition = _auCheck updateOperation
|
||||
|
||||
-- The check constraint is translated to boolean expression
|
||||
checkBoolExp <- qwdQuery <$> runFromIrDiscardCTEs (runReaderT (fromGBoolExp checkCondition) (EntityAlias withAlias))
|
||||
checkBoolExp <- runFromIrDiscardCTEs (runReaderT (fromGBoolExp checkCondition) (EntityAlias withAlias))
|
||||
|
||||
let withSelect =
|
||||
emptySelect
|
||||
|
@ -14,8 +14,6 @@ module Hasura.Backends.MSSQL.FromIr
|
||||
runFromIrUseCTEs,
|
||||
runFromIrUseCTEsT,
|
||||
Error (..),
|
||||
tellBefore,
|
||||
tellAfter,
|
||||
tellCTE,
|
||||
|
||||
-- * Name generation
|
||||
@ -39,31 +37,17 @@ import Hasura.RQL.IR qualified as IR
|
||||
import Hasura.SQL.Backend
|
||||
|
||||
-- | Allow the query process to emit extra setup / teardown steps
|
||||
data IRWriter = IRWriter
|
||||
{ irwBefore :: [TempTableDDL],
|
||||
irwAfter :: [TempTableDDL],
|
||||
irwCTEs :: Maybe With
|
||||
newtype IRWriter = IRWriter
|
||||
{ irwCTEs :: Maybe With
|
||||
}
|
||||
|
||||
instance Semigroup IRWriter where
|
||||
(IRWriter a b c) <> (IRWriter a' b' c') = IRWriter (a <> a') (b' <> b) (c <> c')
|
||||
deriving (Semigroup) via (Maybe With)
|
||||
|
||||
instance Monoid IRWriter where
|
||||
mempty = IRWriter mempty mempty Nothing
|
||||
|
||||
-- | add a step to be run before the main query
|
||||
tellBefore :: TempTableDDL -> FromIr ()
|
||||
tellBefore step =
|
||||
tell (IRWriter {irwBefore = [step], irwAfter = mempty, irwCTEs = Nothing})
|
||||
|
||||
-- | add a step to be run after the main query
|
||||
tellAfter :: TempTableDDL -> FromIr ()
|
||||
tellAfter step =
|
||||
tell (IRWriter {irwBefore = mempty, irwAfter = [step], irwCTEs = Nothing})
|
||||
mempty = IRWriter Nothing
|
||||
|
||||
tellCTE :: Aliased (InterpolatedQuery Expression) -> FromIr ()
|
||||
tellCTE cte =
|
||||
tell (IRWriter {irwBefore = mempty, irwAfter = mempty, irwCTEs = Just (With $ pure $ CTEUnsafeRawSQL <$> cte)})
|
||||
tell (IRWriter {irwCTEs = Just (With $ pure $ CTEUnsafeRawSQL <$> cte)})
|
||||
|
||||
-- | The central Monad used throughout for all conversion functions.
|
||||
--
|
||||
@ -92,39 +76,38 @@ newtype FromIr a = FromIr
|
||||
-- supplied action.
|
||||
runFromIr ::
|
||||
(Traversable t, MonadError QErr m) =>
|
||||
((a, IRWriter) -> QueryWithDDL a) ->
|
||||
((a, IRWriter) -> a) ->
|
||||
t (FromIr a) ->
|
||||
m (t (QueryWithDDL a))
|
||||
runFromIr toQueryWithDDL =
|
||||
m (t a)
|
||||
runFromIr toResult =
|
||||
flip onLeft (throw500 . tshow)
|
||||
. V.runValidate
|
||||
. flip evalStateT mempty
|
||||
. fmap (fmap toQueryWithDDL)
|
||||
. fmap (fmap toResult)
|
||||
. traverse (runWriterT . unFromIr)
|
||||
|
||||
-- | Run a 'FromIr' action, throwing errors that have been collected using the
|
||||
-- supplied action, and attach CTEs created from native queries to the select query.
|
||||
runFromIrUseCTEs :: MonadError QErr m => FromIr Select -> m (QueryWithDDL Select)
|
||||
runFromIrUseCTEs :: MonadError QErr m => FromIr Select -> m Select
|
||||
runFromIrUseCTEs fromir = runIdentity <$> runFromIr attachCTEs (Identity fromir)
|
||||
|
||||
-- | Run a 'FromIr' action, throwing errors that have been collected using the
|
||||
-- supplied action, and discard CTEs created from native queries to the select query.
|
||||
runFromIrDiscardCTEs :: MonadError QErr m => FromIr a -> m (QueryWithDDL a)
|
||||
runFromIrDiscardCTEs :: MonadError QErr m => FromIr a -> m a
|
||||
runFromIrDiscardCTEs fromir = runIdentity <$> runFromIr discardCTEs (Identity fromir)
|
||||
|
||||
-- | Run a 'FromIr' action, throwing errors that have been collected using the
|
||||
-- supplied action, and attach CTEs created from native queries to the select query.
|
||||
runFromIrUseCTEsT :: (Traversable t, MonadError QErr m) => t (FromIr Select) -> m (t (QueryWithDDL Select))
|
||||
runFromIrUseCTEsT :: (Traversable t, MonadError QErr m) => t (FromIr Select) -> m (t Select)
|
||||
runFromIrUseCTEsT = runFromIr attachCTEs
|
||||
|
||||
attachCTEs :: (Select, IRWriter) -> QueryWithDDL Select
|
||||
attachCTEs (select, IRWriter before after ctes) =
|
||||
QueryWithDDL before select {selectWith = ctes <> selectWith select} after
|
||||
attachCTEs :: (Select, IRWriter) -> Select
|
||||
attachCTEs (select, IRWriter ctes) = select {selectWith = ctes <> selectWith select}
|
||||
|
||||
discardCTEs :: (a, IRWriter) -> QueryWithDDL a
|
||||
discardCTEs (a, IRWriter before after _ctes) =
|
||||
discardCTEs :: (a, IRWriter) -> a
|
||||
discardCTEs =
|
||||
-- TODO: assert ctes is empty, or throw an error "not supported"
|
||||
QueryWithDDL before a after
|
||||
fst
|
||||
|
||||
-- | Errors that may happen during translation.
|
||||
data Error
|
||||
|
@ -95,22 +95,18 @@ msDBQueryPlan ::
|
||||
m (DBStepInfo 'MSSQL)
|
||||
msDBQueryPlan userInfo sourceName sourceConfig qrf _ _ = do
|
||||
let sessionVariables = _uiSession userInfo
|
||||
(QueryWithDDL {qwdBeforeSteps, qwdAfterSteps, qwdQuery = statement}) <- planQuery sessionVariables qrf
|
||||
statement <- planQuery sessionVariables qrf
|
||||
queryTags <- ask
|
||||
|
||||
-- Append Query tags comment to the select statement
|
||||
let printer = fromSelect statement `withQueryTagsPrinter` queryTags
|
||||
queryString = ODBC.renderQuery (toQueryPretty printer)
|
||||
|
||||
pure $ DBStepInfo @'MSSQL sourceName sourceConfig (Just queryString) (runSelectQuery printer qwdBeforeSteps qwdAfterSteps) ()
|
||||
pure $ DBStepInfo @'MSSQL sourceName sourceConfig (Just queryString) (runSelectQuery printer) ()
|
||||
where
|
||||
runSelectQuery queryPrinter beforeSteps afterSteps = OnBaseMonad do
|
||||
let queryTx = do
|
||||
let executeStep = Tx.unitQueryE defaultMSSQLTxErrorHandler . toQueryFlat . TQ.fromTempTableDDL
|
||||
traverse_ executeStep beforeSteps
|
||||
result <- encJFromText <$> Tx.singleRowQueryE defaultMSSQLTxErrorHandler (toQueryFlat queryPrinter)
|
||||
traverse_ executeStep afterSteps
|
||||
pure result
|
||||
runSelectQuery queryPrinter = OnBaseMonad do
|
||||
let queryTx =
|
||||
encJFromText <$> Tx.singleRowQueryE defaultMSSQLTxErrorHandler (toQueryFlat queryPrinter)
|
||||
mssqlRunReadOnly (_mscExecCtx sourceConfig) (fmap withNoStatistics queryTx)
|
||||
|
||||
runShowplan ::
|
||||
@ -137,7 +133,7 @@ msDBQueryExplain ::
|
||||
m (AB.AnyBackend DBStepInfo)
|
||||
msDBQueryExplain fieldName userInfo sourceName sourceConfig qrf _ _ = do
|
||||
let sessionVariables = _uiSession userInfo
|
||||
statement <- qwdQuery <$> planQuery sessionVariables qrf
|
||||
statement <- planQuery sessionVariables qrf
|
||||
let query = toQueryPretty (fromSelect statement)
|
||||
queryString = ODBC.renderQuery query
|
||||
odbcQuery = OnBaseMonad $
|
||||
|
@ -52,7 +52,7 @@ planQuery ::
|
||||
MonadError QErr m =>
|
||||
SessionVariables ->
|
||||
QueryDB 'MSSQL Void (UnpreparedValue 'MSSQL) ->
|
||||
m (QueryWithDDL Select)
|
||||
m Select
|
||||
planQuery sessionVariables queryDB = do
|
||||
rootField <- traverse (prepareValueQuery sessionVariables) queryDB
|
||||
runIrWrappingRoot $ fromQueryRootField rootField
|
||||
@ -78,19 +78,18 @@ planSourceRelationship
|
||||
traverseSourceRelationshipSelection
|
||||
(fmap Const . prepareValueQuery sessionVariables)
|
||||
sourceRelationshipRaw
|
||||
qwdQuery
|
||||
<$> runIrWrappingRoot
|
||||
( fromSourceRelationship
|
||||
lhs
|
||||
lhsSchema
|
||||
argumentId
|
||||
(relationshipName, sourceRelationship)
|
||||
)
|
||||
runIrWrappingRoot
|
||||
( fromSourceRelationship
|
||||
lhs
|
||||
lhsSchema
|
||||
argumentId
|
||||
(relationshipName, sourceRelationship)
|
||||
)
|
||||
|
||||
runIrWrappingRoot ::
|
||||
MonadError QErr m =>
|
||||
FromIr Select ->
|
||||
m (QueryWithDDL Select)
|
||||
m Select
|
||||
runIrWrappingRoot selectAction =
|
||||
runFromIrUseCTEs selectAction `onLeft` (throwError . overrideQErrStatus HTTP.status400 NotSupported)
|
||||
|
||||
@ -140,7 +139,7 @@ planSubscription unpreparedMap sessionVariables = do
|
||||
emptyPrepareState
|
||||
let rootFields :: InsOrdHashMap G.Name (FromIr Select)
|
||||
rootFields = fmap fromQueryRootField rootFieldMap
|
||||
selectMap <- fmap qwdQuery <$> runFromIrUseCTEsT rootFields
|
||||
selectMap <- runFromIrUseCTEsT rootFields
|
||||
pure (collapseMap selectMap, prepareState)
|
||||
|
||||
-- Plan a query without prepare/exec.
|
||||
|
@ -16,7 +16,6 @@ module Hasura.Backends.MSSQL.ToQuery
|
||||
toQueryPretty,
|
||||
fromInsert,
|
||||
fromMerge,
|
||||
fromTempTableDDL,
|
||||
fromSetIdentityInsert,
|
||||
fromDelete,
|
||||
fromUpdate,
|
||||
@ -40,7 +39,6 @@ import Data.Text.Lazy qualified as L
|
||||
import Data.Text.Lazy.Builder qualified as L
|
||||
import Database.ODBC.SQLServer
|
||||
import Hasura.Backends.MSSQL.Types
|
||||
import Hasura.Backends.MSSQL.Types qualified as MSSQL
|
||||
import Hasura.NativeQuery.Metadata (InterpolatedItem (..), InterpolatedQuery (..))
|
||||
import Hasura.Prelude hiding (GT, LT)
|
||||
|
||||
@ -439,32 +437,6 @@ fromUpdateSet setColumns =
|
||||
UpdateSet p -> " = " <+> p
|
||||
UpdateInc p -> " += " <+> p
|
||||
|
||||
fromTempTableDDL :: MSSQL.TempTableDDL -> Printer
|
||||
fromTempTableDDL = \case
|
||||
CreateTemp tempTableName tempColumns ->
|
||||
"CREATE TABLE "
|
||||
<+> fromTempTableName tempTableName
|
||||
<+> " ( "
|
||||
<+> columns
|
||||
<+> " ) "
|
||||
where
|
||||
columns =
|
||||
SepByPrinter
|
||||
("," <+> NewlinePrinter)
|
||||
(map columnNameAndType tempColumns)
|
||||
columnNameAndType (UnifiedColumn name ty) =
|
||||
fromColumnName name
|
||||
<+> " "
|
||||
<+> fromString (T.unpack (scalarTypeDBName DataLengthMax ty))
|
||||
InsertTemp tempTableName interpolatedQuery ->
|
||||
"INSERT INTO "
|
||||
<+> fromTempTableName tempTableName
|
||||
<+> " "
|
||||
<+> renderInterpolatedQuery interpolatedQuery
|
||||
DropTemp tempTableName ->
|
||||
"DROP TABLE "
|
||||
<+> fromTempTableName tempTableName
|
||||
|
||||
-- | Converts `SelectIntoTempTable`.
|
||||
--
|
||||
-- > SelectIntoTempTable (TempTableName "deleted") [UnifiedColumn "id" IntegerType, UnifiedColumn "name" TextType] (TableName "table" "schema")
|
||||
|
@ -61,14 +61,12 @@ module Hasura.Backends.MSSQL.Types.Internal
|
||||
Deleted (..),
|
||||
Output (..),
|
||||
Projection (..),
|
||||
QueryWithDDL (..),
|
||||
Reselect (..),
|
||||
Root (..),
|
||||
ScalarType (..),
|
||||
SchemaName (..),
|
||||
Select (..),
|
||||
SetIdentityInsert (..),
|
||||
TempTableDDL (..),
|
||||
TempTableName (..),
|
||||
SomeTableName (..),
|
||||
TempTable (..),
|
||||
@ -388,23 +386,6 @@ data CTEBody
|
||||
= CTESelect Select
|
||||
| CTEUnsafeRawSQL (InterpolatedQuery Expression)
|
||||
|
||||
-- | Extra query steps that can be emitted from the main
|
||||
-- query to do things like setup temp tables
|
||||
data TempTableDDL
|
||||
= -- | create a temp table
|
||||
CreateTemp
|
||||
{ stcTempTableName :: TempTableName,
|
||||
stcColumns :: [UnifiedColumn]
|
||||
}
|
||||
| -- | insert output of a statement into a temp table
|
||||
InsertTemp
|
||||
{ stiTempTableName :: TempTableName,
|
||||
stiExpression :: InterpolatedQuery Expression
|
||||
}
|
||||
| -- | Drop a temp table
|
||||
DropTemp
|
||||
{stdTempTableName :: TempTableName}
|
||||
|
||||
data Top
|
||||
= NoTop
|
||||
| Top Int
|
||||
@ -549,13 +530,6 @@ newtype ConstraintName = ConstraintName {constraintNameText :: Text}
|
||||
|
||||
newtype FunctionName = FunctionName {functionNameText :: Text}
|
||||
|
||||
-- | type for a query generated from IR along with any DDL actions
|
||||
data QueryWithDDL a = QueryWithDDL
|
||||
{ qwdBeforeSteps :: [TempTableDDL],
|
||||
qwdQuery :: a,
|
||||
qwdAfterSteps :: [TempTableDDL]
|
||||
}
|
||||
|
||||
-- | Derived from the odbc package.
|
||||
data ScalarType
|
||||
= CharType
|
||||
|
Loading…
Reference in New Issue
Block a user