2020-10-29 19:58:13 +03:00
|
|
|
module Hasura.Backends.Postgres.Execute.Mutation
|
|
|
|
( MutationRemoteJoinCtx
|
2021-02-14 09:07:52 +03:00
|
|
|
, MutateResp(..)
|
2020-10-29 19:58:13 +03:00
|
|
|
--
|
|
|
|
, execDeleteQuery
|
|
|
|
, execInsertQuery
|
|
|
|
, execUpdateQuery
|
|
|
|
--
|
2020-05-27 18:02:58 +03:00
|
|
|
, executeMutationOutputQuery
|
2019-03-07 13:24:07 +03:00
|
|
|
, mutateAndFetchCols
|
2020-10-29 19:58:13 +03:00
|
|
|
) where
|
2019-03-07 13:24:07 +03:00
|
|
|
|
2019-09-14 09:01:06 +03:00
|
|
|
import Hasura.Prelude
|
|
|
|
|
2020-10-29 19:58:13 +03:00
|
|
|
import qualified Data.Sequence as DS
|
|
|
|
import qualified Database.PG.Query as Q
|
|
|
|
import qualified Network.HTTP.Client as HTTP
|
|
|
|
import qualified Network.HTTP.Types as N
|
|
|
|
|
2021-04-22 00:44:37 +03:00
|
|
|
import Data.Aeson
|
2021-02-14 09:07:52 +03:00
|
|
|
|
2020-10-29 19:58:13 +03:00
|
|
|
import qualified Hasura.Backends.Postgres.SQL.DML as S
|
2020-10-27 16:53:49 +03:00
|
|
|
|
2020-10-29 19:58:13 +03:00
|
|
|
import Hasura.Backends.Postgres.Connection
|
2020-10-27 16:53:49 +03:00
|
|
|
import Hasura.Backends.Postgres.SQL.Types
|
|
|
|
import Hasura.Backends.Postgres.SQL.Value
|
2020-10-29 19:58:13 +03:00
|
|
|
import Hasura.Backends.Postgres.Translate.Delete
|
|
|
|
import Hasura.Backends.Postgres.Translate.Insert
|
|
|
|
import Hasura.Backends.Postgres.Translate.Mutation
|
|
|
|
import Hasura.Backends.Postgres.Translate.Returning
|
|
|
|
import Hasura.Backends.Postgres.Translate.Select
|
|
|
|
import Hasura.Backends.Postgres.Translate.Update
|
2021-05-11 18:18:31 +03:00
|
|
|
import Hasura.Base.Error
|
2019-03-18 19:22:21 +03:00
|
|
|
import Hasura.EncJSON
|
2021-07-29 11:29:12 +03:00
|
|
|
import Hasura.QueryTags
|
2019-03-07 13:24:07 +03:00
|
|
|
import Hasura.RQL.DML.Internal
|
2020-10-29 19:58:13 +03:00
|
|
|
import Hasura.RQL.IR.Delete
|
|
|
|
import Hasura.RQL.IR.Insert
|
|
|
|
import Hasura.RQL.IR.Returning
|
|
|
|
import Hasura.RQL.IR.Select
|
|
|
|
import Hasura.RQL.IR.Update
|
2019-03-07 13:24:07 +03:00
|
|
|
import Hasura.RQL.Types
|
2020-11-10 10:50:26 +03:00
|
|
|
import Hasura.SQL.Types
|
2020-10-21 19:35:06 +03:00
|
|
|
import Hasura.Session
|
2019-03-07 13:24:07 +03:00
|
|
|
|
2020-10-27 16:53:49 +03:00
|
|
|
|
2021-04-22 00:44:37 +03:00
|
|
|
data MutateResp (b :: BackendType) a
|
2021-02-14 09:07:52 +03:00
|
|
|
= MutateResp
|
|
|
|
{ _mrAffectedRows :: !Int
|
2021-04-22 00:44:37 +03:00
|
|
|
, _mrReturningColumns :: ![ColumnValues b a]
|
|
|
|
} deriving (Generic)
|
|
|
|
deriving instance (Backend b, Show a) => Show (MutateResp b a)
|
|
|
|
deriving instance (Backend b, Eq a) => Eq (MutateResp b a)
|
|
|
|
|
|
|
|
instance (Backend b, ToJSON a) => ToJSON (MutateResp b a) where
|
|
|
|
toJSON = genericToJSON hasuraJSON
|
|
|
|
|
|
|
|
instance (Backend b, FromJSON a) => FromJSON (MutateResp b a) where
|
|
|
|
parseJSON = genericParseJSON hasuraJSON
|
|
|
|
|
2020-05-27 18:02:58 +03:00
|
|
|
type MutationRemoteJoinCtx = (HTTP.Manager, [N.Header], UserInfo)
|
|
|
|
|
2020-11-12 12:25:48 +03:00
|
|
|
data Mutation (b :: BackendType)
|
2019-03-07 13:24:07 +03:00
|
|
|
= Mutation
|
2021-06-11 06:26:50 +03:00
|
|
|
{ _mTable :: !QualifiedTable
|
|
|
|
, _mQuery :: !(MutationCTE, DS.Seq Q.PrepArg)
|
|
|
|
, _mOutput :: !(MutationOutput b)
|
|
|
|
, _mCols :: ![ColumnInfo b]
|
|
|
|
, _mStrfyNum :: !Bool
|
2020-05-27 18:02:58 +03:00
|
|
|
}
|
|
|
|
|
|
|
|
mkMutation
|
2021-06-11 06:26:50 +03:00
|
|
|
:: UserInfo
|
2020-05-27 18:02:58 +03:00
|
|
|
-> QualifiedTable
|
2020-11-12 12:25:48 +03:00
|
|
|
-> (MutationCTE, DS.Seq Q.PrepArg)
|
2021-04-22 00:44:37 +03:00
|
|
|
-> MutationOutput ('Postgres pgKind)
|
|
|
|
-> [ColumnInfo ('Postgres pgKind)]
|
2020-05-27 18:02:58 +03:00
|
|
|
-> Bool
|
2021-04-22 00:44:37 +03:00
|
|
|
-> Mutation ('Postgres pgKind)
|
2021-06-11 06:26:50 +03:00
|
|
|
mkMutation _userInfo table query output allCols strfyNum =
|
|
|
|
Mutation table query output allCols strfyNum
|
2019-03-07 13:24:07 +03:00
|
|
|
|
2020-05-27 18:02:58 +03:00
|
|
|
runMutation
|
2020-07-14 22:00:58 +03:00
|
|
|
::
|
2021-06-11 06:26:50 +03:00
|
|
|
( MonadTx m
|
2021-04-22 00:44:37 +03:00
|
|
|
, Backend ('Postgres pgKind)
|
2021-05-21 05:46:58 +03:00
|
|
|
, PostgresAnnotatedFieldJSON pgKind
|
2021-07-29 11:29:12 +03:00
|
|
|
, MonadReader QueryTagsComment m
|
2020-07-14 22:00:58 +03:00
|
|
|
)
|
2021-06-11 06:26:50 +03:00
|
|
|
=> Mutation ('Postgres pgKind)
|
2020-07-14 22:00:58 +03:00
|
|
|
-> m EncJSON
|
2021-06-11 06:26:50 +03:00
|
|
|
runMutation mut =
|
|
|
|
bool (mutateAndReturn mut) (mutateAndSel mut) $
|
2020-02-13 20:38:23 +03:00
|
|
|
hasNestedFld $ _mOutput mut
|
2019-03-07 13:24:07 +03:00
|
|
|
|
2020-05-27 18:02:58 +03:00
|
|
|
mutateAndReturn
|
2020-07-14 22:00:58 +03:00
|
|
|
::
|
2021-06-11 06:26:50 +03:00
|
|
|
( MonadTx m
|
2021-04-22 00:44:37 +03:00
|
|
|
, Backend ('Postgres pgKind)
|
2021-05-21 05:46:58 +03:00
|
|
|
, PostgresAnnotatedFieldJSON pgKind
|
2021-07-29 11:29:12 +03:00
|
|
|
, MonadReader QueryTagsComment m
|
2020-07-14 22:00:58 +03:00
|
|
|
)
|
2021-06-11 06:26:50 +03:00
|
|
|
=> Mutation ('Postgres pgKind)
|
2020-07-14 22:00:58 +03:00
|
|
|
-> m EncJSON
|
2021-06-11 06:26:50 +03:00
|
|
|
mutateAndReturn (Mutation qt (cte, p) mutationOutput allCols strfyNum) =
|
|
|
|
executeMutationOutputQuery qt allCols Nothing cte mutationOutput strfyNum (toList p)
|
2019-03-07 13:24:07 +03:00
|
|
|
|
2020-10-29 19:58:13 +03:00
|
|
|
|
|
|
|
execUpdateQuery
|
server: IR for DB-DB joins
### Description
This PR adds the required IR for DB to DB joins, based on @paf31 and @0x777 's `feature/db-to-db` branch.
To do so, it also refactors the IR to introduce a new type parameter, `r`, which is used to recursively constructs the `v` parameter of remote QueryDBs. When collecting remote joins, we replace `r` with `Const Void`, indicating at the type level that there cannot be any leftover remote join.
Furthermore, this PR refactors IR.Select for readability, moves some code from IR.Root to IR.Select to avoid having to deal with circular dependencies, and makes it compile by adding `error` in all new cases in the execution pipeline.
The diff doesn't make it clear, but most of Select.hs is actually unchanged. Declarations have just been reordered by topic, in the following order:
- type declarations
- instance declarations
- type aliases
- constructor functions
- traverse functions
https://github.com/hasura/graphql-engine-mono/pull/1580
Co-authored-by: Phil Freeman <630306+paf31@users.noreply.github.com>
GitOrigin-RevId: bbdcb4119cec8bb3fc32f1294f91b8dea0728721
2021-06-18 02:12:11 +03:00
|
|
|
:: forall pgKind m
|
|
|
|
. ( MonadTx m
|
|
|
|
, Backend ('Postgres pgKind)
|
|
|
|
, PostgresAnnotatedFieldJSON pgKind
|
2021-07-29 11:29:12 +03:00
|
|
|
, MonadReader QueryTagsComment m
|
server: IR for DB-DB joins
### Description
This PR adds the required IR for DB to DB joins, based on @paf31 and @0x777 's `feature/db-to-db` branch.
To do so, it also refactors the IR to introduce a new type parameter, `r`, which is used to recursively constructs the `v` parameter of remote QueryDBs. When collecting remote joins, we replace `r` with `Const Void`, indicating at the type level that there cannot be any leftover remote join.
Furthermore, this PR refactors IR.Select for readability, moves some code from IR.Root to IR.Select to avoid having to deal with circular dependencies, and makes it compile by adding `error` in all new cases in the execution pipeline.
The diff doesn't make it clear, but most of Select.hs is actually unchanged. Declarations have just been reordered by topic, in the following order:
- type declarations
- instance declarations
- type aliases
- constructor functions
- traverse functions
https://github.com/hasura/graphql-engine-mono/pull/1580
Co-authored-by: Phil Freeman <630306+paf31@users.noreply.github.com>
GitOrigin-RevId: bbdcb4119cec8bb3fc32f1294f91b8dea0728721
2021-06-18 02:12:11 +03:00
|
|
|
)
|
2021-06-11 06:26:50 +03:00
|
|
|
=> Bool
|
|
|
|
-> UserInfo
|
2021-04-22 00:44:37 +03:00
|
|
|
-> (AnnUpd ('Postgres pgKind), DS.Seq Q.PrepArg)
|
2020-10-29 19:58:13 +03:00
|
|
|
-> m EncJSON
|
2021-07-29 11:29:12 +03:00
|
|
|
execUpdateQuery strfyNum userInfo (u, p) =
|
|
|
|
runMutation
|
|
|
|
(mkMutation userInfo (uqp1Table u) (MCCheckConstraint updateCTE, p) (uqp1Output u) (uqp1AllCols u) strfyNum)
|
2020-10-29 19:58:13 +03:00
|
|
|
where
|
|
|
|
updateCTE = mkUpdateCTE u
|
|
|
|
|
|
|
|
execDeleteQuery
|
server: IR for DB-DB joins
### Description
This PR adds the required IR for DB to DB joins, based on @paf31 and @0x777 's `feature/db-to-db` branch.
To do so, it also refactors the IR to introduce a new type parameter, `r`, which is used to recursively constructs the `v` parameter of remote QueryDBs. When collecting remote joins, we replace `r` with `Const Void`, indicating at the type level that there cannot be any leftover remote join.
Furthermore, this PR refactors IR.Select for readability, moves some code from IR.Root to IR.Select to avoid having to deal with circular dependencies, and makes it compile by adding `error` in all new cases in the execution pipeline.
The diff doesn't make it clear, but most of Select.hs is actually unchanged. Declarations have just been reordered by topic, in the following order:
- type declarations
- instance declarations
- type aliases
- constructor functions
- traverse functions
https://github.com/hasura/graphql-engine-mono/pull/1580
Co-authored-by: Phil Freeman <630306+paf31@users.noreply.github.com>
GitOrigin-RevId: bbdcb4119cec8bb3fc32f1294f91b8dea0728721
2021-06-18 02:12:11 +03:00
|
|
|
:: forall pgKind m
|
|
|
|
. ( MonadTx m
|
|
|
|
, Backend ('Postgres pgKind)
|
|
|
|
, PostgresAnnotatedFieldJSON pgKind
|
2021-07-29 11:29:12 +03:00
|
|
|
, MonadReader QueryTagsComment m
|
server: IR for DB-DB joins
### Description
This PR adds the required IR for DB to DB joins, based on @paf31 and @0x777 's `feature/db-to-db` branch.
To do so, it also refactors the IR to introduce a new type parameter, `r`, which is used to recursively constructs the `v` parameter of remote QueryDBs. When collecting remote joins, we replace `r` with `Const Void`, indicating at the type level that there cannot be any leftover remote join.
Furthermore, this PR refactors IR.Select for readability, moves some code from IR.Root to IR.Select to avoid having to deal with circular dependencies, and makes it compile by adding `error` in all new cases in the execution pipeline.
The diff doesn't make it clear, but most of Select.hs is actually unchanged. Declarations have just been reordered by topic, in the following order:
- type declarations
- instance declarations
- type aliases
- constructor functions
- traverse functions
https://github.com/hasura/graphql-engine-mono/pull/1580
Co-authored-by: Phil Freeman <630306+paf31@users.noreply.github.com>
GitOrigin-RevId: bbdcb4119cec8bb3fc32f1294f91b8dea0728721
2021-06-18 02:12:11 +03:00
|
|
|
)
|
2021-06-11 06:26:50 +03:00
|
|
|
=> Bool
|
|
|
|
-> UserInfo
|
2021-04-22 00:44:37 +03:00
|
|
|
-> (AnnDel ('Postgres pgKind), DS.Seq Q.PrepArg)
|
2020-10-29 19:58:13 +03:00
|
|
|
-> m EncJSON
|
2021-07-29 11:29:12 +03:00
|
|
|
execDeleteQuery strfyNum userInfo (u, p) =
|
|
|
|
runMutation
|
|
|
|
(mkMutation userInfo (dqp1Table u) (MCDelete delete, p) (dqp1Output u) (dqp1AllCols u) strfyNum)
|
2020-10-29 19:58:13 +03:00
|
|
|
where
|
2020-11-12 12:25:48 +03:00
|
|
|
delete = mkDelete u
|
2020-10-29 19:58:13 +03:00
|
|
|
|
|
|
|
execInsertQuery
|
2021-06-11 06:26:50 +03:00
|
|
|
:: ( MonadTx m
|
2021-04-22 00:44:37 +03:00
|
|
|
, Backend ('Postgres pgKind)
|
2021-05-21 05:46:58 +03:00
|
|
|
, PostgresAnnotatedFieldJSON pgKind
|
2021-07-29 11:29:12 +03:00
|
|
|
, MonadReader QueryTagsComment m
|
2020-10-29 19:58:13 +03:00
|
|
|
)
|
2021-06-11 06:26:50 +03:00
|
|
|
=> Bool
|
|
|
|
-> UserInfo
|
2021-04-22 00:44:37 +03:00
|
|
|
-> (InsertQueryP1 ('Postgres pgKind), DS.Seq Q.PrepArg)
|
2020-10-29 19:58:13 +03:00
|
|
|
-> m EncJSON
|
2021-06-11 06:26:50 +03:00
|
|
|
execInsertQuery strfyNum userInfo (u, p) =
|
|
|
|
runMutation
|
2021-07-29 11:29:12 +03:00
|
|
|
(mkMutation userInfo (iqp1Table u) (MCCheckConstraint insertCTE, p) (iqp1Output u) (iqp1AllCols u) strfyNum)
|
2020-10-29 19:58:13 +03:00
|
|
|
where
|
|
|
|
insertCTE = mkInsertCTE u
|
|
|
|
|
|
|
|
|
|
|
|
|
2020-07-01 15:14:19 +03:00
|
|
|
{- Note: [Prepared statements in Mutations]
|
|
|
|
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
|
|
|
|
The SQL statements we generate for mutations seem to include the actual values
|
|
|
|
in the statements in some cases which pretty much makes them unfit for reuse
|
|
|
|
(Handling relationships in the returning clause is the source of this
|
|
|
|
complexity). Further, `PGConn` has an internal cache which maps a statement to
|
|
|
|
a 'prepared statement id' on Postgres. As we prepare more and more single-use
|
|
|
|
SQL statements we end up leaking memory both on graphql-engine and Postgres
|
|
|
|
till the connection is closed. So a simpler but very crude fix is to not use
|
|
|
|
prepared statements for mutations. The performance of insert mutations
|
|
|
|
shouldn't be affected but updates and delete mutations with complex boolean
|
|
|
|
conditions **might** see some degradation.
|
|
|
|
-}
|
|
|
|
|
2020-05-27 18:02:58 +03:00
|
|
|
mutateAndSel
|
2021-04-22 00:44:37 +03:00
|
|
|
:: forall pgKind m
|
2021-06-11 06:26:50 +03:00
|
|
|
. ( MonadTx m
|
2021-04-22 00:44:37 +03:00
|
|
|
, Backend ('Postgres pgKind)
|
2021-05-21 05:46:58 +03:00
|
|
|
, PostgresAnnotatedFieldJSON pgKind
|
2021-07-29 11:29:12 +03:00
|
|
|
, MonadReader QueryTagsComment m
|
2021-04-22 00:44:37 +03:00
|
|
|
)
|
2021-06-11 06:26:50 +03:00
|
|
|
=> Mutation ('Postgres pgKind)
|
2020-07-14 22:00:58 +03:00
|
|
|
-> m EncJSON
|
2021-06-11 06:26:50 +03:00
|
|
|
mutateAndSel (Mutation qt q mutationOutput allCols strfyNum) = do
|
2019-03-07 13:24:07 +03:00
|
|
|
-- Perform mutation and fetch unique columns
|
2020-05-27 18:02:58 +03:00
|
|
|
MutateResp _ columnVals <- liftTx $ mutateAndFetchCols qt allCols q strfyNum
|
2020-11-12 12:25:48 +03:00
|
|
|
select <- mkSelectExpFromColumnValues qt allCols columnVals
|
2019-03-07 13:24:07 +03:00
|
|
|
-- Perform select query and fetch returning fields
|
2021-06-11 06:26:50 +03:00
|
|
|
executeMutationOutputQuery qt allCols Nothing
|
|
|
|
(MCSelectValues select) mutationOutput strfyNum []
|
2020-11-12 12:25:48 +03:00
|
|
|
|
|
|
|
withCheckPermission :: (MonadError QErr m) => m (a, Bool) -> m a
|
|
|
|
withCheckPermission sqlTx = do
|
|
|
|
(rawResponse, checkConstraint) <- sqlTx
|
|
|
|
unless checkConstraint $ throw400 PermissionError $
|
|
|
|
"check constraint of an insert/update permission has failed"
|
|
|
|
pure rawResponse
|
2020-05-27 18:02:58 +03:00
|
|
|
|
|
|
|
executeMutationOutputQuery
|
2021-04-22 00:44:37 +03:00
|
|
|
:: forall pgKind m
|
2021-06-11 06:26:50 +03:00
|
|
|
. ( MonadTx m
|
2021-04-22 00:44:37 +03:00
|
|
|
, Backend ('Postgres pgKind)
|
2021-05-21 05:46:58 +03:00
|
|
|
, PostgresAnnotatedFieldJSON pgKind
|
2021-07-29 11:29:12 +03:00
|
|
|
, MonadReader QueryTagsComment m
|
2021-04-22 00:44:37 +03:00
|
|
|
)
|
2021-06-11 06:26:50 +03:00
|
|
|
=> QualifiedTable
|
2021-04-22 00:44:37 +03:00
|
|
|
-> [ColumnInfo ('Postgres pgKind)]
|
2020-11-12 12:25:48 +03:00
|
|
|
-> Maybe Int
|
|
|
|
-> MutationCTE
|
2021-04-22 00:44:37 +03:00
|
|
|
-> MutationOutput ('Postgres pgKind)
|
2020-11-12 12:25:48 +03:00
|
|
|
-> Bool
|
2020-05-27 18:02:58 +03:00
|
|
|
-> [Q.PrepArg] -- ^ Prepared params
|
|
|
|
-> m EncJSON
|
2021-06-11 06:26:50 +03:00
|
|
|
executeMutationOutputQuery qt allCols preCalAffRows cte mutOutput strfyNum prepArgs = do
|
2021-07-29 11:29:12 +03:00
|
|
|
queryTags <- ask
|
2020-11-12 12:25:48 +03:00
|
|
|
let queryTx :: Q.FromRes a => m a
|
|
|
|
queryTx = do
|
|
|
|
let selectWith = mkMutationOutputExp qt allCols preCalAffRows cte mutOutput strfyNum
|
|
|
|
query = Q.fromBuilder $ toSQL selectWith
|
2021-07-29 11:29:12 +03:00
|
|
|
queryWithQueryTags = query { Q.getQueryText = (Q.getQueryText query) <> (_unQueryTagsComment queryTags) }
|
2020-11-12 12:25:48 +03:00
|
|
|
-- See Note [Prepared statements in Mutations]
|
2021-07-29 11:29:12 +03:00
|
|
|
liftTx (Q.rawQE dmlTxErrorHandler queryWithQueryTags prepArgs False)
|
2020-11-12 12:25:48 +03:00
|
|
|
|
2021-06-11 06:26:50 +03:00
|
|
|
if checkPermissionRequired cte
|
|
|
|
then withCheckPermission $ Q.getRow <$> queryTx
|
|
|
|
else (runIdentity . Q.getRow) <$> queryTx
|
2019-03-07 13:24:07 +03:00
|
|
|
|
|
|
|
mutateAndFetchCols
|
2021-04-22 00:44:37 +03:00
|
|
|
:: forall pgKind
|
2021-05-21 05:46:58 +03:00
|
|
|
. (Backend ('Postgres pgKind), PostgresAnnotatedFieldJSON pgKind)
|
2021-04-22 00:44:37 +03:00
|
|
|
=> QualifiedTable
|
|
|
|
-> [ColumnInfo ('Postgres pgKind)]
|
2020-11-12 12:25:48 +03:00
|
|
|
-> (MutationCTE, DS.Seq Q.PrepArg)
|
2019-03-07 13:24:07 +03:00
|
|
|
-> Bool
|
2021-04-22 00:44:37 +03:00
|
|
|
-> Q.TxE QErr (MutateResp ('Postgres pgKind) TxtEncodedVal)
|
2020-11-12 12:25:48 +03:00
|
|
|
mutateAndFetchCols qt cols (cte, p) strfyNum = do
|
|
|
|
let mutationTx :: Q.FromRes a => Q.TxE QErr a
|
|
|
|
mutationTx =
|
|
|
|
-- See Note [Prepared statements in Mutations]
|
|
|
|
Q.rawQE dmlTxErrorHandler sqlText (toList p) False
|
|
|
|
|
|
|
|
if checkPermissionRequired cte
|
|
|
|
then withCheckPermission $ (first Q.getAltJ . Q.getRow) <$> mutationTx
|
|
|
|
else (Q.getAltJ . runIdentity . Q.getRow) <$> mutationTx
|
2019-03-07 13:24:07 +03:00
|
|
|
where
|
2020-10-27 13:34:31 +03:00
|
|
|
aliasIdentifier = Identifier $ qualifiedObjectToText qt <> "__mutation_result"
|
|
|
|
tabFrom = FromIdentifier aliasIdentifier
|
2019-03-07 13:24:07 +03:00
|
|
|
tabPerm = TablePerm annBoolExpTrue Nothing
|
|
|
|
selFlds = flip map cols $
|
2021-04-22 00:44:37 +03:00
|
|
|
\ci -> (fromCol @('Postgres pgKind) $ pgiColumn ci, mkAnnColumnFieldAsText ci)
|
2019-03-07 13:24:07 +03:00
|
|
|
|
2020-11-12 12:25:48 +03:00
|
|
|
sqlText = Q.fromBuilder $ toSQL selectWith
|
|
|
|
selectWith = S.SelectWith [(S.Alias aliasIdentifier, getMutationCTE cte)] select
|
|
|
|
select = S.mkSelect { S.selExtr = S.Extractor extrExp Nothing
|
|
|
|
: bool [] [S.Extractor checkErrExp Nothing] (checkPermissionRequired cte)
|
|
|
|
}
|
|
|
|
checkErrExp = mkCheckErrorExp aliasIdentifier
|
2019-03-07 13:24:07 +03:00
|
|
|
extrExp = S.applyJsonBuildObj
|
|
|
|
[ S.SELit "affected_rows", affRowsSel
|
|
|
|
, S.SELit "returning_columns", colSel
|
|
|
|
]
|
|
|
|
|
|
|
|
affRowsSel = S.SESelect $
|
|
|
|
S.mkSelect
|
|
|
|
{ S.selExtr = [S.Extractor S.countStar Nothing]
|
2020-10-27 13:34:31 +03:00
|
|
|
, S.selFrom = Just $ S.FromExp [S.FIIdentifier aliasIdentifier]
|
2019-03-07 13:24:07 +03:00
|
|
|
}
|
2020-02-13 20:38:23 +03:00
|
|
|
colSel = S.SESelect $ mkSQLSelect JASMultipleRows $
|
2020-06-08 15:13:01 +03:00
|
|
|
AnnSelectG selFlds tabFrom tabPerm noSelectArgs strfyNum
|