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 Execute
|
|
|
|
--
|
|
|
|
-- This module implements the needed functionality for implementing a 'BackendExecute'
|
|
|
|
-- instance for Postgres, which defines an interface for translating a root field into
|
|
|
|
-- an execution plan and interacting with a database.
|
|
|
|
--
|
|
|
|
-- This module includes the Postgres implementation of queries, mutations, and more.
|
2021-05-21 05:46:58 +03:00
|
|
|
module Hasura.Backends.Postgres.Instances.Execute
|
2021-09-24 01:56:37 +03:00
|
|
|
( PreparedSql (..),
|
|
|
|
)
|
|
|
|
where
|
|
|
|
|
|
|
|
import Control.Monad.Trans.Control qualified as MT
|
|
|
|
import Data.Aeson qualified as J
|
2022-07-19 04:51:42 +03:00
|
|
|
import Data.Environment qualified as Env
|
2021-09-24 01:56:37 +03:00
|
|
|
import Data.HashMap.Strict qualified as Map
|
2021-10-29 17:42:07 +03:00
|
|
|
import Data.HashMap.Strict.InsOrd qualified as OMap
|
2021-09-24 01:56:37 +03:00
|
|
|
import Data.IntMap qualified as IntMap
|
|
|
|
import Data.Sequence qualified as Seq
|
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
|
2021-09-24 01:56:37 +03:00
|
|
|
import Hasura.Backends.Postgres.Execute.Insert (convertToSQLTransaction)
|
|
|
|
import Hasura.Backends.Postgres.Execute.Mutation qualified as PGE
|
|
|
|
import Hasura.Backends.Postgres.Execute.Prepare
|
|
|
|
( PlanningSt (..),
|
|
|
|
PrepArgMap,
|
|
|
|
initPlanningSt,
|
|
|
|
prepareWithPlan,
|
|
|
|
prepareWithoutPlan,
|
|
|
|
withUserVars,
|
|
|
|
)
|
2022-04-07 17:41:43 +03:00
|
|
|
import Hasura.Backends.Postgres.Execute.Subscription qualified as PGL
|
2022-04-27 18:36:02 +03:00
|
|
|
import Hasura.Backends.Postgres.Execute.Types (PGSourceConfig (..), dmlTxErrorHandler)
|
2021-09-24 01:56:37 +03:00
|
|
|
import Hasura.Backends.Postgres.SQL.DML qualified as S
|
2022-09-21 14:34:39 +03:00
|
|
|
import Hasura.Backends.Postgres.SQL.Types qualified as Postgres
|
|
|
|
import Hasura.Backends.Postgres.SQL.Value qualified as Postgres
|
2021-09-24 01:56:37 +03:00
|
|
|
import Hasura.Backends.Postgres.Translate.Select (PostgresAnnotatedFieldJSON)
|
|
|
|
import Hasura.Backends.Postgres.Translate.Select qualified as DS
|
2022-09-21 14:34:39 +03:00
|
|
|
import Hasura.Backends.Postgres.Types.Function qualified as Postgres
|
2022-07-18 18:15:34 +03:00
|
|
|
import Hasura.Backends.Postgres.Types.Update qualified as BackendUpdate
|
2021-09-24 01:56:37 +03:00
|
|
|
import Hasura.Base.Error (QErr)
|
2022-09-05 18:03:18 +03:00
|
|
|
import Hasura.EncJSON (EncJSON, encJFromJValue)
|
2021-09-24 01:56:37 +03:00
|
|
|
import Hasura.GraphQL.Execute.Backend
|
|
|
|
( BackendExecute (..),
|
|
|
|
DBStepInfo (..),
|
|
|
|
ExplainPlan (..),
|
|
|
|
convertRemoteSourceRelationship,
|
|
|
|
)
|
2022-03-21 13:39:49 +03:00
|
|
|
import Hasura.GraphQL.Execute.Subscription.Plan
|
|
|
|
( ParameterizedSubscriptionQueryPlan (..),
|
|
|
|
SubscriptionQueryPlan (..),
|
|
|
|
SubscriptionQueryPlanExplanation (..),
|
2021-09-24 01:56:37 +03:00
|
|
|
mkCohortVariables,
|
|
|
|
newCohortId,
|
|
|
|
)
|
2021-10-29 17:42:07 +03:00
|
|
|
import Hasura.GraphQL.Namespace
|
|
|
|
( RootFieldAlias (..),
|
|
|
|
RootFieldMap,
|
|
|
|
)
|
2022-04-22 22:53:12 +03:00
|
|
|
import Hasura.GraphQL.Namespace qualified as G
|
2022-07-14 20:57:28 +03:00
|
|
|
import Hasura.GraphQL.Schema.Options qualified as Options
|
2021-09-24 01:56:37 +03:00
|
|
|
import Hasura.Prelude
|
|
|
|
import Hasura.QueryTags
|
|
|
|
( QueryTagsComment (..),
|
|
|
|
emptyQueryTagsComment,
|
|
|
|
)
|
2022-05-31 01:07:02 +03:00
|
|
|
import Hasura.RQL.IR
|
2021-09-24 01:56:37 +03:00
|
|
|
import Hasura.RQL.IR.Delete qualified as IR
|
|
|
|
import Hasura.RQL.IR.Insert qualified as IR
|
|
|
|
import Hasura.RQL.IR.Returning qualified as IR
|
|
|
|
import Hasura.RQL.IR.Select qualified as IR
|
|
|
|
import Hasura.RQL.IR.Update qualified as IR
|
2022-04-27 16:57:28 +03:00
|
|
|
import Hasura.RQL.Types.Backend
|
2022-04-07 17:41:43 +03:00
|
|
|
import Hasura.RQL.Types.Column
|
2022-04-22 22:53:12 +03:00
|
|
|
( ColumnType (..),
|
2022-04-07 17:41:43 +03:00
|
|
|
ColumnValue (..),
|
2022-04-27 16:57:28 +03:00
|
|
|
ciName,
|
2022-04-07 17:41:43 +03:00
|
|
|
)
|
2022-04-22 22:53:12 +03:00
|
|
|
import Hasura.RQL.Types.Common
|
|
|
|
( FieldName (..),
|
|
|
|
JsonAggSelect (..),
|
|
|
|
SourceName,
|
|
|
|
)
|
2022-05-25 13:24:41 +03:00
|
|
|
import Hasura.RQL.Types.Function
|
2021-09-24 01:56:37 +03:00
|
|
|
import Hasura.SQL.AnyBackend qualified as AB
|
2022-04-27 16:57:28 +03:00
|
|
|
import Hasura.SQL.Backend
|
2021-09-24 01:56:37 +03:00
|
|
|
import Hasura.Session (UserInfo (..))
|
|
|
|
import Hasura.Tracing qualified as Tracing
|
|
|
|
import Language.GraphQL.Draft.Syntax qualified as G
|
|
|
|
|
|
|
|
data PreparedSql = PreparedSql
|
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
|
|
|
{ _psQuery :: PG.Query,
|
2022-07-29 17:05:03 +03:00
|
|
|
_psPrepArgs :: PrepArgMap
|
2021-06-11 06:26:50 +03:00
|
|
|
}
|
|
|
|
|
2021-05-21 05:46:58 +03:00
|
|
|
instance
|
2021-09-24 01:56:37 +03:00
|
|
|
( Backend ('Postgres pgKind),
|
|
|
|
PostgresAnnotatedFieldJSON pgKind
|
|
|
|
) =>
|
|
|
|
BackendExecute ('Postgres pgKind)
|
|
|
|
where
|
|
|
|
type PreparedQuery ('Postgres pgKind) = PreparedSql
|
2021-04-22 00:44:37 +03:00
|
|
|
type MultiplexedQuery ('Postgres pgKind) = PGL.MultiplexedQuery
|
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
|
|
|
type ExecutionMonad ('Postgres pgKind) = Tracing.TraceT (PG.TxET QErr IO)
|
2021-02-12 06:04:09 +03:00
|
|
|
|
|
|
|
mkDBQueryPlan = pgDBQueryPlan
|
|
|
|
mkDBMutationPlan = pgDBMutationPlan
|
2022-04-07 17:41:43 +03:00
|
|
|
mkLiveQuerySubscriptionPlan = pgDBLiveQuerySubscriptionPlan
|
|
|
|
mkDBStreamingSubscriptionPlan = pgDBStreamingSubscriptionPlan
|
2021-04-13 14:10:08 +03:00
|
|
|
mkDBQueryExplain = pgDBQueryExplain
|
2022-03-21 13:39:49 +03:00
|
|
|
mkSubscriptionExplain = pgDBSubscriptionExplain
|
2021-09-22 13:43:05 +03:00
|
|
|
mkDBRemoteRelationshipPlan = pgDBRemoteRelationshipPlan
|
2021-02-12 06:04:09 +03:00
|
|
|
|
|
|
|
-- query
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
pgDBQueryPlan ::
|
|
|
|
forall pgKind m.
|
|
|
|
( MonadError QErr m,
|
|
|
|
Backend ('Postgres pgKind),
|
|
|
|
PostgresAnnotatedFieldJSON pgKind,
|
|
|
|
MonadReader QueryTagsComment m
|
|
|
|
) =>
|
|
|
|
UserInfo ->
|
2022-07-19 04:51:42 +03:00
|
|
|
Env.Environment ->
|
2021-09-24 01:56:37 +03:00
|
|
|
SourceName ->
|
|
|
|
SourceConfig ('Postgres pgKind) ->
|
2021-12-07 16:12:02 +03:00
|
|
|
QueryDB ('Postgres pgKind) Void (UnpreparedValue ('Postgres pgKind)) ->
|
2021-09-24 01:56:37 +03:00
|
|
|
m (DBStepInfo ('Postgres pgKind))
|
2022-07-19 04:51:42 +03:00
|
|
|
pgDBQueryPlan userInfo _env sourceName sourceConfig qrf = do
|
2021-07-31 00:41:52 +03:00
|
|
|
(preparedQuery, PlanningSt _ _ planVals) <-
|
|
|
|
flip runStateT initPlanningSt $ traverse (prepareWithPlan userInfo) qrf
|
2021-09-23 15:37:56 +03:00
|
|
|
queryTagsComment <- ask
|
|
|
|
let preparedSQLWithQueryTags = appendPreparedSQLWithQueryTags (irToRootFieldPlan planVals preparedQuery) queryTagsComment
|
2021-07-29 11:29:12 +03:00
|
|
|
let (action, preparedSQL) = mkCurPlanTx userInfo preparedSQLWithQueryTags
|
2021-06-11 06:26:50 +03:00
|
|
|
pure $ DBStepInfo @('Postgres pgKind) sourceName sourceConfig preparedSQL action
|
2021-02-12 06:04:09 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
pgDBQueryExplain ::
|
|
|
|
forall pgKind m.
|
|
|
|
( MonadError QErr m,
|
|
|
|
Backend ('Postgres pgKind),
|
|
|
|
PostgresAnnotatedFieldJSON pgKind
|
|
|
|
) =>
|
2021-10-29 17:42:07 +03:00
|
|
|
RootFieldAlias ->
|
2021-09-24 01:56:37 +03:00
|
|
|
UserInfo ->
|
|
|
|
SourceName ->
|
|
|
|
SourceConfig ('Postgres pgKind) ->
|
2021-12-07 16:12:02 +03:00
|
|
|
QueryDB ('Postgres pgKind) Void (UnpreparedValue ('Postgres pgKind)) ->
|
2021-09-24 01:56:37 +03:00
|
|
|
m (AB.AnyBackend DBStepInfo)
|
2021-09-22 13:43:05 +03:00
|
|
|
pgDBQueryExplain fieldName userInfo sourceName sourceConfig rootSelection = do
|
2022-06-15 21:15:51 +03:00
|
|
|
preparedQuery <- traverse (prepareWithoutPlan userInfo) rootSelection
|
2021-06-11 06:26:50 +03:00
|
|
|
let PreparedSql querySQL _ = irToRootFieldPlan mempty preparedQuery
|
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
|
|
|
textSQL = PG.getQueryText querySQL
|
2021-04-13 14:10:08 +03:00
|
|
|
-- CAREFUL!: an `EXPLAIN ANALYZE` here would actually *execute* this
|
|
|
|
-- query, maybe resulting in privilege escalation:
|
2022-10-18 19:47:41 +03:00
|
|
|
withExplain = "EXPLAIN " <> textSQL
|
2021-09-24 01:56:37 +03:00
|
|
|
let action =
|
|
|
|
liftTx $
|
2022-10-07 14:55:42 +03:00
|
|
|
PG.withQE dmlTxErrorHandler (PG.fromText withExplain) () True <&> \planList ->
|
2021-09-24 01:56:37 +03:00
|
|
|
encJFromJValue $ ExplainPlan fieldName (Just textSQL) (Just $ map runIdentity planList)
|
|
|
|
pure $
|
|
|
|
AB.mkAnyBackend $
|
|
|
|
DBStepInfo @('Postgres pgKind) sourceName sourceConfig Nothing action
|
|
|
|
|
2022-03-21 13:39:49 +03:00
|
|
|
pgDBSubscriptionExplain ::
|
2021-09-24 01:56:37 +03:00
|
|
|
( MonadError QErr m,
|
|
|
|
MonadIO m,
|
|
|
|
MT.MonadBaseControl IO m
|
|
|
|
) =>
|
2022-03-21 13:39:49 +03:00
|
|
|
SubscriptionQueryPlan ('Postgres pgKind) (MultiplexedQuery ('Postgres pgKind)) ->
|
|
|
|
m SubscriptionQueryPlanExplanation
|
|
|
|
pgDBSubscriptionExplain plan = do
|
|
|
|
let parameterizedPlan = _sqpParameterizedPlan plan
|
|
|
|
pgExecCtx = _pscExecCtx $ _sqpSourceConfig plan
|
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
|
|
|
queryText = PG.getQueryText . PGL.unMultiplexedQuery $ _plqpQuery parameterizedPlan
|
2021-04-13 14:10:08 +03:00
|
|
|
-- CAREFUL!: an `EXPLAIN ANALYZE` here would actually *execute* this
|
|
|
|
-- query, maybe resulting in privilege escalation:
|
2022-10-18 19:47:41 +03:00
|
|
|
explainQuery = PG.fromText $ "EXPLAIN " <> queryText
|
2021-04-13 14:10:08 +03:00
|
|
|
cohortId <- newCohortId
|
2021-09-24 01:56:37 +03:00
|
|
|
explanationLines <-
|
|
|
|
liftEitherM $
|
|
|
|
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 pgExecCtx PG.ReadOnly $
|
2022-03-21 13:39:49 +03:00
|
|
|
map runIdentity <$> PGL.executeQuery explainQuery [(cohortId, _sqpVariables plan)]
|
|
|
|
pure $ SubscriptionQueryPlanExplanation queryText explanationLines $ _sqpVariables plan
|
2021-02-12 06:04:09 +03:00
|
|
|
|
|
|
|
-- mutation
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
convertDelete ::
|
|
|
|
forall pgKind m.
|
|
|
|
( MonadError QErr m,
|
|
|
|
Backend ('Postgres pgKind),
|
2022-04-28 22:33:33 +03:00
|
|
|
PostgresAnnotatedFieldJSON pgKind,
|
|
|
|
MonadReader QueryTagsComment m
|
2021-09-24 01:56:37 +03:00
|
|
|
) =>
|
|
|
|
UserInfo ->
|
2021-12-07 16:12:02 +03:00
|
|
|
IR.AnnDelG ('Postgres pgKind) Void (UnpreparedValue ('Postgres pgKind)) ->
|
2022-07-14 20:57:28 +03:00
|
|
|
Options.StringifyNumbers ->
|
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
|
|
|
m (Tracing.TraceT (PG.TxET QErr IO) EncJSON)
|
2022-04-28 22:33:33 +03:00
|
|
|
convertDelete userInfo deleteOperation stringifyNum = do
|
|
|
|
queryTags <- ask
|
2021-07-31 00:41:52 +03:00
|
|
|
preparedDelete <- traverse (prepareWithoutPlan userInfo) deleteOperation
|
2022-07-19 09:55:42 +03:00
|
|
|
pure $ flip runReaderT queryTags $ PGE.execDeleteQuery stringifyNum (_adNamingConvention deleteOperation) userInfo (preparedDelete, Seq.empty)
|
2021-02-12 06:04:09 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
convertUpdate ::
|
|
|
|
forall pgKind m.
|
|
|
|
( MonadError QErr m,
|
|
|
|
Backend ('Postgres pgKind),
|
2022-04-28 22:33:33 +03:00
|
|
|
PostgresAnnotatedFieldJSON pgKind,
|
|
|
|
MonadReader QueryTagsComment m
|
2021-09-24 01:56:37 +03:00
|
|
|
) =>
|
|
|
|
UserInfo ->
|
2021-12-07 16:12:02 +03:00
|
|
|
IR.AnnotatedUpdateG ('Postgres pgKind) Void (UnpreparedValue ('Postgres pgKind)) ->
|
2022-07-14 20:57:28 +03:00
|
|
|
Options.StringifyNumbers ->
|
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
|
|
|
m (Tracing.TraceT (PG.TxET QErr IO) EncJSON)
|
2022-04-28 22:33:33 +03:00
|
|
|
convertUpdate userInfo updateOperation stringifyNum = do
|
|
|
|
queryTags <- ask
|
2021-07-31 00:41:52 +03:00
|
|
|
preparedUpdate <- traverse (prepareWithoutPlan userInfo) updateOperation
|
2022-07-18 18:15:34 +03:00
|
|
|
if BackendUpdate.isEmpty $ IR._auBackend updateOperation
|
2021-11-25 00:39:42 +03:00
|
|
|
then pure $ pure $ IR.buildEmptyMutResp $ IR._auOutput preparedUpdate
|
2021-09-24 01:56:37 +03:00
|
|
|
else
|
|
|
|
pure $
|
|
|
|
flip runReaderT queryTags $
|
2022-07-19 09:55:42 +03:00
|
|
|
PGE.execUpdateQuery stringifyNum (_auNamingConvention updateOperation) userInfo (preparedUpdate, Seq.empty)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
|
|
|
convertInsert ::
|
|
|
|
forall pgKind m.
|
|
|
|
( MonadError QErr m,
|
|
|
|
Backend ('Postgres pgKind),
|
2022-04-28 22:33:33 +03:00
|
|
|
PostgresAnnotatedFieldJSON pgKind,
|
|
|
|
MonadReader QueryTagsComment m
|
2021-09-24 01:56:37 +03:00
|
|
|
) =>
|
|
|
|
UserInfo ->
|
2022-04-01 09:43:05 +03:00
|
|
|
IR.AnnotatedInsert ('Postgres pgKind) Void (UnpreparedValue ('Postgres pgKind)) ->
|
2022-07-14 20:57:28 +03:00
|
|
|
Options.StringifyNumbers ->
|
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
|
|
|
m (Tracing.TraceT (PG.TxET QErr IO) EncJSON)
|
2022-04-28 22:33:33 +03:00
|
|
|
convertInsert userInfo insertOperation stringifyNum = do
|
|
|
|
queryTags <- ask
|
2021-07-31 00:41:52 +03:00
|
|
|
preparedInsert <- traverse (prepareWithoutPlan userInfo) insertOperation
|
2022-07-19 09:55:42 +03:00
|
|
|
pure $ flip runReaderT queryTags $ convertToSQLTransaction preparedInsert userInfo Seq.empty stringifyNum (_aiNamingConvention insertOperation)
|
2021-02-12 06:04:09 +03:00
|
|
|
|
|
|
|
-- | A pared-down version of 'Query.convertQuerySelSet', for use in execution of
|
|
|
|
-- special case of SQL function mutations (see 'MDBFunction').
|
2021-09-24 01:56:37 +03:00
|
|
|
convertFunction ::
|
|
|
|
forall pgKind m.
|
|
|
|
( MonadError QErr m,
|
|
|
|
Backend ('Postgres pgKind),
|
2022-04-28 22:33:33 +03:00
|
|
|
PostgresAnnotatedFieldJSON pgKind,
|
|
|
|
MonadReader QueryTagsComment m
|
2021-09-24 01:56:37 +03:00
|
|
|
) =>
|
|
|
|
UserInfo ->
|
|
|
|
JsonAggSelect ->
|
|
|
|
-- | VOLATILE function as 'SelectExp'
|
2021-12-07 16:12:02 +03:00
|
|
|
IR.AnnSimpleSelectG ('Postgres pgKind) Void (UnpreparedValue ('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
|
|
|
m (Tracing.TraceT (PG.TxET QErr IO) EncJSON)
|
2022-04-28 22:33:33 +03:00
|
|
|
convertFunction userInfo jsonAggSelect unpreparedQuery = do
|
|
|
|
queryTags <- ask
|
2021-02-12 06:04:09 +03:00
|
|
|
-- Transform the RQL AST into a prepared SQL query
|
2021-09-24 01:56:37 +03:00
|
|
|
(preparedQuery, PlanningSt _ _ planVals) <-
|
|
|
|
flip runStateT initPlanningSt $
|
|
|
|
traverse (prepareWithPlan userInfo) unpreparedQuery
|
2021-02-12 06:04:09 +03:00
|
|
|
let queryResultFn =
|
|
|
|
case jsonAggSelect of
|
|
|
|
JASMultipleRows -> QDBMultipleRows
|
|
|
|
JASSingleObject -> QDBSingleRow
|
2021-07-29 11:29:12 +03:00
|
|
|
let preparedSQLWithQueryTags = appendPreparedSQLWithQueryTags (irToRootFieldPlan planVals $ queryResultFn preparedQuery) queryTags
|
2022-11-02 23:53:23 +03:00
|
|
|
pure $!
|
|
|
|
fst $
|
|
|
|
mkCurPlanTx userInfo preparedSQLWithQueryTags -- forget (Maybe PreparedSql)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
|
|
|
pgDBMutationPlan ::
|
|
|
|
forall pgKind m.
|
|
|
|
( MonadError QErr m,
|
|
|
|
Backend ('Postgres pgKind),
|
|
|
|
PostgresAnnotatedFieldJSON pgKind,
|
|
|
|
MonadReader QueryTagsComment m
|
|
|
|
) =>
|
|
|
|
UserInfo ->
|
2022-07-14 20:57:28 +03:00
|
|
|
Options.StringifyNumbers ->
|
2021-09-24 01:56:37 +03:00
|
|
|
SourceName ->
|
|
|
|
SourceConfig ('Postgres pgKind) ->
|
2021-12-07 16:12:02 +03:00
|
|
|
MutationDB ('Postgres pgKind) Void (UnpreparedValue ('Postgres pgKind)) ->
|
2021-09-24 01:56:37 +03:00
|
|
|
m (DBStepInfo ('Postgres pgKind))
|
2021-09-23 15:37:56 +03:00
|
|
|
pgDBMutationPlan userInfo stringifyNum sourceName sourceConfig mrf = do
|
2021-09-24 01:56:37 +03:00
|
|
|
go <$> case mrf of
|
2022-04-28 22:33:33 +03:00
|
|
|
MDBInsert s -> convertInsert userInfo s stringifyNum
|
|
|
|
MDBUpdate s -> convertUpdate userInfo s stringifyNum
|
|
|
|
MDBDelete s -> convertDelete userInfo s stringifyNum
|
|
|
|
MDBFunction returnsSet s -> convertFunction userInfo returnsSet s
|
2021-02-12 06:04:09 +03:00
|
|
|
where
|
2021-06-11 06:26:50 +03:00
|
|
|
go v = DBStepInfo @('Postgres pgKind) sourceName sourceConfig Nothing v
|
2021-04-01 23:40:31 +03:00
|
|
|
|
2021-02-23 20:37:27 +03:00
|
|
|
-- subscription
|
2021-02-20 16:45:49 +03:00
|
|
|
|
2022-04-07 17:41:43 +03:00
|
|
|
pgDBLiveQuerySubscriptionPlan ::
|
2021-09-24 01:56:37 +03:00
|
|
|
forall pgKind m.
|
|
|
|
( MonadError QErr m,
|
|
|
|
MonadIO m,
|
|
|
|
Backend ('Postgres pgKind),
|
|
|
|
PostgresAnnotatedFieldJSON pgKind,
|
|
|
|
MonadReader QueryTagsComment m
|
|
|
|
) =>
|
|
|
|
UserInfo ->
|
|
|
|
SourceName ->
|
|
|
|
SourceConfig ('Postgres pgKind) ->
|
2021-10-29 17:42:07 +03:00
|
|
|
Maybe G.Name ->
|
2021-12-07 16:12:02 +03:00
|
|
|
RootFieldMap (QueryDB ('Postgres pgKind) Void (UnpreparedValue ('Postgres pgKind))) ->
|
2022-03-21 13:39:49 +03:00
|
|
|
m (SubscriptionQueryPlan ('Postgres pgKind) (MultiplexedQuery ('Postgres pgKind)))
|
2022-04-07 17:41:43 +03:00
|
|
|
pgDBLiveQuerySubscriptionPlan userInfo _sourceName sourceConfig namespace unpreparedAST = do
|
2021-09-24 01:56:37 +03:00
|
|
|
(preparedAST, PGL.QueryParametersInfo {..}) <-
|
|
|
|
flip runStateT mempty $
|
2022-11-02 23:53:23 +03:00
|
|
|
for unpreparedAST $
|
|
|
|
traverse (PGL.resolveMultiplexedValue (_uiSession userInfo))
|
2022-04-07 17:41:43 +03:00
|
|
|
subscriptionQueryTagsComment <- ask
|
2021-10-29 17:42:07 +03:00
|
|
|
let multiplexedQuery = PGL.mkMultiplexedQuery $ OMap.mapKeys _rfaAlias preparedAST
|
2021-09-23 15:37:56 +03:00
|
|
|
multiplexedQueryWithQueryTags =
|
2022-04-07 17:41:43 +03:00
|
|
|
multiplexedQuery {PGL.unMultiplexedQuery = appendSQLWithQueryTags (PGL.unMultiplexedQuery multiplexedQuery) subscriptionQueryTagsComment}
|
2021-02-20 16:45:49 +03:00
|
|
|
roleName = _uiRole userInfo
|
2022-03-21 13:39:49 +03:00
|
|
|
parameterizedPlan = ParameterizedSubscriptionQueryPlan roleName multiplexedQueryWithQueryTags
|
2021-02-20 16:45:49 +03:00
|
|
|
|
|
|
|
-- We need to ensure that the values provided for variables are correct according to Postgres.
|
|
|
|
-- Without this check an invalid value for a variable for one instance of the subscription will
|
|
|
|
-- take down the entire multiplexed query.
|
2021-09-24 01:56:37 +03:00
|
|
|
validatedQueryVars <- PGL.validateVariables (_pscExecCtx sourceConfig) _qpiReusableVariableValues
|
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
|
|
|
validatedSyntheticVars <- PGL.validateVariables (_pscExecCtx sourceConfig) $ toList _qpiSyntheticVariableValues
|
2021-02-20 16:45:49 +03:00
|
|
|
|
|
|
|
-- TODO validatedQueryVars validatedSyntheticVars
|
2021-09-24 01:56:37 +03:00
|
|
|
let cohortVariables =
|
|
|
|
mkCohortVariables
|
|
|
|
_qpiReferencedSessionVariables
|
|
|
|
(_uiSession userInfo)
|
|
|
|
validatedQueryVars
|
|
|
|
validatedSyntheticVars
|
2022-04-07 17:41:43 +03:00
|
|
|
mempty -- live query subscriptions don't use the streaming cursor variables
|
2022-03-21 13:39:49 +03:00
|
|
|
pure $ SubscriptionQueryPlan parameterizedPlan sourceConfig cohortVariables namespace
|
2021-04-22 00:44:37 +03:00
|
|
|
|
2022-04-07 17:41:43 +03:00
|
|
|
pgDBStreamingSubscriptionPlan ::
|
|
|
|
forall pgKind m.
|
|
|
|
( MonadError QErr m,
|
|
|
|
MonadIO m,
|
|
|
|
Backend ('Postgres pgKind),
|
|
|
|
PostgresAnnotatedFieldJSON pgKind,
|
|
|
|
MonadReader QueryTagsComment m
|
|
|
|
) =>
|
|
|
|
UserInfo ->
|
|
|
|
SourceName ->
|
|
|
|
SourceConfig ('Postgres pgKind) ->
|
|
|
|
(RootFieldAlias, (QueryDB ('Postgres pgKind) Void (UnpreparedValue ('Postgres pgKind)))) ->
|
|
|
|
m (SubscriptionQueryPlan ('Postgres pgKind) (MultiplexedQuery ('Postgres pgKind)))
|
|
|
|
pgDBStreamingSubscriptionPlan userInfo _sourceName sourceConfig (rootFieldAlias, unpreparedAST) = do
|
|
|
|
(preparedAST, PGL.QueryParametersInfo {..}) <-
|
|
|
|
flip runStateT mempty $
|
|
|
|
traverse (PGL.resolveMultiplexedValue (_uiSession userInfo)) unpreparedAST
|
|
|
|
subscriptionQueryTagsComment <- ask
|
2022-04-22 22:53:12 +03:00
|
|
|
let multiplexedQuery = PGL.mkStreamingMultiplexedQuery (G._rfaAlias rootFieldAlias, preparedAST)
|
2022-04-07 17:41:43 +03:00
|
|
|
multiplexedQueryWithQueryTags =
|
|
|
|
multiplexedQuery {PGL.unMultiplexedQuery = appendSQLWithQueryTags (PGL.unMultiplexedQuery multiplexedQuery) subscriptionQueryTagsComment}
|
|
|
|
roleName = _uiRole userInfo
|
|
|
|
parameterizedPlan = ParameterizedSubscriptionQueryPlan roleName multiplexedQueryWithQueryTags
|
|
|
|
|
|
|
|
-- We need to ensure that the values provided for variables are correct according to Postgres.
|
|
|
|
-- Without this check an invalid value for a variable for one instance of the subscription will
|
|
|
|
-- take down the entire multiplexed query.
|
|
|
|
validatedQueryVars <- PGL.validateVariables (_pscExecCtx sourceConfig) _qpiReusableVariableValues
|
|
|
|
validatedSyntheticVars <- PGL.validateVariables (_pscExecCtx sourceConfig) $ toList _qpiSyntheticVariableValues
|
|
|
|
validatedCursorVars <- PGL.validateVariables (_pscExecCtx sourceConfig) $ getCursorVars unpreparedAST
|
|
|
|
|
|
|
|
let cohortVariables =
|
|
|
|
mkCohortVariables
|
|
|
|
_qpiReferencedSessionVariables
|
|
|
|
(_uiSession userInfo)
|
|
|
|
validatedQueryVars
|
|
|
|
validatedSyntheticVars
|
|
|
|
validatedCursorVars
|
|
|
|
|
|
|
|
pure $ SubscriptionQueryPlan parameterizedPlan sourceConfig cohortVariables $ _rfaNamespace rootFieldAlias
|
|
|
|
where
|
|
|
|
getCursorVars qdb =
|
|
|
|
case qdb of
|
|
|
|
QDBStreamMultipleRows (IR.AnnSelectStreamG () _ _ _ args _) ->
|
|
|
|
let cursorArg = IR._ssaCursorArg args
|
|
|
|
colInfo = IR._sciColInfo cursorArg
|
|
|
|
in Map.singleton (ciName colInfo) (IR._sciInitialValue cursorArg)
|
|
|
|
_ -> mempty
|
|
|
|
|
2021-06-11 06:26:50 +03:00
|
|
|
-- turn the current plan into a transaction
|
2021-09-24 01:56:37 +03:00
|
|
|
mkCurPlanTx ::
|
|
|
|
UserInfo ->
|
|
|
|
PreparedSql ->
|
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, Maybe PreparedSql)
|
2021-06-11 06:26:50 +03:00
|
|
|
mkCurPlanTx userInfo ps@(PreparedSql q prepMap) =
|
|
|
|
-- generate the SQL and prepared vars or the bytestring
|
|
|
|
let args = withUserVars (_uiSession userInfo) prepMap
|
|
|
|
-- WARNING: this quietly assumes the intmap keys are contiguous
|
|
|
|
prepArgs = fst <$> IntMap.elems args
|
2021-09-24 01:56:37 +03:00
|
|
|
in (,Just ps) $
|
2022-11-02 23:53:23 +03:00
|
|
|
Tracing.trace "Postgres" $
|
|
|
|
liftTx $
|
|
|
|
asSingleRowJsonResp q prepArgs
|
2022-04-22 16:38:35 +03:00
|
|
|
|
|
|
|
-- | This function is generally used on the result of 'selectQuerySQL',
|
|
|
|
-- 'selectAggregateQuerySQL' or 'connectionSelectSQL' to run said query and get
|
|
|
|
-- back the resulting JSON.
|
|
|
|
asSingleRowJsonResp ::
|
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.Query ->
|
|
|
|
[PG.PrepArg] ->
|
|
|
|
PG.TxE QErr EncJSON
|
2022-04-22 16:38:35 +03:00
|
|
|
asSingleRowJsonResp 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
|
|
|
runIdentity . PG.getRow
|
|
|
|
<$> PG.rawQE dmlTxErrorHandler query args True
|
2021-06-11 06:26:50 +03:00
|
|
|
|
|
|
|
-- convert a query from an intermediate representation to... another
|
2021-09-24 01:56:37 +03:00
|
|
|
irToRootFieldPlan ::
|
|
|
|
( Backend ('Postgres pgKind),
|
|
|
|
DS.PostgresAnnotatedFieldJSON pgKind
|
|
|
|
) =>
|
|
|
|
PrepArgMap ->
|
2021-12-07 16:12:02 +03:00
|
|
|
QueryDB ('Postgres pgKind) Void S.SQLExp ->
|
2021-09-24 01:56:37 +03:00
|
|
|
PreparedSql
|
2021-06-11 06:26:50 +03:00
|
|
|
irToRootFieldPlan prepped = \case
|
|
|
|
QDBMultipleRows s -> mkPreparedSql (DS.selectQuerySQL JASMultipleRows) s
|
2021-09-24 01:56:37 +03:00
|
|
|
QDBSingleRow s -> mkPreparedSql (DS.selectQuerySQL JASSingleObject) s
|
|
|
|
QDBAggregation s -> mkPreparedSql DS.selectAggregateQuerySQL s
|
|
|
|
QDBConnection s -> mkPreparedSql DS.connectionSelectQuerySQL s
|
2022-04-07 17:41:43 +03:00
|
|
|
QDBStreamMultipleRows s -> mkPreparedSql DS.selectStreamQuerySQL s
|
2021-06-11 06:26:50 +03:00
|
|
|
where
|
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
|
|
|
mkPreparedSql :: (t -> PG.Query) -> t -> PreparedSql
|
2021-06-11 06:26:50 +03:00
|
|
|
mkPreparedSql f simpleSel =
|
|
|
|
PreparedSql (f simpleSel) prepped
|
2021-07-29 11:29:12 +03:00
|
|
|
|
|
|
|
-- Append Query Tags to the Prepared SQL
|
|
|
|
appendPreparedSQLWithQueryTags :: PreparedSql -> QueryTagsComment -> PreparedSql
|
|
|
|
appendPreparedSQLWithQueryTags preparedSQL queryTags =
|
|
|
|
preparedSQL {_psQuery = appendSQLWithQueryTags query queryTags}
|
|
|
|
where
|
|
|
|
query = _psQuery preparedSQL
|
|
|
|
|
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
|
|
|
appendSQLWithQueryTags :: PG.Query -> QueryTagsComment -> PG.Query
|
|
|
|
appendSQLWithQueryTags query queryTags = query {PG.getQueryText = queryText <> _unQueryTagsComment queryTags}
|
2021-07-29 11:29:12 +03:00
|
|
|
where
|
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
|
|
|
queryText = PG.getQueryText query
|
2021-09-22 13:43:05 +03:00
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- Remote Relationships (e.g. DB-to-DB Joins, remote schema joins, etc.)
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
|
|
|
|
-- | Construct an action (i.e. 'DBStepInfo') which can marshal some remote
|
|
|
|
-- relationship information into a form that Postgres can query against.
|
2021-09-24 01:56:37 +03:00
|
|
|
pgDBRemoteRelationshipPlan ::
|
|
|
|
forall pgKind m.
|
|
|
|
( MonadError QErr m,
|
|
|
|
Backend ('Postgres pgKind),
|
|
|
|
PostgresAnnotatedFieldJSON pgKind
|
|
|
|
) =>
|
|
|
|
UserInfo ->
|
|
|
|
SourceName ->
|
|
|
|
SourceConfig ('Postgres pgKind) ->
|
2021-09-22 13:43:05 +03:00
|
|
|
-- | List of json objects, each of which becomes a row of the table.
|
2021-09-24 01:56:37 +03:00
|
|
|
NonEmpty J.Object ->
|
2021-09-22 13:43:05 +03:00
|
|
|
-- | The above objects have this schema
|
|
|
|
--
|
|
|
|
-- XXX: What is this for/what does this mean?
|
2021-09-24 01:56:37 +03:00
|
|
|
HashMap FieldName (Column ('Postgres pgKind), ScalarType ('Postgres pgKind)) ->
|
2021-09-22 13:43:05 +03:00
|
|
|
-- | This is a field name from the lhs that *has* to be selected in the
|
|
|
|
-- response along with the relationship.
|
2021-09-24 01:56:37 +03:00
|
|
|
FieldName ->
|
2021-12-07 16:12:02 +03:00
|
|
|
(FieldName, IR.SourceRelationshipSelection ('Postgres pgKind) Void UnpreparedValue) ->
|
2021-09-24 01:56:37 +03:00
|
|
|
m (DBStepInfo ('Postgres pgKind))
|
2021-09-22 13:43:05 +03:00
|
|
|
pgDBRemoteRelationshipPlan userInfo sourceName sourceConfig lhs lhsSchema argumentId relationship = do
|
|
|
|
-- NOTE: 'QueryTags' currently cannot support remote relationship queries.
|
|
|
|
--
|
|
|
|
-- In the future if we want to add support we'll need to add a new type of
|
|
|
|
-- metadata (e.g. 'ParameterizedQueryHash' doesn't make sense here) and find
|
|
|
|
-- a root field name that makes sense to attach to it.
|
2022-07-19 04:51:42 +03:00
|
|
|
flip runReaderT emptyQueryTagsComment $ pgDBQueryPlan userInfo Env.emptyEnvironment sourceName sourceConfig rootSelection
|
2021-09-22 13:43:05 +03:00
|
|
|
where
|
2022-09-21 14:34:39 +03:00
|
|
|
coerceToColumn = Postgres.unsafePGCol . getFieldNameTxt
|
2021-09-22 13:43:05 +03:00
|
|
|
joinColumnMapping = mapKeys coerceToColumn lhsSchema
|
|
|
|
|
|
|
|
rowsArgument :: UnpreparedValue ('Postgres pgKind)
|
|
|
|
rowsArgument =
|
2021-09-24 01:56:37 +03:00
|
|
|
UVParameter Nothing $
|
2022-09-21 14:34:39 +03:00
|
|
|
ColumnValue (ColumnScalar Postgres.PGJSONB) $
|
2022-11-02 23:53:23 +03:00
|
|
|
Postgres.PGValJSONB $
|
|
|
|
PG.JSONB $
|
|
|
|
J.toJSON lhs
|
2021-09-22 13:43:05 +03:00
|
|
|
jsonToRecordSet :: IR.SelectFromG ('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
|
|
|
|
|
|
|
|
recordSetDefinitionList =
|
2022-09-21 14:34:39 +03:00
|
|
|
(coerceToColumn argumentId, Postgres.PGBigInt) : Map.toList (fmap snd joinColumnMapping)
|
2021-09-22 13:43:05 +03:00
|
|
|
jsonToRecordSet =
|
|
|
|
IR.FromFunction
|
2022-09-21 14:34:39 +03:00
|
|
|
(Postgres.QualifiedObject "pg_catalog" $ Postgres.FunctionName "jsonb_to_recordset")
|
|
|
|
(FunctionArgsExp [Postgres.AEInput rowsArgument] mempty)
|
2021-09-22 13:43:05 +03:00
|
|
|
(Just recordSetDefinitionList)
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
rootSelection =
|
|
|
|
convertRemoteSourceRelationship
|
|
|
|
(fst <$> joinColumnMapping)
|
|
|
|
jsonToRecordSet
|
2022-09-21 14:34:39 +03:00
|
|
|
(Postgres.unsafePGCol $ getFieldNameTxt argumentId)
|
|
|
|
(ColumnScalar Postgres.PGBigInt)
|
2021-09-24 01:56:37 +03:00
|
|
|
relationship
|