2021-04-22 00:44:37 +03:00
|
|
|
{-# LANGUAGE UndecidableInstances #-}
|
2021-02-12 06:04:09 +03:00
|
|
|
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
|
|
|
|
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
|
|
|
|
( runPGMutationTransaction,
|
|
|
|
)
|
|
|
|
where
|
2021-09-24 01:56:37 +03:00
|
|
|
|
Allow backend execution to happen on the base app monad.
### Description
Each Backend executes queries against the database in a slightly different stack: Postgres uses its own `TXeT`, MSSQL uses a variant of it, BigQuery is simply in `ExceptT QErr IO`... To accommodate those variations, we had originally introduced an `ExecutionMonad b` type family in `BackendExecute`, allowing each backend to describe its own stack. It was then up to that backend's `BackendTransport` instance to implement running said stack, and converting the result back into our main app monad.
However, this was not without complications: `TraceT` is one of them: as it usually needs to be on the top of the stack, converting from one stack to the other implies the use `interpTraceT`, which is quite monstrous. Furthermore, as part of the Entitlement Services work, we're trying to move to a "Services" architecture in which the entire engine runs in one base monad, that delegates features and dependencies to monad constraints; and as a result we'd like to minimize the number of different monad stacks we have to maintain and translate from and to in the codebase.
To improve things, this PR changes `ExecutionMonad b` from an _absolute_ stack to a _relative_ one: i.e.: what needs to be stacked on top of our base monad for the execution. In `Transport`, we then only need to pop the top of the stack, and voila. This greatly simplifies the implementation of the backends, as there's no longer any need to do any stack transformation: MySQL's implementation becomes a `runIdentityT`! This also removes most mentions of `TraceT` from the execution code since it's no longer required: we can rely on the base monad's existing `MonadTrace` constraint.
To continue encapsulating monadic actions in `DBStepInfo` and avoid threading a bunch of `forall` all over the place, this PR introduces a small local helper: `OnBaseMonad`. One only downside of all this is that this requires adding `MonadBaseControl IO m` constraint all over the place: previously, we would run directly on `IO` and lift, and would therefore not need to bring that constraint all the way.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7789
GitOrigin-RevId: e9b2e431c5c47fa9851abf87545c0415ff6d1a12
2023-02-09 17:38:33 +03:00
|
|
|
import Control.Monad.Trans.Control
|
2021-03-13 17:40:50 +03:00
|
|
|
import Data.Aeson qualified as J
|
2021-02-20 16:45:49 +03:00
|
|
|
import Data.ByteString qualified as B
|
2021-04-01 23:40:31 +03:00
|
|
|
import Data.HashMap.Strict.InsOrd qualified as OMap
|
2021-02-12 06:04:09 +03:00
|
|
|
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-06-11 06:26:50 +03:00
|
|
|
import Hasura.Backends.Postgres.Instances.Execute qualified as EQ
|
2021-03-13 17:40:50 +03:00
|
|
|
import Hasura.Backends.Postgres.SQL.Value
|
2021-05-21 05:46:58 +03:00
|
|
|
import Hasura.Backends.Postgres.Translate.Select (PostgresAnnotatedFieldJSON)
|
2021-05-11 18:18:31 +03:00
|
|
|
import Hasura.Base.Error
|
2021-02-12 06:04:09 +03:00
|
|
|
import Hasura.EncJSON
|
2021-02-20 16:45:49 +03:00
|
|
|
import Hasura.GraphQL.Execute.Backend
|
2022-03-21 13:39:49 +03:00
|
|
|
import Hasura.GraphQL.Execute.Subscription.Plan
|
2021-03-13 17:40:50 +03:00
|
|
|
import Hasura.GraphQL.Logging
|
2021-10-29 17:42:07 +03:00
|
|
|
import Hasura.GraphQL.Namespace
|
|
|
|
( RootFieldAlias,
|
|
|
|
RootFieldMap,
|
|
|
|
mkUnNamespacedRootFieldAlias,
|
|
|
|
)
|
2021-02-12 06:04:09 +03:00
|
|
|
import Hasura.GraphQL.Transport.Backend
|
|
|
|
import Hasura.GraphQL.Transport.HTTP.Protocol
|
2021-02-20 16:45:49 +03:00
|
|
|
import Hasura.Logging qualified as L
|
2022-06-23 12:14:24 +03:00
|
|
|
import Hasura.Name qualified as Name
|
2021-02-12 06:04:09 +03:00
|
|
|
import Hasura.Prelude
|
2023-01-25 10:12:53 +03:00
|
|
|
import Hasura.RQL.DDL.ConnectionTemplate (BackendResolvedConnectionTemplate (..), ResolvedConnectionTemplateWrapper (..))
|
2022-04-27 16:57:28 +03:00
|
|
|
import Hasura.RQL.Types.Backend
|
2023-01-25 10:12:53 +03:00
|
|
|
import Hasura.SQL.AnyBackend qualified as AB
|
2022-04-27 16:57:28 +03:00
|
|
|
import Hasura.SQL.Backend
|
2021-02-20 16:45:49 +03:00
|
|
|
import Hasura.Server.Types (RequestId)
|
2021-02-12 06:04:09 +03:00
|
|
|
import Hasura.Session
|
2021-02-20 16:45:49 +03:00
|
|
|
import Hasura.Tracing
|
2021-02-12 06:04:09 +03:00
|
|
|
|
2021-05-21 05:46:58 +03:00
|
|
|
instance
|
|
|
|
( 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
|
|
|
|
|
|
|
runPGQuery ::
|
|
|
|
( MonadIO m,
|
Allow backend execution to happen on the base app monad.
### Description
Each Backend executes queries against the database in a slightly different stack: Postgres uses its own `TXeT`, MSSQL uses a variant of it, BigQuery is simply in `ExceptT QErr IO`... To accommodate those variations, we had originally introduced an `ExecutionMonad b` type family in `BackendExecute`, allowing each backend to describe its own stack. It was then up to that backend's `BackendTransport` instance to implement running said stack, and converting the result back into our main app monad.
However, this was not without complications: `TraceT` is one of them: as it usually needs to be on the top of the stack, converting from one stack to the other implies the use `interpTraceT`, which is quite monstrous. Furthermore, as part of the Entitlement Services work, we're trying to move to a "Services" architecture in which the entire engine runs in one base monad, that delegates features and dependencies to monad constraints; and as a result we'd like to minimize the number of different monad stacks we have to maintain and translate from and to in the codebase.
To improve things, this PR changes `ExecutionMonad b` from an _absolute_ stack to a _relative_ one: i.e.: what needs to be stacked on top of our base monad for the execution. In `Transport`, we then only need to pop the top of the stack, and voila. This greatly simplifies the implementation of the backends, as there's no longer any need to do any stack transformation: MySQL's implementation becomes a `runIdentityT`! This also removes most mentions of `TraceT` from the execution code since it's no longer required: we can rely on the base monad's existing `MonadTrace` constraint.
To continue encapsulating monadic actions in `DBStepInfo` and avoid threading a bunch of `forall` all over the place, this PR introduces a small local helper: `OnBaseMonad`. One only downside of all this is that this requires adding `MonadBaseControl IO m` constraint all over the place: previously, we would run directly on `IO` and lift, and would therefore not need to bring that constraint all the way.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7789
GitOrigin-RevId: e9b2e431c5c47fa9851abf87545c0415ff6d1a12
2023-02-09 17:38:33 +03:00
|
|
|
MonadBaseControl IO m,
|
2021-02-12 06:04:09 +03:00
|
|
|
MonadError QErr m,
|
|
|
|
MonadQueryLog m,
|
|
|
|
MonadTrace m
|
|
|
|
) =>
|
|
|
|
RequestId ->
|
|
|
|
GQLReqUnparsed ->
|
2021-10-29 17:42:07 +03:00
|
|
|
RootFieldAlias ->
|
2021-02-12 06:04:09 +03:00
|
|
|
UserInfo ->
|
|
|
|
L.Logger L.Hasura ->
|
2021-04-22 00:44:37 +03:00
|
|
|
SourceConfig ('Postgres pgKind) ->
|
Allow backend execution to happen on the base app monad.
### Description
Each Backend executes queries against the database in a slightly different stack: Postgres uses its own `TXeT`, MSSQL uses a variant of it, BigQuery is simply in `ExceptT QErr IO`... To accommodate those variations, we had originally introduced an `ExecutionMonad b` type family in `BackendExecute`, allowing each backend to describe its own stack. It was then up to that backend's `BackendTransport` instance to implement running said stack, and converting the result back into our main app monad.
However, this was not without complications: `TraceT` is one of them: as it usually needs to be on the top of the stack, converting from one stack to the other implies the use `interpTraceT`, which is quite monstrous. Furthermore, as part of the Entitlement Services work, we're trying to move to a "Services" architecture in which the entire engine runs in one base monad, that delegates features and dependencies to monad constraints; and as a result we'd like to minimize the number of different monad stacks we have to maintain and translate from and to in the codebase.
To improve things, this PR changes `ExecutionMonad b` from an _absolute_ stack to a _relative_ one: i.e.: what needs to be stacked on top of our base monad for the execution. In `Transport`, we then only need to pop the top of the stack, and voila. This greatly simplifies the implementation of the backends, as there's no longer any need to do any stack transformation: MySQL's implementation becomes a `runIdentityT`! This also removes most mentions of `TraceT` from the execution code since it's no longer required: we can rely on the base monad's existing `MonadTrace` constraint.
To continue encapsulating monadic actions in `DBStepInfo` and avoid threading a bunch of `forall` all over the place, this PR introduces a small local helper: `OnBaseMonad`. One only downside of all this is that this requires adding `MonadBaseControl IO m` constraint all over the place: previously, we would run directly on `IO` and lift, and would therefore not need to bring that constraint all the way.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7789
GitOrigin-RevId: e9b2e431c5c47fa9851abf87545c0415ff6d1a12
2023-02-09 17:38:33 +03:00
|
|
|
OnBaseMonad (PG.TxET QErr) EncJSON ->
|
2021-06-11 06:26:50 +03:00
|
|
|
Maybe EQ.PreparedSql ->
|
2023-01-25 10:12:53 +03:00
|
|
|
ResolvedConnectionTemplate ('Postgres pgKind) ->
|
2021-02-12 06:04:09 +03:00
|
|
|
-- | Also return the time spent in the PG query; for telemetry.
|
|
|
|
m (DiffTime, EncJSON)
|
2023-01-25 10:12:53 +03:00
|
|
|
runPGQuery reqId query fieldName _userInfo logger sourceConfig tx genSql resolvedConnectionTemplate = do
|
2021-02-12 06:04:09 +03:00
|
|
|
-- log the generated SQL and the graphql query
|
2023-01-25 10:12:53 +03:00
|
|
|
logQueryLog logger $ mkQueryLog query fieldName genSql reqId (resolvedConnectionTemplate <$ resolvedConnectionTemplate)
|
2021-02-12 06:04:09 +03:00
|
|
|
withElapsedTime $
|
|
|
|
trace ("Postgres Query for root field " <>> fieldName) $
|
Allow backend execution to happen on the base app monad.
### Description
Each Backend executes queries against the database in a slightly different stack: Postgres uses its own `TXeT`, MSSQL uses a variant of it, BigQuery is simply in `ExceptT QErr IO`... To accommodate those variations, we had originally introduced an `ExecutionMonad b` type family in `BackendExecute`, allowing each backend to describe its own stack. It was then up to that backend's `BackendTransport` instance to implement running said stack, and converting the result back into our main app monad.
However, this was not without complications: `TraceT` is one of them: as it usually needs to be on the top of the stack, converting from one stack to the other implies the use `interpTraceT`, which is quite monstrous. Furthermore, as part of the Entitlement Services work, we're trying to move to a "Services" architecture in which the entire engine runs in one base monad, that delegates features and dependencies to monad constraints; and as a result we'd like to minimize the number of different monad stacks we have to maintain and translate from and to in the codebase.
To improve things, this PR changes `ExecutionMonad b` from an _absolute_ stack to a _relative_ one: i.e.: what needs to be stacked on top of our base monad for the execution. In `Transport`, we then only need to pop the top of the stack, and voila. This greatly simplifies the implementation of the backends, as there's no longer any need to do any stack transformation: MySQL's implementation becomes a `runIdentityT`! This also removes most mentions of `TraceT` from the execution code since it's no longer required: we can rely on the base monad's existing `MonadTrace` constraint.
To continue encapsulating monadic actions in `DBStepInfo` and avoid threading a bunch of `forall` all over the place, this PR introduces a small local helper: `OnBaseMonad`. One only downside of all this is that this requires adding `MonadBaseControl IO m` constraint all over the place: previously, we would run directly on `IO` and lift, and would therefore not need to bring that constraint all the way.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7789
GitOrigin-RevId: e9b2e431c5c47fa9851abf87545c0415ff6d1a12
2023-02-09 17:38:33 +03:00
|
|
|
runQueryTx (_pscExecCtx sourceConfig) (GraphQLQuery resolvedConnectionTemplate) $
|
|
|
|
runOnBaseMonad tx
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-02-12 06:04:09 +03:00
|
|
|
runPGMutation ::
|
|
|
|
( MonadIO m,
|
Allow backend execution to happen on the base app monad.
### Description
Each Backend executes queries against the database in a slightly different stack: Postgres uses its own `TXeT`, MSSQL uses a variant of it, BigQuery is simply in `ExceptT QErr IO`... To accommodate those variations, we had originally introduced an `ExecutionMonad b` type family in `BackendExecute`, allowing each backend to describe its own stack. It was then up to that backend's `BackendTransport` instance to implement running said stack, and converting the result back into our main app monad.
However, this was not without complications: `TraceT` is one of them: as it usually needs to be on the top of the stack, converting from one stack to the other implies the use `interpTraceT`, which is quite monstrous. Furthermore, as part of the Entitlement Services work, we're trying to move to a "Services" architecture in which the entire engine runs in one base monad, that delegates features and dependencies to monad constraints; and as a result we'd like to minimize the number of different monad stacks we have to maintain and translate from and to in the codebase.
To improve things, this PR changes `ExecutionMonad b` from an _absolute_ stack to a _relative_ one: i.e.: what needs to be stacked on top of our base monad for the execution. In `Transport`, we then only need to pop the top of the stack, and voila. This greatly simplifies the implementation of the backends, as there's no longer any need to do any stack transformation: MySQL's implementation becomes a `runIdentityT`! This also removes most mentions of `TraceT` from the execution code since it's no longer required: we can rely on the base monad's existing `MonadTrace` constraint.
To continue encapsulating monadic actions in `DBStepInfo` and avoid threading a bunch of `forall` all over the place, this PR introduces a small local helper: `OnBaseMonad`. One only downside of all this is that this requires adding `MonadBaseControl IO m` constraint all over the place: previously, we would run directly on `IO` and lift, and would therefore not need to bring that constraint all the way.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7789
GitOrigin-RevId: e9b2e431c5c47fa9851abf87545c0415ff6d1a12
2023-02-09 17:38:33 +03:00
|
|
|
MonadBaseControl IO m,
|
2021-02-12 06:04:09 +03:00
|
|
|
MonadError QErr m,
|
|
|
|
MonadQueryLog m,
|
|
|
|
MonadTrace m
|
|
|
|
) =>
|
|
|
|
RequestId ->
|
|
|
|
GQLReqUnparsed ->
|
2021-10-29 17:42:07 +03:00
|
|
|
RootFieldAlias ->
|
2021-02-12 06:04:09 +03:00
|
|
|
UserInfo ->
|
|
|
|
L.Logger L.Hasura ->
|
2021-04-22 00:44:37 +03:00
|
|
|
SourceConfig ('Postgres pgKind) ->
|
Allow backend execution to happen on the base app monad.
### Description
Each Backend executes queries against the database in a slightly different stack: Postgres uses its own `TXeT`, MSSQL uses a variant of it, BigQuery is simply in `ExceptT QErr IO`... To accommodate those variations, we had originally introduced an `ExecutionMonad b` type family in `BackendExecute`, allowing each backend to describe its own stack. It was then up to that backend's `BackendTransport` instance to implement running said stack, and converting the result back into our main app monad.
However, this was not without complications: `TraceT` is one of them: as it usually needs to be on the top of the stack, converting from one stack to the other implies the use `interpTraceT`, which is quite monstrous. Furthermore, as part of the Entitlement Services work, we're trying to move to a "Services" architecture in which the entire engine runs in one base monad, that delegates features and dependencies to monad constraints; and as a result we'd like to minimize the number of different monad stacks we have to maintain and translate from and to in the codebase.
To improve things, this PR changes `ExecutionMonad b` from an _absolute_ stack to a _relative_ one: i.e.: what needs to be stacked on top of our base monad for the execution. In `Transport`, we then only need to pop the top of the stack, and voila. This greatly simplifies the implementation of the backends, as there's no longer any need to do any stack transformation: MySQL's implementation becomes a `runIdentityT`! This also removes most mentions of `TraceT` from the execution code since it's no longer required: we can rely on the base monad's existing `MonadTrace` constraint.
To continue encapsulating monadic actions in `DBStepInfo` and avoid threading a bunch of `forall` all over the place, this PR introduces a small local helper: `OnBaseMonad`. One only downside of all this is that this requires adding `MonadBaseControl IO m` constraint all over the place: previously, we would run directly on `IO` and lift, and would therefore not need to bring that constraint all the way.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7789
GitOrigin-RevId: e9b2e431c5c47fa9851abf87545c0415ff6d1a12
2023-02-09 17:38:33 +03:00
|
|
|
OnBaseMonad (PG.TxET QErr) EncJSON ->
|
2021-06-11 06:26:50 +03:00
|
|
|
Maybe EQ.PreparedSql ->
|
2023-01-25 10:12:53 +03:00
|
|
|
ResolvedConnectionTemplate ('Postgres pgKind) ->
|
2021-02-12 06:04:09 +03:00
|
|
|
m (DiffTime, EncJSON)
|
2023-01-25 10:12:53 +03:00
|
|
|
runPGMutation reqId query fieldName userInfo logger sourceConfig tx _genSql resolvedConnectionTemplate = do
|
2021-02-12 06:04:09 +03:00
|
|
|
-- log the graphql query
|
2023-01-25 10:12:53 +03:00
|
|
|
logQueryLog logger $ mkQueryLog query fieldName Nothing reqId (resolvedConnectionTemplate <$ resolvedConnectionTemplate)
|
2021-02-12 06:04:09 +03:00
|
|
|
withElapsedTime $
|
|
|
|
trace ("Postgres Mutation for root field " <>> fieldName) $
|
Allow backend execution to happen on the base app monad.
### Description
Each Backend executes queries against the database in a slightly different stack: Postgres uses its own `TXeT`, MSSQL uses a variant of it, BigQuery is simply in `ExceptT QErr IO`... To accommodate those variations, we had originally introduced an `ExecutionMonad b` type family in `BackendExecute`, allowing each backend to describe its own stack. It was then up to that backend's `BackendTransport` instance to implement running said stack, and converting the result back into our main app monad.
However, this was not without complications: `TraceT` is one of them: as it usually needs to be on the top of the stack, converting from one stack to the other implies the use `interpTraceT`, which is quite monstrous. Furthermore, as part of the Entitlement Services work, we're trying to move to a "Services" architecture in which the entire engine runs in one base monad, that delegates features and dependencies to monad constraints; and as a result we'd like to minimize the number of different monad stacks we have to maintain and translate from and to in the codebase.
To improve things, this PR changes `ExecutionMonad b` from an _absolute_ stack to a _relative_ one: i.e.: what needs to be stacked on top of our base monad for the execution. In `Transport`, we then only need to pop the top of the stack, and voila. This greatly simplifies the implementation of the backends, as there's no longer any need to do any stack transformation: MySQL's implementation becomes a `runIdentityT`! This also removes most mentions of `TraceT` from the execution code since it's no longer required: we can rely on the base monad's existing `MonadTrace` constraint.
To continue encapsulating monadic actions in `DBStepInfo` and avoid threading a bunch of `forall` all over the place, this PR introduces a small local helper: `OnBaseMonad`. One only downside of all this is that this requires adding `MonadBaseControl IO m` constraint all over the place: previously, we would run directly on `IO` and lift, and would therefore not need to bring that constraint all the way.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7789
GitOrigin-RevId: e9b2e431c5c47fa9851abf87545c0415ff6d1a12
2023-02-09 17:38:33 +03:00
|
|
|
runTxWithCtxAndUserInfo userInfo (_pscExecCtx sourceConfig) (Tx PG.ReadWrite Nothing) (GraphQLQuery resolvedConnectionTemplate) $
|
|
|
|
runOnBaseMonad tx
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-02-20 16:45:49 +03:00
|
|
|
runPGSubscription ::
|
Allow backend execution to happen on the base app monad.
### Description
Each Backend executes queries against the database in a slightly different stack: Postgres uses its own `TXeT`, MSSQL uses a variant of it, BigQuery is simply in `ExceptT QErr IO`... To accommodate those variations, we had originally introduced an `ExecutionMonad b` type family in `BackendExecute`, allowing each backend to describe its own stack. It was then up to that backend's `BackendTransport` instance to implement running said stack, and converting the result back into our main app monad.
However, this was not without complications: `TraceT` is one of them: as it usually needs to be on the top of the stack, converting from one stack to the other implies the use `interpTraceT`, which is quite monstrous. Furthermore, as part of the Entitlement Services work, we're trying to move to a "Services" architecture in which the entire engine runs in one base monad, that delegates features and dependencies to monad constraints; and as a result we'd like to minimize the number of different monad stacks we have to maintain and translate from and to in the codebase.
To improve things, this PR changes `ExecutionMonad b` from an _absolute_ stack to a _relative_ one: i.e.: what needs to be stacked on top of our base monad for the execution. In `Transport`, we then only need to pop the top of the stack, and voila. This greatly simplifies the implementation of the backends, as there's no longer any need to do any stack transformation: MySQL's implementation becomes a `runIdentityT`! This also removes most mentions of `TraceT` from the execution code since it's no longer required: we can rely on the base monad's existing `MonadTrace` constraint.
To continue encapsulating monadic actions in `DBStepInfo` and avoid threading a bunch of `forall` all over the place, this PR introduces a small local helper: `OnBaseMonad`. One only downside of all this is that this requires adding `MonadBaseControl IO m` constraint all over the place: previously, we would run directly on `IO` and lift, and would therefore not need to bring that constraint all the way.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7789
GitOrigin-RevId: e9b2e431c5c47fa9851abf87545c0415ff6d1a12
2023-02-09 17:38:33 +03:00
|
|
|
(MonadIO m, MonadBaseControl IO m) =>
|
2021-04-22 00:44:37 +03:00
|
|
|
SourceConfig ('Postgres pgKind) ->
|
|
|
|
MultiplexedQuery ('Postgres pgKind) ->
|
2021-02-20 16:45:49 +03:00
|
|
|
[(CohortId, CohortVariables)] ->
|
2023-01-25 10:12:53 +03:00
|
|
|
ResolvedConnectionTemplate ('Postgres pgKind) ->
|
2021-02-20 16:45:49 +03:00
|
|
|
m (DiffTime, Either QErr [(CohortId, B.ByteString)])
|
2023-01-25 10:12:53 +03:00
|
|
|
runPGSubscription sourceConfig query variables resolvedConnectionTemplate =
|
2021-09-01 20:56:46 +03:00
|
|
|
withElapsedTime $
|
2022-04-22 22:53:12 +03:00
|
|
|
runExceptT $
|
2023-01-25 10:12:53 +03:00
|
|
|
runQueryTx (_pscExecCtx sourceConfig) (GraphQLQuery resolvedConnectionTemplate) $
|
2022-04-22 22:53:12 +03:00
|
|
|
PGL.executeMultiplexedQuery query variables
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2022-04-07 17:41:43 +03:00
|
|
|
runPGStreamingSubscription ::
|
Allow backend execution to happen on the base app monad.
### Description
Each Backend executes queries against the database in a slightly different stack: Postgres uses its own `TXeT`, MSSQL uses a variant of it, BigQuery is simply in `ExceptT QErr IO`... To accommodate those variations, we had originally introduced an `ExecutionMonad b` type family in `BackendExecute`, allowing each backend to describe its own stack. It was then up to that backend's `BackendTransport` instance to implement running said stack, and converting the result back into our main app monad.
However, this was not without complications: `TraceT` is one of them: as it usually needs to be on the top of the stack, converting from one stack to the other implies the use `interpTraceT`, which is quite monstrous. Furthermore, as part of the Entitlement Services work, we're trying to move to a "Services" architecture in which the entire engine runs in one base monad, that delegates features and dependencies to monad constraints; and as a result we'd like to minimize the number of different monad stacks we have to maintain and translate from and to in the codebase.
To improve things, this PR changes `ExecutionMonad b` from an _absolute_ stack to a _relative_ one: i.e.: what needs to be stacked on top of our base monad for the execution. In `Transport`, we then only need to pop the top of the stack, and voila. This greatly simplifies the implementation of the backends, as there's no longer any need to do any stack transformation: MySQL's implementation becomes a `runIdentityT`! This also removes most mentions of `TraceT` from the execution code since it's no longer required: we can rely on the base monad's existing `MonadTrace` constraint.
To continue encapsulating monadic actions in `DBStepInfo` and avoid threading a bunch of `forall` all over the place, this PR introduces a small local helper: `OnBaseMonad`. One only downside of all this is that this requires adding `MonadBaseControl IO m` constraint all over the place: previously, we would run directly on `IO` and lift, and would therefore not need to bring that constraint all the way.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7789
GitOrigin-RevId: e9b2e431c5c47fa9851abf87545c0415ff6d1a12
2023-02-09 17:38:33 +03:00
|
|
|
(MonadIO m, MonadBaseControl IO m) =>
|
2022-04-07 17:41:43 +03:00
|
|
|
SourceConfig ('Postgres pgKind) ->
|
|
|
|
MultiplexedQuery ('Postgres pgKind) ->
|
|
|
|
[(CohortId, CohortVariables)] ->
|
2023-01-25 10:12:53 +03:00
|
|
|
ResolvedConnectionTemplate ('Postgres pgKind) ->
|
2022-04-07 17:41:43 +03:00
|
|
|
m (DiffTime, Either QErr [(CohortId, B.ByteString, CursorVariableValues)])
|
2023-01-25 10:12:53 +03:00
|
|
|
runPGStreamingSubscription sourceConfig query variables resolvedConnectionTemplate =
|
2022-04-07 17:41:43 +03:00
|
|
|
withElapsedTime $
|
|
|
|
runExceptT $ do
|
2023-01-25 10:12:53 +03:00
|
|
|
res <- runQueryTx (_pscExecCtx sourceConfig) (GraphQLQuery resolvedConnectionTemplate) $ PGL.executeStreamingMultiplexedQuery query variables
|
2022-09-21 21:40:41 +03:00
|
|
|
pure $ res <&> (\(cohortId, cohortRes, cursorVariableVals) -> (cohortId, cohortRes, PG.getViaJSON cursorVariableVals))
|
2022-04-07 17:41:43 +03:00
|
|
|
|
2021-04-13 14:10:08 +03:00
|
|
|
runPGQueryExplain ::
|
2021-04-22 00:44:37 +03:00
|
|
|
forall pgKind m.
|
2021-04-13 14:10:08 +03:00
|
|
|
( MonadIO m,
|
Allow backend execution to happen on the base app monad.
### Description
Each Backend executes queries against the database in a slightly different stack: Postgres uses its own `TXeT`, MSSQL uses a variant of it, BigQuery is simply in `ExceptT QErr IO`... To accommodate those variations, we had originally introduced an `ExecutionMonad b` type family in `BackendExecute`, allowing each backend to describe its own stack. It was then up to that backend's `BackendTransport` instance to implement running said stack, and converting the result back into our main app monad.
However, this was not without complications: `TraceT` is one of them: as it usually needs to be on the top of the stack, converting from one stack to the other implies the use `interpTraceT`, which is quite monstrous. Furthermore, as part of the Entitlement Services work, we're trying to move to a "Services" architecture in which the entire engine runs in one base monad, that delegates features and dependencies to monad constraints; and as a result we'd like to minimize the number of different monad stacks we have to maintain and translate from and to in the codebase.
To improve things, this PR changes `ExecutionMonad b` from an _absolute_ stack to a _relative_ one: i.e.: what needs to be stacked on top of our base monad for the execution. In `Transport`, we then only need to pop the top of the stack, and voila. This greatly simplifies the implementation of the backends, as there's no longer any need to do any stack transformation: MySQL's implementation becomes a `runIdentityT`! This also removes most mentions of `TraceT` from the execution code since it's no longer required: we can rely on the base monad's existing `MonadTrace` constraint.
To continue encapsulating monadic actions in `DBStepInfo` and avoid threading a bunch of `forall` all over the place, this PR introduces a small local helper: `OnBaseMonad`. One only downside of all this is that this requires adding `MonadBaseControl IO m` constraint all over the place: previously, we would run directly on `IO` and lift, and would therefore not need to bring that constraint all the way.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7789
GitOrigin-RevId: e9b2e431c5c47fa9851abf87545c0415ff6d1a12
2023-02-09 17:38:33 +03:00
|
|
|
MonadBaseControl IO m,
|
|
|
|
MonadError QErr m,
|
|
|
|
MonadTrace m
|
2021-04-13 14:10:08 +03:00
|
|
|
) =>
|
2021-04-22 00:44:37 +03:00
|
|
|
DBStepInfo ('Postgres pgKind) ->
|
2021-04-13 14:10:08 +03:00
|
|
|
m EncJSON
|
2023-01-25 10:12:53 +03:00
|
|
|
runPGQueryExplain (DBStepInfo _ sourceConfig _ action resolvedConnectionTemplate) =
|
Allow backend execution to happen on the base app monad.
### Description
Each Backend executes queries against the database in a slightly different stack: Postgres uses its own `TXeT`, MSSQL uses a variant of it, BigQuery is simply in `ExceptT QErr IO`... To accommodate those variations, we had originally introduced an `ExecutionMonad b` type family in `BackendExecute`, allowing each backend to describe its own stack. It was then up to that backend's `BackendTransport` instance to implement running said stack, and converting the result back into our main app monad.
However, this was not without complications: `TraceT` is one of them: as it usually needs to be on the top of the stack, converting from one stack to the other implies the use `interpTraceT`, which is quite monstrous. Furthermore, as part of the Entitlement Services work, we're trying to move to a "Services" architecture in which the entire engine runs in one base monad, that delegates features and dependencies to monad constraints; and as a result we'd like to minimize the number of different monad stacks we have to maintain and translate from and to in the codebase.
To improve things, this PR changes `ExecutionMonad b` from an _absolute_ stack to a _relative_ one: i.e.: what needs to be stacked on top of our base monad for the execution. In `Transport`, we then only need to pop the top of the stack, and voila. This greatly simplifies the implementation of the backends, as there's no longer any need to do any stack transformation: MySQL's implementation becomes a `runIdentityT`! This also removes most mentions of `TraceT` from the execution code since it's no longer required: we can rely on the base monad's existing `MonadTrace` constraint.
To continue encapsulating monadic actions in `DBStepInfo` and avoid threading a bunch of `forall` all over the place, this PR introduces a small local helper: `OnBaseMonad`. One only downside of all this is that this requires adding `MonadBaseControl IO m` constraint all over the place: previously, we would run directly on `IO` and lift, and would therefore not need to bring that constraint all the way.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7789
GitOrigin-RevId: e9b2e431c5c47fa9851abf87545c0415ff6d1a12
2023-02-09 17:38:33 +03:00
|
|
|
runQueryTx (_pscExecCtx sourceConfig) (GraphQLQuery resolvedConnectionTemplate) $
|
|
|
|
runOnBaseMonad action
|
2021-04-13 14:10:08 +03:00
|
|
|
|
2021-03-13 17:40:50 +03:00
|
|
|
mkQueryLog ::
|
|
|
|
GQLReqUnparsed ->
|
2021-10-29 17:42:07 +03:00
|
|
|
RootFieldAlias ->
|
2021-06-11 06:26:50 +03:00
|
|
|
Maybe EQ.PreparedSql ->
|
2021-03-13 17:40:50 +03:00
|
|
|
RequestId ->
|
2023-01-25 10:12:53 +03:00
|
|
|
Maybe (ResolvedConnectionTemplate ('Postgres pgKind)) ->
|
2021-03-13 17:40:50 +03:00
|
|
|
QueryLog
|
2023-01-25 10:12:53 +03:00
|
|
|
mkQueryLog gqlQuery fieldName preparedSql requestId resolvedConnectionTemplate =
|
|
|
|
QueryLog gqlQuery ((fieldName,) <$> generatedQuery) requestId (QueryLogKindDatabase (mkBackendResolvedConnectionTemplate <$> resolvedConnectionTemplate))
|
2021-03-13 17:40:50 +03:00
|
|
|
where
|
2023-01-25 10:12:53 +03:00
|
|
|
mkBackendResolvedConnectionTemplate ::
|
|
|
|
ResolvedConnectionTemplate ('Postgres pgKind) ->
|
|
|
|
BackendResolvedConnectionTemplate
|
|
|
|
mkBackendResolvedConnectionTemplate =
|
|
|
|
BackendResolvedConnectionTemplate . AB.mkAnyBackend @('Postgres 'Vanilla) . ResolvedConnectionTemplateWrapper
|
2021-06-11 06:26:50 +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]
|
|
|
|
|
|
|
|
runPGMutationTransaction ::
|
|
|
|
( MonadIO m,
|
Allow backend execution to happen on the base app monad.
### Description
Each Backend executes queries against the database in a slightly different stack: Postgres uses its own `TXeT`, MSSQL uses a variant of it, BigQuery is simply in `ExceptT QErr IO`... To accommodate those variations, we had originally introduced an `ExecutionMonad b` type family in `BackendExecute`, allowing each backend to describe its own stack. It was then up to that backend's `BackendTransport` instance to implement running said stack, and converting the result back into our main app monad.
However, this was not without complications: `TraceT` is one of them: as it usually needs to be on the top of the stack, converting from one stack to the other implies the use `interpTraceT`, which is quite monstrous. Furthermore, as part of the Entitlement Services work, we're trying to move to a "Services" architecture in which the entire engine runs in one base monad, that delegates features and dependencies to monad constraints; and as a result we'd like to minimize the number of different monad stacks we have to maintain and translate from and to in the codebase.
To improve things, this PR changes `ExecutionMonad b` from an _absolute_ stack to a _relative_ one: i.e.: what needs to be stacked on top of our base monad for the execution. In `Transport`, we then only need to pop the top of the stack, and voila. This greatly simplifies the implementation of the backends, as there's no longer any need to do any stack transformation: MySQL's implementation becomes a `runIdentityT`! This also removes most mentions of `TraceT` from the execution code since it's no longer required: we can rely on the base monad's existing `MonadTrace` constraint.
To continue encapsulating monadic actions in `DBStepInfo` and avoid threading a bunch of `forall` all over the place, this PR introduces a small local helper: `OnBaseMonad`. One only downside of all this is that this requires adding `MonadBaseControl IO m` constraint all over the place: previously, we would run directly on `IO` and lift, and would therefore not need to bring that constraint all the way.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7789
GitOrigin-RevId: e9b2e431c5c47fa9851abf87545c0415ff6d1a12
2023-02-09 17:38:33 +03:00
|
|
|
MonadBaseControl IO m,
|
2021-04-01 23:40:31 +03:00
|
|
|
MonadError QErr m,
|
|
|
|
MonadQueryLog m,
|
|
|
|
MonadTrace m
|
|
|
|
) =>
|
|
|
|
RequestId ->
|
|
|
|
GQLReqUnparsed ->
|
|
|
|
UserInfo ->
|
|
|
|
L.Logger L.Hasura ->
|
2021-04-22 00:44:37 +03:00
|
|
|
SourceConfig ('Postgres pgKind) ->
|
2023-01-25 10:12:53 +03:00
|
|
|
ResolvedConnectionTemplate ('Postgres pgKind) ->
|
2021-10-29 17:42:07 +03:00
|
|
|
RootFieldMap (DBStepInfo ('Postgres pgKind)) ->
|
|
|
|
m (DiffTime, RootFieldMap EncJSON)
|
2023-01-25 10:12:53 +03:00
|
|
|
runPGMutationTransaction reqId query userInfo logger sourceConfig resolvedConnectionTemplate mutations = do
|
|
|
|
logQueryLog logger $ mkQueryLog query (mkUnNamespacedRootFieldAlias Name._transaction) Nothing reqId (resolvedConnectionTemplate <$ resolvedConnectionTemplate)
|
Allow backend execution to happen on the base app monad.
### Description
Each Backend executes queries against the database in a slightly different stack: Postgres uses its own `TXeT`, MSSQL uses a variant of it, BigQuery is simply in `ExceptT QErr IO`... To accommodate those variations, we had originally introduced an `ExecutionMonad b` type family in `BackendExecute`, allowing each backend to describe its own stack. It was then up to that backend's `BackendTransport` instance to implement running said stack, and converting the result back into our main app monad.
However, this was not without complications: `TraceT` is one of them: as it usually needs to be on the top of the stack, converting from one stack to the other implies the use `interpTraceT`, which is quite monstrous. Furthermore, as part of the Entitlement Services work, we're trying to move to a "Services" architecture in which the entire engine runs in one base monad, that delegates features and dependencies to monad constraints; and as a result we'd like to minimize the number of different monad stacks we have to maintain and translate from and to in the codebase.
To improve things, this PR changes `ExecutionMonad b` from an _absolute_ stack to a _relative_ one: i.e.: what needs to be stacked on top of our base monad for the execution. In `Transport`, we then only need to pop the top of the stack, and voila. This greatly simplifies the implementation of the backends, as there's no longer any need to do any stack transformation: MySQL's implementation becomes a `runIdentityT`! This also removes most mentions of `TraceT` from the execution code since it's no longer required: we can rely on the base monad's existing `MonadTrace` constraint.
To continue encapsulating monadic actions in `DBStepInfo` and avoid threading a bunch of `forall` all over the place, this PR introduces a small local helper: `OnBaseMonad`. One only downside of all this is that this requires adding `MonadBaseControl IO m` constraint all over the place: previously, we would run directly on `IO` and lift, and would therefore not need to bring that constraint all the way.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7789
GitOrigin-RevId: e9b2e431c5c47fa9851abf87545c0415ff6d1a12
2023-02-09 17:38:33 +03:00
|
|
|
withElapsedTime $
|
|
|
|
runTxWithCtxAndUserInfo userInfo (_pscExecCtx sourceConfig) (Tx PG.ReadWrite Nothing) (GraphQLQuery resolvedConnectionTemplate) $
|
|
|
|
flip OMap.traverseWithKey mutations \fieldName dbsi ->
|
|
|
|
trace ("Postgres Mutation for root field " <>> fieldName) $
|
|
|
|
runOnBaseMonad $
|
|
|
|
dbsiAction dbsi
|