2021-04-22 00:44:37 +03:00
|
|
|
{-# LANGUAGE UndecidableInstances #-}
|
2021-09-24 01:56:37 +03:00
|
|
|
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
2021-02-12 06:04:09 +03:00
|
|
|
|
2022-02-08 12:24:34 +03:00
|
|
|
-- | Postgres Instances Transport
|
|
|
|
--
|
|
|
|
-- Defines the MSSQL instance of 'BackendTransport' and how to interact with the
|
|
|
|
-- database for running queries, mutations, subscriptions, and so on.
|
2021-04-01 23:40:31 +03:00
|
|
|
module Hasura.Backends.Postgres.Instances.Transport
|
2021-09-24 01:56:37 +03:00
|
|
|
( runPGMutationTransaction,
|
|
|
|
)
|
|
|
|
where
|
|
|
|
|
|
|
|
import Data.Aeson qualified as J
|
|
|
|
import Data.ByteString qualified as B
|
|
|
|
import Data.HashMap.Strict.InsOrd qualified as OMap
|
|
|
|
import Data.Text.Extended
|
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
|
2022-04-27 16:57:28 +03:00
|
|
|
import Hasura.Backends.Postgres.Connection.MonadTx
|
2022-04-07 17:41:43 +03:00
|
|
|
import Hasura.Backends.Postgres.Execute.Subscription qualified as PGL
|
2022-04-27 16:57:28 +03:00
|
|
|
import Hasura.Backends.Postgres.Execute.Types
|
2021-09-24 01:56:37 +03:00
|
|
|
import Hasura.Backends.Postgres.Instances.Execute qualified as EQ
|
|
|
|
import Hasura.Backends.Postgres.SQL.Value
|
|
|
|
import Hasura.Backends.Postgres.Translate.Select (PostgresAnnotatedFieldJSON)
|
|
|
|
import Hasura.Base.Error
|
|
|
|
import Hasura.EncJSON
|
|
|
|
import Hasura.GraphQL.Execute.Backend
|
2022-03-21 13:39:49 +03:00
|
|
|
import Hasura.GraphQL.Execute.Subscription.Plan
|
2021-09-24 01:56:37 +03:00
|
|
|
import Hasura.GraphQL.Logging
|
2021-10-29 17:42:07 +03:00
|
|
|
import Hasura.GraphQL.Namespace
|
|
|
|
( RootFieldAlias,
|
|
|
|
RootFieldMap,
|
|
|
|
mkUnNamespacedRootFieldAlias,
|
|
|
|
)
|
2021-09-24 01:56:37 +03:00
|
|
|
import Hasura.GraphQL.Transport.Backend
|
|
|
|
import Hasura.GraphQL.Transport.HTTP.Protocol
|
|
|
|
import Hasura.Logging qualified as L
|
2022-06-23 12:14:24 +03:00
|
|
|
import Hasura.Name qualified as Name
|
2021-09-24 01:56:37 +03:00
|
|
|
import Hasura.Prelude
|
2022-04-27 16:57:28 +03:00
|
|
|
import Hasura.RQL.Types.Backend
|
|
|
|
import Hasura.SQL.Backend
|
2021-09-24 01:56:37 +03:00
|
|
|
import Hasura.Server.Types (RequestId)
|
|
|
|
import Hasura.Session
|
|
|
|
import Hasura.Tracing
|
|
|
|
import Hasura.Tracing qualified as Tracing
|
2021-02-12 06:04:09 +03:00
|
|
|
|
2021-05-21 05:46:58 +03:00
|
|
|
instance
|
2021-09-24 01:56:37 +03:00
|
|
|
( Backend ('Postgres pgKind),
|
|
|
|
PostgresAnnotatedFieldJSON pgKind
|
|
|
|
) =>
|
|
|
|
BackendTransport ('Postgres pgKind)
|
|
|
|
where
|
|
|
|
runDBQuery = runPGQuery
|
|
|
|
runDBMutation = runPGMutation
|
2021-02-20 16:45:49 +03:00
|
|
|
runDBSubscription = runPGSubscription
|
2022-04-07 17:41:43 +03:00
|
|
|
runDBStreamingSubscription = runPGStreamingSubscription
|
2021-04-13 14:10:08 +03:00
|
|
|
runDBQueryExplain = runPGQueryExplain
|
2021-02-12 06:04:09 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
runPGQuery ::
|
|
|
|
( MonadIO m,
|
|
|
|
MonadError QErr m,
|
|
|
|
MonadQueryLog m,
|
|
|
|
MonadTrace m
|
|
|
|
) =>
|
|
|
|
RequestId ->
|
|
|
|
GQLReqUnparsed ->
|
2021-10-29 17:42:07 +03:00
|
|
|
RootFieldAlias ->
|
2021-09-24 01:56:37 +03:00
|
|
|
UserInfo ->
|
|
|
|
L.Logger L.Hasura ->
|
|
|
|
SourceConfig ('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
|
|
|
Tracing.TraceT (PG.TxET QErr IO) EncJSON ->
|
2021-09-24 01:56:37 +03:00
|
|
|
Maybe EQ.PreparedSql ->
|
|
|
|
-- | Also return the time spent in the PG query; for telemetry.
|
|
|
|
m (DiffTime, EncJSON)
|
2021-09-06 17:29:44 +03:00
|
|
|
runPGQuery reqId query fieldName _userInfo logger sourceConfig tx genSql = do
|
2021-02-12 06:04:09 +03:00
|
|
|
-- log the generated SQL and the graphql query
|
2021-03-13 17:40:50 +03:00
|
|
|
logQueryLog logger $ mkQueryLog query fieldName genSql reqId
|
2021-09-24 01:56:37 +03:00
|
|
|
withElapsedTime $
|
|
|
|
trace ("Postgres Query for root field " <>> fieldName) $
|
2021-09-25 06:59:35 +03:00
|
|
|
Tracing.interpTraceT (runQueryTx $ _pscExecCtx sourceConfig) tx
|
2021-09-24 01:56:37 +03:00
|
|
|
|
|
|
|
runPGMutation ::
|
|
|
|
( MonadIO m,
|
|
|
|
MonadError QErr m,
|
|
|
|
MonadQueryLog m,
|
|
|
|
MonadTrace m
|
|
|
|
) =>
|
|
|
|
RequestId ->
|
|
|
|
GQLReqUnparsed ->
|
2021-10-29 17:42:07 +03:00
|
|
|
RootFieldAlias ->
|
2021-09-24 01:56:37 +03:00
|
|
|
UserInfo ->
|
|
|
|
L.Logger L.Hasura ->
|
|
|
|
SourceConfig ('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
|
|
|
Tracing.TraceT (PG.TxET QErr IO) EncJSON ->
|
2021-09-24 01:56:37 +03:00
|
|
|
Maybe EQ.PreparedSql ->
|
|
|
|
m (DiffTime, EncJSON)
|
|
|
|
runPGMutation reqId query fieldName userInfo logger sourceConfig tx _genSql = do
|
2021-02-12 06:04:09 +03:00
|
|
|
-- log the graphql query
|
2021-03-13 17:40:50 +03:00
|
|
|
logQueryLog logger $ mkQueryLog query fieldName Nothing reqId
|
2021-02-12 06:04:09 +03:00
|
|
|
ctx <- Tracing.currentContext
|
2021-09-24 01:56:37 +03:00
|
|
|
withElapsedTime $
|
|
|
|
trace ("Postgres Mutation for root field " <>> fieldName) $
|
|
|
|
Tracing.interpTraceT
|
|
|
|
( liftEitherM . liftIO . runExceptT
|
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
|
|
|
. runTx (_pscExecCtx sourceConfig) PG.ReadWrite
|
2021-09-24 01:56:37 +03:00
|
|
|
. withTraceContext ctx
|
|
|
|
. withUserInfo userInfo
|
|
|
|
)
|
|
|
|
tx
|
|
|
|
|
|
|
|
runPGSubscription ::
|
|
|
|
MonadIO m =>
|
|
|
|
SourceConfig ('Postgres pgKind) ->
|
|
|
|
MultiplexedQuery ('Postgres pgKind) ->
|
|
|
|
[(CohortId, CohortVariables)] ->
|
|
|
|
m (DiffTime, Either QErr [(CohortId, B.ByteString)])
|
2021-09-01 20:56:46 +03:00
|
|
|
runPGSubscription sourceConfig query variables =
|
2021-09-24 01:56:37 +03:00
|
|
|
withElapsedTime $
|
2022-04-22 22:53:12 +03:00
|
|
|
runExceptT $ runQueryTx (_pscExecCtx sourceConfig) $ PGL.executeMultiplexedQuery query variables
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2022-04-07 17:41:43 +03:00
|
|
|
runPGStreamingSubscription ::
|
|
|
|
MonadIO m =>
|
|
|
|
SourceConfig ('Postgres pgKind) ->
|
|
|
|
MultiplexedQuery ('Postgres pgKind) ->
|
|
|
|
[(CohortId, CohortVariables)] ->
|
|
|
|
m (DiffTime, Either QErr [(CohortId, B.ByteString, CursorVariableValues)])
|
|
|
|
runPGStreamingSubscription sourceConfig query variables =
|
|
|
|
withElapsedTime $
|
|
|
|
runExceptT $ do
|
|
|
|
res <- runQueryTx (_pscExecCtx sourceConfig) $ PGL.executeStreamingMultiplexedQuery query variables
|
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
|
|
|
pure $ res <&> (\(cohortId, cohortRes, cursorVariableVals) -> (cohortId, cohortRes, PG.getAltJ cursorVariableVals))
|
2022-04-07 17:41:43 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
runPGQueryExplain ::
|
|
|
|
forall pgKind m.
|
|
|
|
( MonadIO m,
|
|
|
|
MonadError QErr m
|
|
|
|
) =>
|
|
|
|
DBStepInfo ('Postgres pgKind) ->
|
|
|
|
m EncJSON
|
2021-04-13 14:10:08 +03:00
|
|
|
runPGQueryExplain (DBStepInfo _ sourceConfig _ action) =
|
|
|
|
-- All Postgres transport functions use the same monad stack: the ExecutionMonad defined in the
|
|
|
|
-- matching instance of BackendExecute. However, Explain doesn't need tracing! Rather than
|
|
|
|
-- introducing a separate "ExplainMonad", we simply use @runTraceTWithReporter@ to remove the
|
|
|
|
-- TraceT.
|
|
|
|
runQueryTx (_pscExecCtx sourceConfig) $ runTraceTWithReporter noReporter "explain" $ action
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
mkQueryLog ::
|
|
|
|
GQLReqUnparsed ->
|
2021-10-29 17:42:07 +03:00
|
|
|
RootFieldAlias ->
|
2021-09-24 01:56:37 +03:00
|
|
|
Maybe EQ.PreparedSql ->
|
|
|
|
RequestId ->
|
|
|
|
QueryLog
|
2021-03-13 17:40:50 +03:00
|
|
|
mkQueryLog gqlQuery fieldName preparedSql requestId =
|
2021-04-28 20:38:05 +03:00
|
|
|
QueryLog gqlQuery ((fieldName,) <$> generatedQuery) requestId QueryLogKindDatabase
|
2021-03-13 17:40:50 +03:00
|
|
|
where
|
2021-09-24 01:56:37 +03:00
|
|
|
generatedQuery =
|
|
|
|
preparedSql <&> \(EQ.PreparedSql query args) ->
|
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
|
|
|
GeneratedQuery (PG.getQueryText query) (J.toJSON $ pgScalarValueToJson . snd <$> args)
|
2021-04-01 23:40:31 +03:00
|
|
|
|
|
|
|
-- ad-hoc transaction optimisation
|
|
|
|
-- see Note [Backwards-compatible transaction optimisation]
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
runPGMutationTransaction ::
|
|
|
|
( MonadIO m,
|
|
|
|
MonadError QErr m,
|
|
|
|
MonadQueryLog m,
|
|
|
|
MonadTrace m
|
|
|
|
) =>
|
|
|
|
RequestId ->
|
|
|
|
GQLReqUnparsed ->
|
|
|
|
UserInfo ->
|
|
|
|
L.Logger L.Hasura ->
|
|
|
|
SourceConfig ('Postgres pgKind) ->
|
2021-10-29 17:42:07 +03:00
|
|
|
RootFieldMap (DBStepInfo ('Postgres pgKind)) ->
|
|
|
|
m (DiffTime, RootFieldMap EncJSON)
|
2021-04-01 23:40:31 +03:00
|
|
|
runPGMutationTransaction reqId query userInfo logger sourceConfig mutations = do
|
2022-06-23 12:14:24 +03:00
|
|
|
logQueryLog logger $ mkQueryLog query (mkUnNamespacedRootFieldAlias Name._transaction) Nothing reqId
|
2021-04-01 23:40:31 +03:00
|
|
|
ctx <- Tracing.currentContext
|
|
|
|
withElapsedTime $ do
|
2021-09-24 01:56:37 +03:00
|
|
|
Tracing.interpTraceT
|
|
|
|
( liftEitherM . liftIO . runExceptT
|
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
|
|
|
. runTx (_pscExecCtx sourceConfig) PG.ReadWrite
|
2021-09-24 01:56:37 +03:00
|
|
|
. withTraceContext ctx
|
|
|
|
. withUserInfo userInfo
|
|
|
|
)
|
|
|
|
$ flip OMap.traverseWithKey mutations \fieldName dbsi ->
|
|
|
|
trace ("Postgres Mutation for root field " <>> fieldName) $ dbsiAction dbsi
|