2023-06-28 13:18:09 +03:00
|
|
|
{-# LANGUAGE TemplateHaskell #-}
|
|
|
|
|
2022-02-08 12:24:34 +03:00
|
|
|
-- | Postgres Execute Mutation
|
|
|
|
--
|
|
|
|
-- Generic combinators for translating and excecuting IR mutation statements.
|
|
|
|
-- Used by the specific mutation modules, e.g. 'Hasura.Backends.Postgres.Execute.Insert'.
|
|
|
|
--
|
|
|
|
-- See 'Hasura.Backends.Postgres.Instances.Execute'.
|
2020-10-29 19:58:13 +03:00
|
|
|
module Hasura.Backends.Postgres.Execute.Mutation
|
2022-02-15 22:55:22 +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,
|
2023-06-28 13:18:09 +03:00
|
|
|
--
|
|
|
|
ValidateInputPayloadVersion,
|
|
|
|
validateInputPayloadVersion,
|
|
|
|
ValidateInputErrorResponse (..),
|
|
|
|
HttpHandlerLog (..),
|
|
|
|
ValidateInsertInputLog (..),
|
|
|
|
InsertValidationPayloadMap,
|
|
|
|
validateUpdateMutation,
|
|
|
|
validateMutation,
|
2020-10-29 19:58:13 +03:00
|
|
|
)
|
2019-09-14 09:01:06 +03:00
|
|
|
where
|
2020-10-27 16:53:49 +03:00
|
|
|
|
2023-06-28 13:18:09 +03:00
|
|
|
import Control.Exception (try)
|
|
|
|
import Control.Lens qualified as Lens
|
2023-01-27 17:36:35 +03:00
|
|
|
import Control.Monad.Writer (runWriter)
|
2021-04-22 00:44:37 +03:00
|
|
|
import Data.Aeson
|
2023-06-28 13:18:09 +03:00
|
|
|
import Data.Aeson qualified as J
|
|
|
|
import Data.Aeson.Key qualified as J
|
|
|
|
import Data.Aeson.TH qualified as J
|
|
|
|
import Data.Environment qualified as Env
|
|
|
|
import Data.HashMap.Strict qualified as HashMap
|
|
|
|
import Data.HashMap.Strict.InsOrd qualified as InsOrdHashMap
|
2020-10-29 19:58:13 +03:00
|
|
|
import Data.Sequence qualified as DS
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
import Database.PG.Query qualified as PG
|
2020-10-29 19:58:13 +03:00
|
|
|
import Hasura.Backends.Postgres.Connection
|
|
|
|
import Hasura.Backends.Postgres.SQL.DML qualified as S
|
2023-06-28 13:18:09 +03:00
|
|
|
import Hasura.Backends.Postgres.SQL.Types hiding (TableName)
|
2020-10-27 16:53:49 +03:00
|
|
|
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
|
2023-01-27 17:36:35 +03:00
|
|
|
import Hasura.Backends.Postgres.Translate.Select.Internal.Helpers (customSQLToTopLevelCTEs, toQuery)
|
2020-10-29 19:58:13 +03:00
|
|
|
import Hasura.Backends.Postgres.Translate.Update
|
2023-06-28 13:18:09 +03:00
|
|
|
import Hasura.Backends.Postgres.Types.Update qualified as Postgres
|
2021-05-11 18:18:31 +03:00
|
|
|
import Hasura.Base.Error
|
2019-03-18 19:22:21 +03:00
|
|
|
import Hasura.EncJSON
|
2023-06-28 13:18:09 +03:00
|
|
|
import Hasura.GraphQL.Parser.Internal.Convert
|
|
|
|
import Hasura.GraphQL.Parser.Variable qualified as G
|
|
|
|
import Hasura.HTTP
|
|
|
|
import Hasura.Logging qualified as L
|
2019-09-14 09:01:06 +03:00
|
|
|
import Hasura.Prelude
|
2021-07-29 11:29:12 +03:00
|
|
|
import Hasura.QueryTags
|
2023-06-28 13:18:09 +03:00
|
|
|
import Hasura.RQL.DDL.Headers
|
2022-04-27 16:57:28 +03:00
|
|
|
import Hasura.RQL.IR.BoolExp
|
2020-10-29 19:58:13 +03:00
|
|
|
import Hasura.RQL.IR.Delete
|
|
|
|
import Hasura.RQL.IR.Insert
|
2023-06-28 13:18:09 +03:00
|
|
|
import Hasura.RQL.IR.Insert qualified as IR
|
2020-10-29 19:58:13 +03:00
|
|
|
import Hasura.RQL.IR.Returning
|
|
|
|
import Hasura.RQL.IR.Select
|
|
|
|
import Hasura.RQL.IR.Update
|
2023-06-28 13:18:09 +03:00
|
|
|
import Hasura.RQL.IR.Update qualified as IR
|
|
|
|
import Hasura.RQL.IR.Value (UnpreparedValue)
|
|
|
|
import Hasura.RQL.IR.Value qualified as IR
|
2022-04-27 16:57:28 +03:00
|
|
|
import Hasura.RQL.Types.Backend
|
2023-04-24 21:35:48 +03:00
|
|
|
import Hasura.RQL.Types.BackendType
|
2022-04-27 16:57:28 +03:00
|
|
|
import Hasura.RQL.Types.Column
|
|
|
|
import Hasura.RQL.Types.Common
|
2023-06-28 13:18:09 +03:00
|
|
|
import Hasura.RQL.Types.Headers (HeaderConf)
|
2023-05-17 17:02:09 +03:00
|
|
|
import Hasura.RQL.Types.NamingCase (NamingCase)
|
2023-06-28 13:18:09 +03:00
|
|
|
import Hasura.RQL.Types.Permission
|
2023-04-24 18:17:15 +03:00
|
|
|
import Hasura.RQL.Types.Schema.Options qualified as Options
|
2023-06-28 13:18:09 +03:00
|
|
|
import Hasura.Server.Utils
|
2020-10-21 19:35:06 +03:00
|
|
|
import Hasura.Session
|
2023-06-28 13:18:09 +03:00
|
|
|
import Hasura.Tracing qualified as Tracing
|
|
|
|
import Language.GraphQL.Draft.Syntax qualified as G
|
|
|
|
import Network.HTTP.Client.Transformable qualified as HTTP
|
|
|
|
import Network.Wreq qualified as Wreq
|
2019-03-07 13:24:07 +03:00
|
|
|
|
2021-04-22 00:44:37 +03:00
|
|
|
data MutateResp (b :: BackendType) a = MutateResp
|
2022-07-29 17:05:03 +03:00
|
|
|
{ _mrAffectedRows :: Int,
|
|
|
|
_mrReturningColumns :: [ColumnValues b a]
|
2021-09-24 01:56:37 +03:00
|
|
|
}
|
2021-04-22 00:44:37 +03:00
|
|
|
deriving (Generic)
|
2020-10-27 16:53:49 +03:00
|
|
|
|
2021-04-22 00:44:37 +03:00
|
|
|
deriving instance (Backend b, Show a) => Show (MutateResp b a)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-04-22 00:44:37 +03:00
|
|
|
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-11-12 12:25:48 +03:00
|
|
|
data Mutation (b :: BackendType) = Mutation
|
2022-07-29 17:05:03 +03:00
|
|
|
{ _mTable :: QualifiedTable,
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
_mQuery :: (MutationCTE, DS.Seq PG.PrepArg),
|
2022-07-29 17:05:03 +03:00
|
|
|
_mOutput :: MutationOutput b,
|
|
|
|
_mCols :: [ColumnInfo b],
|
|
|
|
_mStrfyNum :: Options.StringifyNumbers,
|
|
|
|
_mNamingConvention :: Maybe NamingCase
|
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 ->
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
(MutationCTE, DS.Seq PG.PrepArg) ->
|
2021-04-22 00:44:37 +03:00
|
|
|
MutationOutput ('Postgres pgKind) ->
|
|
|
|
[ColumnInfo ('Postgres pgKind)] ->
|
2022-07-14 20:57:28 +03:00
|
|
|
Options.StringifyNumbers ->
|
2022-07-19 09:55:42 +03:00
|
|
|
Maybe NamingCase ->
|
2021-04-22 00:44:37 +03:00
|
|
|
Mutation ('Postgres pgKind)
|
2022-07-19 09:55:42 +03:00
|
|
|
mkMutation _userInfo table query output allCols strfyNum tCase =
|
|
|
|
Mutation table query output allCols strfyNum tCase
|
2019-03-07 13:24:07 +03:00
|
|
|
|
2020-05-27 18:02:58 +03:00
|
|
|
runMutation ::
|
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 =
|
2023-05-24 16:51:56 +03:00
|
|
|
bool (mutateAndReturn mut) (mutateAndSel mut)
|
|
|
|
$ hasNestedFld
|
|
|
|
$ _mOutput mut
|
2019-03-07 13:24:07 +03:00
|
|
|
|
2020-05-27 18:02:58 +03:00
|
|
|
mutateAndReturn ::
|
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
|
2022-07-19 09:55:42 +03:00
|
|
|
mutateAndReturn (Mutation qt (cte, p) mutationOutput allCols strfyNum tCase) =
|
|
|
|
executeMutationOutputQuery qt allCols Nothing cte mutationOutput strfyNum tCase (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
|
|
|
) =>
|
2022-07-14 20:57:28 +03:00
|
|
|
Options.StringifyNumbers ->
|
2022-07-19 09:55:42 +03:00
|
|
|
Maybe NamingCase ->
|
2021-06-11 06:26:50 +03:00
|
|
|
UserInfo ->
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
(AnnotatedUpdate ('Postgres pgKind), DS.Seq PG.PrepArg) ->
|
2020-10-29 19:58:13 +03:00
|
|
|
m EncJSON
|
2022-07-19 09:55:42 +03:00
|
|
|
execUpdateQuery strfyNum tCase userInfo (u, p) =
|
2022-07-18 18:15:34 +03:00
|
|
|
case updateCTE of
|
|
|
|
Update singleUpdate -> runCTE singleUpdate
|
|
|
|
MultiUpdate ctes -> encJFromList <$> traverse runCTE ctes
|
2020-10-29 19:58:13 +03:00
|
|
|
where
|
2022-07-18 18:15:34 +03:00
|
|
|
updateCTE :: UpdateCTE
|
2020-10-29 19:58:13 +03:00
|
|
|
updateCTE = mkUpdateCTE u
|
|
|
|
|
2022-07-18 18:15:34 +03:00
|
|
|
runCTE :: S.TopLevelCTE -> m EncJSON
|
|
|
|
runCTE cte =
|
|
|
|
runMutation
|
2022-07-19 09:55:42 +03:00
|
|
|
(mkMutation userInfo (_auTable u) (MCCheckConstraint cte, p) (_auOutput u) (_auAllCols u) strfyNum tCase)
|
2022-07-18 18:15:34 +03:00
|
|
|
|
2020-10-29 19:58:13 +03:00
|
|
|
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
|
|
|
) =>
|
2022-07-14 20:57:28 +03:00
|
|
|
Options.StringifyNumbers ->
|
2022-07-19 09:55:42 +03:00
|
|
|
Maybe NamingCase ->
|
2021-06-11 06:26:50 +03:00
|
|
|
UserInfo ->
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
(AnnDel ('Postgres pgKind), DS.Seq PG.PrepArg) ->
|
2020-10-29 19:58:13 +03:00
|
|
|
m EncJSON
|
2022-07-19 09:55:42 +03:00
|
|
|
execDeleteQuery strfyNum tCase userInfo (u, p) =
|
2021-07-29 11:29:12 +03:00
|
|
|
runMutation
|
2022-07-19 09:55:42 +03:00
|
|
|
(mkMutation userInfo (_adTable u) (MCDelete delete, p) (_adOutput u) (_adAllCols u) strfyNum tCase)
|
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
|
|
|
) =>
|
2022-07-14 20:57:28 +03:00
|
|
|
Options.StringifyNumbers ->
|
2022-07-19 09:55:42 +03:00
|
|
|
Maybe NamingCase ->
|
2021-06-11 06:26:50 +03:00
|
|
|
UserInfo ->
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
(InsertQueryP1 ('Postgres pgKind), DS.Seq PG.PrepArg) ->
|
2020-10-29 19:58:13 +03:00
|
|
|
m EncJSON
|
2022-07-19 09:55:42 +03:00
|
|
|
execInsertQuery strfyNum tCase userInfo (u, p) =
|
2021-06-11 06:26:50 +03:00
|
|
|
runMutation
|
2022-07-19 09:55:42 +03:00
|
|
|
(mkMutation userInfo (iqp1Table u) (MCCheckConstraint insertCTE, p) (iqp1Output u) (iqp1AllCols u) strfyNum tCase)
|
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
|
2022-07-19 09:55:42 +03:00
|
|
|
mutateAndSel (Mutation qt q mutationOutput allCols strfyNum tCase) = do
|
2019-03-07 13:24:07 +03:00
|
|
|
-- Perform mutation and fetch unique columns
|
2022-07-19 09:55:42 +03:00
|
|
|
MutateResp _ columnVals <- liftTx $ mutateAndFetchCols qt allCols q strfyNum tCase
|
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
|
2022-07-19 09:55:42 +03:00
|
|
|
tCase
|
2021-06-11 06:26:50 +03:00
|
|
|
[]
|
2020-11-12 12:25:48 +03:00
|
|
|
|
|
|
|
withCheckPermission :: (MonadError QErr m) => m (a, Bool) -> m a
|
|
|
|
withCheckPermission sqlTx = do
|
|
|
|
(rawResponse, checkConstraint) <- sqlTx
|
2023-05-24 16:51:56 +03:00
|
|
|
unless checkConstraint
|
|
|
|
$ throw400 PermissionError
|
|
|
|
$ "check constraint of an insert/update permission has failed"
|
2020-11-12 12:25:48 +03:00
|
|
|
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) ->
|
2022-07-14 20:57:28 +03:00
|
|
|
Options.StringifyNumbers ->
|
2022-07-19 09:55:42 +03:00
|
|
|
Maybe NamingCase ->
|
2020-05-27 18:02:58 +03:00
|
|
|
-- | Prepared params
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
[PG.PrepArg] ->
|
2020-05-27 18:02:58 +03:00
|
|
|
m EncJSON
|
2022-07-19 09:55:42 +03:00
|
|
|
executeMutationOutputQuery qt allCols preCalAffRows cte mutOutput strfyNum tCase prepArgs = do
|
2021-07-29 11:29:12 +03:00
|
|
|
queryTags <- ask
|
2023-05-17 17:02:09 +03:00
|
|
|
let queryTx :: (PG.FromRes a) => m a
|
2020-11-12 12:25:48 +03:00
|
|
|
queryTx = do
|
2022-07-19 09:55:42 +03:00
|
|
|
let selectWith = mkMutationOutputExp qt allCols preCalAffRows cte mutOutput strfyNum tCase
|
2023-01-27 17:36:35 +03:00
|
|
|
query = toQuery selectWith
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
queryWithQueryTags = query {PG.getQueryText = (PG.getQueryText query) <> (_unQueryTagsComment queryTags)}
|
2020-11-12 12:25:48 +03:00
|
|
|
-- See Note [Prepared statements in Mutations]
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
liftTx (PG.rawQE dmlTxErrorHandler queryWithQueryTags prepArgs False)
|
2020-11-12 12:25:48 +03:00
|
|
|
|
2021-06-11 06:26:50 +03:00
|
|
|
if checkPermissionRequired cte
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
then withCheckPermission $ PG.getRow <$> queryTx
|
|
|
|
else runIdentity . PG.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)] ->
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
(MutationCTE, DS.Seq PG.PrepArg) ->
|
2022-07-14 20:57:28 +03:00
|
|
|
Options.StringifyNumbers ->
|
2022-07-19 09:55:42 +03:00
|
|
|
Maybe NamingCase ->
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
PG.TxE QErr (MutateResp ('Postgres pgKind) TxtEncodedVal)
|
2022-07-19 09:55:42 +03:00
|
|
|
mutateAndFetchCols qt cols (cte, p) strfyNum tCase = do
|
2023-05-17 17:02:09 +03:00
|
|
|
let mutationTx :: (PG.FromRes a) => PG.TxE QErr a
|
2020-11-12 12:25:48 +03:00
|
|
|
mutationTx =
|
|
|
|
-- See Note [Prepared statements in Mutations]
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
PG.rawQE dmlTxErrorHandler sqlText (toList p) False
|
2020-11-12 12:25:48 +03:00
|
|
|
|
|
|
|
if checkPermissionRequired cte
|
2022-09-21 21:40:41 +03:00
|
|
|
then withCheckPermission $ (first PG.getViaJSON . PG.getRow) <$> mutationTx
|
|
|
|
else (PG.getViaJSON . runIdentity . PG.getRow) <$> mutationTx
|
2019-03-07 13:24:07 +03:00
|
|
|
where
|
2022-10-05 13:03:36 +03:00
|
|
|
rawAlias = S.mkTableAlias $ "mutres__" <> qualifiedObjectToText qt
|
|
|
|
rawIdentifier = S.tableAliasToIdentifier rawAlias
|
|
|
|
tabFrom = FromIdentifier $ FIIdentifier (unTableIdentifier rawIdentifier)
|
2019-03-07 13:24:07 +03:00
|
|
|
tabPerm = TablePerm annBoolExpTrue Nothing
|
2023-05-24 16:51:56 +03:00
|
|
|
selFlds = flip map cols
|
|
|
|
$ \ci -> (fromCol @('Postgres pgKind) $ ciColumn ci, mkAnnColumnFieldAsText ci)
|
2019-03-07 13:24:07 +03:00
|
|
|
|
2023-01-27 17:36:35 +03:00
|
|
|
sqlText = toQuery selectWith
|
|
|
|
|
2020-11-12 12:25:48 +03:00
|
|
|
select =
|
|
|
|
S.mkSelect
|
|
|
|
{ S.selExtr =
|
|
|
|
S.Extractor extrExp Nothing
|
|
|
|
: bool [] [S.Extractor checkErrExp Nothing] (checkPermissionRequired cte)
|
|
|
|
}
|
2023-01-27 17:36:35 +03:00
|
|
|
|
|
|
|
selectWith =
|
|
|
|
S.SelectWith
|
|
|
|
( [(rawAlias, getMutationCTE cte)]
|
|
|
|
<> customSQLToTopLevelCTEs customSQLCTEs
|
|
|
|
)
|
|
|
|
select
|
|
|
|
|
2022-10-05 13:03:36 +03:00
|
|
|
checkErrExp = mkCheckErrorExp rawIdentifier
|
2019-03-07 13:24:07 +03:00
|
|
|
extrExp =
|
|
|
|
S.applyJsonBuildObj
|
|
|
|
[ S.SELit "affected_rows",
|
|
|
|
affRowsSel,
|
|
|
|
S.SELit "returning_columns",
|
|
|
|
colSel
|
|
|
|
]
|
|
|
|
|
|
|
|
affRowsSel =
|
2023-05-24 16:51:56 +03:00
|
|
|
S.SESelect
|
|
|
|
$ S.mkSelect
|
2019-03-07 13:24:07 +03:00
|
|
|
{ S.selExtr = [S.Extractor S.countStar Nothing],
|
2022-10-05 13:03:36 +03:00
|
|
|
S.selFrom = Just $ S.FromExp [S.FIIdentifier rawIdentifier]
|
2019-03-07 13:24:07 +03:00
|
|
|
}
|
2023-01-27 17:36:35 +03:00
|
|
|
|
|
|
|
(colSel, customSQLCTEs) =
|
2023-05-24 16:51:56 +03:00
|
|
|
runWriter
|
|
|
|
$ S.SESelect
|
|
|
|
<$> mkSQLSelect
|
|
|
|
JASMultipleRows
|
|
|
|
( AnnSelectG selFlds tabFrom tabPerm noSelectArgs strfyNum tCase
|
|
|
|
)
|
2023-06-28 13:18:09 +03:00
|
|
|
|
|
|
|
-------------- Validating insert input using external HTTP webhook -----------------------
|
|
|
|
type ValidateInputPayloadVersion = Int
|
|
|
|
|
|
|
|
validateInputPayloadVersion :: ValidateInputPayloadVersion
|
|
|
|
validateInputPayloadVersion = 1
|
|
|
|
|
|
|
|
newtype ValidateInputErrorResponse = ValidateInputErrorResponse {_vierMessage :: Text}
|
|
|
|
deriving (Show, Eq)
|
|
|
|
|
|
|
|
$(J.deriveJSON hasuraJSON ''ValidateInputErrorResponse)
|
|
|
|
|
|
|
|
data HttpHandlerLog = HttpHandlerLog
|
|
|
|
{ _hhlUrl :: Text,
|
|
|
|
_hhlRequest :: J.Value,
|
|
|
|
_hhlRequestHeaders :: [HeaderConf],
|
|
|
|
_hhlResponse :: J.Value,
|
|
|
|
_hhlResponseStatus :: Int
|
|
|
|
}
|
|
|
|
deriving (Show)
|
|
|
|
|
|
|
|
$(J.deriveToJSON hasuraJSON ''HttpHandlerLog)
|
|
|
|
|
|
|
|
data ValidateInsertInputLog
|
|
|
|
= VIILHttpHandler HttpHandlerLog
|
|
|
|
|
|
|
|
instance J.ToJSON ValidateInsertInputLog where
|
|
|
|
toJSON (VIILHttpHandler httpHandlerLog) =
|
|
|
|
J.object $ ["type" J..= ("http" :: String), "details" J..= J.toJSON httpHandlerLog]
|
|
|
|
|
|
|
|
instance L.ToEngineLog ValidateInsertInputLog L.Hasura where
|
|
|
|
toEngineLog ahl = (L.LevelInfo, L.ELTValidateInputLog, J.toJSON ahl)
|
|
|
|
|
|
|
|
-- | Map of table name and the value that is being inserted for that table
|
|
|
|
-- This map is helpful for collecting all the insert mutation arguments for the
|
|
|
|
-- nested tables and then sending them all at onve to the input validation webhook.
|
|
|
|
type InsertValidationPayloadMap pgKind = InsOrdHashMap.InsOrdHashMap (TableName ('Postgres pgKind)) ([IR.AnnotatedInsertRow ('Postgres pgKind) (IR.UnpreparedValue ('Postgres pgKind))], (ValidateInput ResolvedWebhook))
|
|
|
|
|
|
|
|
validateUpdateMutation ::
|
|
|
|
forall pgKind m.
|
|
|
|
(MonadError QErr m, MonadIO m, Tracing.MonadTrace m) =>
|
|
|
|
Env.Environment ->
|
|
|
|
HTTP.Manager ->
|
|
|
|
L.Logger L.Hasura ->
|
|
|
|
UserInfo ->
|
|
|
|
ResolvedWebhook ->
|
|
|
|
[HeaderConf] ->
|
|
|
|
Timeout ->
|
|
|
|
Bool ->
|
|
|
|
[HTTP.Header] ->
|
|
|
|
IR.AnnotatedUpdateG ('Postgres pgKind) Void (UnpreparedValue ('Postgres pgKind)) ->
|
|
|
|
Maybe (HashMap G.Name (G.Value G.Variable)) ->
|
|
|
|
m ()
|
|
|
|
validateUpdateMutation env manager logger userInfo resolvedWebHook confHeaders timeout forwardClientHeaders reqHeaders updateOperation maybeSelSetArgs = do
|
|
|
|
inputData <-
|
|
|
|
case maybeSelSetArgs of
|
|
|
|
Just arguments -> do
|
|
|
|
case (IR._auUpdateVariant updateOperation) of
|
|
|
|
-- Mutation arguments for single update (eg: update_customer) are
|
|
|
|
-- present as seperate root fields of the selection set.
|
|
|
|
-- eg:
|
|
|
|
Postgres.SingleBatch _ -> do
|
|
|
|
-- this constructs something like: {"_set":{"name": {"_eq": "abc"}}, "where":{"id":{"_eq":10}}}
|
|
|
|
let singleBatchinputVal =
|
|
|
|
J.object
|
|
|
|
$ map
|
|
|
|
(\(k, v) -> J.fromText (G.unName k) J..= graphQLToJSON v)
|
|
|
|
(HashMap.toList $ arguments)
|
|
|
|
return (J.object ["input" J..= [singleBatchinputVal]])
|
|
|
|
-- Mutation arguments for multiple updates (eg:
|
|
|
|
-- update_customer_many) are present in the "updates" field of the
|
|
|
|
-- selection set.
|
|
|
|
-- Look for "updates" field and get the mutation arguments from it.
|
|
|
|
-- eg: {"updates": [{"_set":{"id":{"_eq":10}}, "where":{"name":{"_eq":"abc"}}}]}
|
|
|
|
Postgres.MultipleBatches _ -> do
|
|
|
|
case (HashMap.lookup $$(G.litName "updates") arguments) of
|
|
|
|
Nothing -> return $ J.Null
|
|
|
|
Just val -> (return $ J.object ["input" J..= graphQLToJSON val])
|
|
|
|
Nothing -> return J.Null
|
|
|
|
validateMutation env manager logger userInfo resolvedWebHook confHeaders timeout forwardClientHeaders reqHeaders inputData
|
|
|
|
|
|
|
|
validateMutation ::
|
|
|
|
forall m.
|
|
|
|
( MonadError QErr m,
|
|
|
|
MonadIO m,
|
|
|
|
Tracing.MonadTrace m
|
|
|
|
) =>
|
|
|
|
Env.Environment ->
|
|
|
|
HTTP.Manager ->
|
|
|
|
L.Logger L.Hasura ->
|
|
|
|
UserInfo ->
|
|
|
|
ResolvedWebhook ->
|
|
|
|
[HeaderConf] ->
|
|
|
|
Timeout ->
|
|
|
|
Bool ->
|
|
|
|
[HTTP.Header] ->
|
|
|
|
J.Value ->
|
|
|
|
m ()
|
|
|
|
validateMutation env manager logger userInfo (ResolvedWebhook urlText) confHeaders timeout forwardClientHeaders reqHeaders inputData = do
|
|
|
|
let requestBody =
|
|
|
|
J.object
|
|
|
|
[ "version" J..= validateInputPayloadVersion,
|
|
|
|
"session_variables" J..= _uiSession userInfo,
|
|
|
|
"role" J..= _uiRole userInfo,
|
|
|
|
"data" J..= inputData
|
|
|
|
]
|
|
|
|
resolvedConfHeaders <- makeHeadersFromConf env confHeaders
|
|
|
|
let clientHeaders = if forwardClientHeaders then mkClientHeadersForward reqHeaders else mempty
|
|
|
|
-- Using HashMap to avoid duplicate headers between configuration headers
|
|
|
|
-- and client headers where configuration headers are preferred
|
|
|
|
hdrs = (HashMap.toList . HashMap.fromList) (resolvedConfHeaders <> defaultHeaders <> clientHeaders)
|
|
|
|
initRequest <- liftIO $ HTTP.mkRequestThrow urlText
|
|
|
|
let request =
|
|
|
|
initRequest
|
|
|
|
& Lens.set HTTP.method "POST"
|
|
|
|
& Lens.set HTTP.headers hdrs
|
|
|
|
& Lens.set HTTP.body (HTTP.RequestBodyLBS $ J.encode requestBody)
|
|
|
|
& Lens.set HTTP.timeout (HTTP.responseTimeoutMicro (unTimeout timeout * 1000000)) -- (default: 10 seconds)
|
|
|
|
httpResponse <-
|
|
|
|
Tracing.traceHTTPRequest request $ \request' ->
|
|
|
|
liftIO . try $ HTTP.httpLbs request' manager
|
|
|
|
|
|
|
|
case httpResponse of
|
|
|
|
Left e ->
|
|
|
|
throw500WithDetail "http exception when validating input data"
|
|
|
|
$ J.toJSON
|
|
|
|
$ HttpException e
|
|
|
|
Right response -> do
|
|
|
|
let responseStatus = response Lens.^. Wreq.responseStatus
|
|
|
|
responseBody = response Lens.^. Wreq.responseBody
|
|
|
|
responseBodyForLogging = fromMaybe (J.String $ lbsToTxt responseBody) $ J.decode' responseBody
|
|
|
|
-- Log the details of the HTTP webhook call
|
|
|
|
L.unLogger logger $ VIILHttpHandler $ HttpHandlerLog urlText requestBody confHeaders responseBodyForLogging (HTTP.statusCode responseStatus)
|
|
|
|
if
|
|
|
|
| HTTP.statusIsSuccessful responseStatus -> pure ()
|
|
|
|
| responseStatus == HTTP.status400 -> do
|
|
|
|
ValidateInputErrorResponse errorMessage <-
|
|
|
|
J.eitherDecode responseBody `onLeft` \e ->
|
|
|
|
throw500WithDetail "received invalid response from input validation webhook"
|
|
|
|
$ J.toJSON
|
|
|
|
$ "invalid response: "
|
|
|
|
<> e
|
|
|
|
throw400 ValidationFailed errorMessage
|
|
|
|
| otherwise -> do
|
|
|
|
let err =
|
|
|
|
J.toJSON
|
|
|
|
$ "expecting 200 or 400 status code, but found "
|
|
|
|
++ show (HTTP.statusCode responseStatus)
|
|
|
|
throw500WithDetail "internal error when validating input data" err
|