2022-03-16 03:39:21 +03:00
|
|
|
|
{-# LANGUAGE QuasiQuotes #-}
|
|
|
|
|
{-# LANGUAGE TemplateHaskell #-}
|
|
|
|
|
|
2022-02-08 12:24:34 +03:00
|
|
|
|
-- | Postgres DDL RunSQL
|
|
|
|
|
--
|
|
|
|
|
-- Escape hatch for running raw SQL against a postgres database.
|
|
|
|
|
--
|
|
|
|
|
-- 'runRunSQL' executes the provided raw SQL.
|
|
|
|
|
--
|
|
|
|
|
-- 'isSchemaCacheBuildRequiredRunSQL' checks for known schema-mutating keywords
|
|
|
|
|
-- in the raw SQL text.
|
|
|
|
|
--
|
|
|
|
|
-- See 'Hasura.Server.API.V2Query' and 'Hasura.Server.API.Query'.
|
2021-02-14 09:07:52 +03:00
|
|
|
|
module Hasura.Backends.Postgres.DDL.RunSQL
|
2021-05-27 18:06:13 +03:00
|
|
|
|
( runRunSQL,
|
|
|
|
|
RunSQL (..),
|
|
|
|
|
isSchemaCacheBuildRequiredRunSQL,
|
|
|
|
|
)
|
|
|
|
|
where
|
2021-09-24 01:56:37 +03:00
|
|
|
|
|
2021-09-09 14:54:19 +03:00
|
|
|
|
import Control.Monad.Trans.Control (MonadBaseControl)
|
2021-05-27 18:06:13 +03:00
|
|
|
|
import Data.Aeson
|
2021-09-09 14:54:19 +03:00
|
|
|
|
import Data.HashMap.Strict qualified as M
|
|
|
|
|
import Data.HashSet qualified as HS
|
2022-12-05 13:20:47 +03:00
|
|
|
|
import Data.List.NonEmpty qualified as NE
|
2021-02-14 09:07:52 +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
|
2021-09-09 14:54:19 +03:00
|
|
|
|
import Hasura.Backends.Postgres.DDL.EventTrigger
|
|
|
|
|
import Hasura.Backends.Postgres.DDL.Source
|
2022-08-24 17:32:08 +03:00
|
|
|
|
( FetchFunctionMetadata,
|
|
|
|
|
FetchTableMetadata,
|
2022-08-24 12:36:30 +03:00
|
|
|
|
ToMetadataFetchQuery,
|
2021-09-09 14:54:19 +03:00
|
|
|
|
fetchFunctionMetadata,
|
|
|
|
|
fetchTableMetadata,
|
|
|
|
|
)
|
2022-04-27 16:57:28 +03:00
|
|
|
|
import Hasura.Backends.Postgres.Execute.Types
|
2022-03-08 16:02:13 +03:00
|
|
|
|
import Hasura.Backends.Postgres.SQL.Types hiding (FunctionName, TableName)
|
2021-05-11 18:18:31 +03:00
|
|
|
|
import Hasura.Base.Error
|
2021-05-27 18:06:13 +03:00
|
|
|
|
import Hasura.EncJSON
|
2021-02-14 09:07:52 +03:00
|
|
|
|
import Hasura.Prelude
|
2021-05-27 18:06:13 +03:00
|
|
|
|
import Hasura.RQL.DDL.Schema
|
2022-12-05 13:20:47 +03:00
|
|
|
|
import Hasura.RQL.DDL.Schema.Diff qualified as Diff
|
2022-04-27 16:57:28 +03:00
|
|
|
|
import Hasura.RQL.Types.Backend
|
|
|
|
|
import Hasura.RQL.Types.Common
|
|
|
|
|
import Hasura.RQL.Types.ComputedField
|
|
|
|
|
import Hasura.RQL.Types.EventTrigger
|
|
|
|
|
import Hasura.RQL.Types.Function
|
|
|
|
|
import Hasura.RQL.Types.Metadata hiding
|
|
|
|
|
( fmFunction,
|
2021-09-09 14:54:19 +03:00
|
|
|
|
tmComputedFields,
|
|
|
|
|
tmTable,
|
|
|
|
|
)
|
2022-04-27 16:57:28 +03:00
|
|
|
|
import Hasura.RQL.Types.Metadata.Backend
|
|
|
|
|
import Hasura.RQL.Types.SchemaCache
|
|
|
|
|
import Hasura.RQL.Types.SchemaCache.Build
|
|
|
|
|
import Hasura.RQL.Types.SchemaCacheTypes
|
|
|
|
|
import Hasura.RQL.Types.Source
|
|
|
|
|
import Hasura.RQL.Types.Table
|
2021-09-09 14:54:19 +03:00
|
|
|
|
import Hasura.SQL.AnyBackend qualified as AB
|
2022-04-27 16:57:28 +03:00
|
|
|
|
import Hasura.SQL.Backend
|
2022-04-22 17:50:01 +03:00
|
|
|
|
import Hasura.Server.Types
|
2021-09-09 14:54:19 +03:00
|
|
|
|
import Hasura.Server.Utils (quoteRegex)
|
2021-09-01 20:56:46 +03:00
|
|
|
|
import Hasura.Session
|
2021-09-09 14:54:19 +03:00
|
|
|
|
import Hasura.Tracing qualified as Tracing
|
|
|
|
|
import Text.Regex.TDFA qualified as TDFA
|
2021-09-24 01:56:37 +03:00
|
|
|
|
|
2021-05-27 18:06:13 +03:00
|
|
|
|
data RunSQL = RunSQL
|
|
|
|
|
{ rSql :: Text,
|
2022-07-29 17:05:03 +03:00
|
|
|
|
rSource :: SourceName,
|
|
|
|
|
rCascade :: Bool,
|
|
|
|
|
rCheckMetadataConsistency :: Maybe Bool,
|
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
|
|
|
|
rTxAccessMode :: PG.TxAccess
|
2021-02-14 09:07:52 +03:00
|
|
|
|
}
|
|
|
|
|
deriving (Show, Eq)
|
|
|
|
|
|
2021-05-27 18:06:13 +03:00
|
|
|
|
instance FromJSON RunSQL where
|
|
|
|
|
parseJSON = withObject "RunSQL" $ \o -> do
|
|
|
|
|
rSql <- o .: "sql"
|
|
|
|
|
rSource <- o .:? "source" .!= defaultSource
|
|
|
|
|
rCascade <- o .:? "cascade" .!= False
|
|
|
|
|
rCheckMetadataConsistency <- o .:? "check_metadata_consistency"
|
|
|
|
|
isReadOnly <- o .:? "read_only" .!= False
|
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
|
|
|
|
let rTxAccessMode = if isReadOnly then PG.ReadOnly else PG.ReadWrite
|
2021-05-27 18:06:13 +03:00
|
|
|
|
pure RunSQL {..}
|
|
|
|
|
|
|
|
|
|
instance ToJSON RunSQL where
|
|
|
|
|
toJSON RunSQL {..} =
|
|
|
|
|
object
|
|
|
|
|
[ "sql" .= rSql,
|
|
|
|
|
"source" .= rSource,
|
|
|
|
|
"cascade" .= rCascade,
|
|
|
|
|
"check_metadata_consistency" .= rCheckMetadataConsistency,
|
|
|
|
|
"read_only"
|
|
|
|
|
.= case rTxAccessMode of
|
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.ReadOnly -> True
|
|
|
|
|
PG.ReadWrite -> False
|
2021-05-27 18:06:13 +03:00
|
|
|
|
]
|
|
|
|
|
|
2022-02-08 12:24:34 +03:00
|
|
|
|
-- | Check for known schema-mutating keywords in the raw SQL text.
|
|
|
|
|
--
|
|
|
|
|
-- See Note [Checking metadata consistency in run_sql].
|
2021-05-27 18:06:13 +03:00
|
|
|
|
isSchemaCacheBuildRequiredRunSQL :: RunSQL -> Bool
|
|
|
|
|
isSchemaCacheBuildRequiredRunSQL RunSQL {..} =
|
|
|
|
|
case rTxAccessMode of
|
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.ReadOnly -> False
|
|
|
|
|
PG.ReadWrite -> fromMaybe (containsDDLKeyword rSql) rCheckMetadataConsistency
|
2021-05-27 18:06:13 +03:00
|
|
|
|
where
|
|
|
|
|
containsDDLKeyword =
|
|
|
|
|
TDFA.match
|
|
|
|
|
$$( quoteRegex
|
|
|
|
|
TDFA.defaultCompOpt
|
|
|
|
|
{ TDFA.caseSensitive = False,
|
|
|
|
|
TDFA.multiline = True,
|
|
|
|
|
TDFA.lastStarGreedy = True
|
|
|
|
|
}
|
|
|
|
|
TDFA.defaultExecOpt
|
|
|
|
|
{ TDFA.captureGroups = False
|
|
|
|
|
}
|
|
|
|
|
"\\balter\\b|\\bdrop\\b|\\breplace\\b|\\bcreate function\\b|\\bcomment on\\b"
|
|
|
|
|
)
|
|
|
|
|
|
|
|
|
|
{- Note [Checking metadata consistency in run_sql]
|
|
|
|
|
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
|
|
|
|
|
SQL queries executed by run_sql may change the Postgres schema in arbitrary
|
|
|
|
|
ways. We attempt to automatically update the metadata to reflect those changes
|
|
|
|
|
as much as possible---for example, if a table is renamed, we want to update the
|
|
|
|
|
metadata to track the table under its new name instead of its old one. This
|
|
|
|
|
schema diffing (plus some integrity checking) is handled by withMetadataCheck.
|
|
|
|
|
|
|
|
|
|
But this process has overhead---it involves reloading the metadata, diffing it,
|
|
|
|
|
and rebuilding the schema cache---so we don’t want to do it if it isn’t
|
|
|
|
|
necessary. The user can explicitly disable the check via the
|
|
|
|
|
check_metadata_consistency option, and we also skip it if the current
|
|
|
|
|
transaction is in READ ONLY mode, since the schema can’t be modified in that
|
|
|
|
|
case, anyway.
|
|
|
|
|
|
|
|
|
|
However, even if neither read_only or check_metadata_consistency is passed, lots
|
|
|
|
|
of queries may not modify the schema at all. As a (fairly stupid) heuristic, we
|
|
|
|
|
check if the query contains any keywords for DDL operations, and if not, we skip
|
|
|
|
|
the metadata check as well. -}
|
2021-02-14 09:07:52 +03:00
|
|
|
|
|
2022-12-05 13:20:47 +03:00
|
|
|
|
-- | Fetch metadata of tracked tables/functions and build @'Diff.TableMeta'/@'Diff.FunctionMeta'
|
2022-03-08 16:02:13 +03:00
|
|
|
|
-- to calculate diff later in @'withMetadataCheck'.
|
|
|
|
|
fetchTablesFunctionsMetadata ::
|
2022-08-24 17:32:08 +03:00
|
|
|
|
forall pgKind m.
|
|
|
|
|
( ToMetadataFetchQuery pgKind,
|
|
|
|
|
FetchTableMetadata pgKind,
|
|
|
|
|
FetchFunctionMetadata pgKind,
|
|
|
|
|
BackendMetadata ('Postgres pgKind),
|
|
|
|
|
MonadTx m
|
|
|
|
|
) =>
|
2021-05-21 05:46:58 +03:00
|
|
|
|
TableCache ('Postgres pgKind) ->
|
2022-12-05 13:20:47 +03:00
|
|
|
|
HS.HashSet (TableName ('Postgres pgKind)) ->
|
2022-10-28 11:23:02 +03:00
|
|
|
|
HS.HashSet (FunctionName ('Postgres pgKind)) ->
|
2022-12-05 13:20:47 +03:00
|
|
|
|
m ([Diff.TableMeta ('Postgres pgKind)], [Diff.FunctionMeta ('Postgres pgKind)])
|
2022-03-08 16:02:13 +03:00
|
|
|
|
fetchTablesFunctionsMetadata tableCache tables functions = do
|
|
|
|
|
tableMetaInfos <- fetchTableMetadata tables
|
2022-08-24 17:32:08 +03:00
|
|
|
|
functionMetaInfos <- fetchFunctionMetadata @pgKind functions
|
2021-02-14 09:07:52 +03:00
|
|
|
|
|
2022-12-05 13:20:47 +03:00
|
|
|
|
let functionMetas =
|
|
|
|
|
[ functionMeta
|
|
|
|
|
| function <- HS.toList functions,
|
|
|
|
|
functionMeta <- mkFunctionMetas functionMetaInfos function
|
|
|
|
|
]
|
|
|
|
|
let tableMetas =
|
|
|
|
|
[ Diff.TableMeta table tableMetaInfo computedFieldInfos
|
|
|
|
|
| (table, tableMetaInfo) <- M.toList tableMetaInfos,
|
|
|
|
|
let computedFieldInfos =
|
|
|
|
|
[ computedFieldMeta
|
|
|
|
|
| Just tableInfo <- pure (M.lookup table tableCache),
|
|
|
|
|
computedField <- getComputedFields tableInfo,
|
|
|
|
|
computedFieldMeta <-
|
|
|
|
|
[ Diff.ComputedFieldMeta fieldName functionMeta
|
|
|
|
|
| let fieldName = _cfiName computedField
|
|
|
|
|
function = _cffName $ _cfiFunction computedField,
|
|
|
|
|
functionMeta <- mkFunctionMetas functionMetaInfos function
|
|
|
|
|
]
|
|
|
|
|
]
|
|
|
|
|
]
|
|
|
|
|
|
|
|
|
|
pure (tableMetas, functionMetas)
|
|
|
|
|
where
|
|
|
|
|
mkFunctionMetas ::
|
|
|
|
|
HashMap QualifiedFunction (FunctionOverloads ('Postgres pgKind)) ->
|
|
|
|
|
QualifiedFunction ->
|
|
|
|
|
[Diff.FunctionMeta ('Postgres pgKind)]
|
|
|
|
|
mkFunctionMetas functionMetaInfos function =
|
|
|
|
|
[ Diff.FunctionMeta (rfiOid rawInfo) function (rfiFunctionType rawInfo)
|
|
|
|
|
| -- It would seem like we could feasibly detect function overloads here already,
|
|
|
|
|
-- But that is handled elsewhere.
|
|
|
|
|
Just overloads <- pure (M.lookup function functionMetaInfos),
|
|
|
|
|
rawInfo <- NE.toList $ getFunctionOverloads overloads
|
|
|
|
|
]
|
2021-02-14 09:07:52 +03:00
|
|
|
|
|
2022-02-08 12:24:34 +03:00
|
|
|
|
-- | Used as an escape hatch to run raw SQL against a database.
|
2021-05-27 18:06:13 +03:00
|
|
|
|
runRunSQL ::
|
|
|
|
|
forall (pgKind :: PostgresKind) m.
|
|
|
|
|
( BackendMetadata ('Postgres pgKind),
|
|
|
|
|
ToMetadataFetchQuery pgKind,
|
2022-08-24 12:36:30 +03:00
|
|
|
|
FetchTableMetadata pgKind,
|
2022-08-24 17:32:08 +03:00
|
|
|
|
FetchFunctionMetadata pgKind,
|
2021-05-27 18:06:13 +03:00
|
|
|
|
CacheRWM m,
|
|
|
|
|
HasServerConfigCtx m,
|
|
|
|
|
MetadataM m,
|
|
|
|
|
MonadBaseControl IO m,
|
|
|
|
|
MonadError QErr m,
|
|
|
|
|
MonadIO m,
|
2021-09-01 20:56:46 +03:00
|
|
|
|
Tracing.MonadTrace m,
|
|
|
|
|
UserInfoM m
|
2021-05-27 18:06:13 +03:00
|
|
|
|
) =>
|
|
|
|
|
RunSQL ->
|
|
|
|
|
m EncJSON
|
2021-09-01 20:56:46 +03:00
|
|
|
|
runRunSQL q@RunSQL {..} = do
|
|
|
|
|
sourceConfig <- askSourceConfig @('Postgres pgKind) rSource
|
|
|
|
|
traceCtx <- Tracing.currentContext
|
|
|
|
|
userInfo <- askUserInfo
|
|
|
|
|
let pgExecCtx = _pscExecCtx sourceConfig
|
|
|
|
|
if (isSchemaCacheBuildRequiredRunSQL q)
|
|
|
|
|
then do
|
|
|
|
|
-- see Note [Checking metadata consistency in run_sql]
|
|
|
|
|
withMetadataCheck @pgKind rSource rCascade rTxAccessMode $
|
|
|
|
|
withTraceContext traceCtx $
|
|
|
|
|
withUserInfo userInfo $
|
|
|
|
|
execRawSQL rSql
|
|
|
|
|
else do
|
2021-09-15 23:45:49 +03:00
|
|
|
|
runTxWithCtx pgExecCtx rTxAccessMode $ execRawSQL rSql
|
2021-02-14 09:07:52 +03:00
|
|
|
|
where
|
2021-05-27 18:06:13 +03:00
|
|
|
|
execRawSQL :: (MonadTx n) => Text -> n EncJSON
|
|
|
|
|
execRawSQL =
|
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
|
|
|
|
fmap (encJFromJValue @RunSQLRes) . liftTx . PG.multiQE rawSqlErrHandler . PG.fromText
|
2021-05-27 18:06:13 +03:00
|
|
|
|
where
|
|
|
|
|
rawSqlErrHandler txe =
|
2021-09-17 10:43:43 +03:00
|
|
|
|
(err400 PostgresError "query execution failed") {qeInternal = Just $ ExtraInternal $ toJSON txe}
|
2021-02-14 09:07:52 +03:00
|
|
|
|
|
2022-03-08 16:02:13 +03:00
|
|
|
|
-- | @'withMetadataCheck' source cascade txAccess runSQLQuery@ executes @runSQLQuery@ and checks if the schema changed as a
|
2021-02-14 09:07:52 +03:00
|
|
|
|
-- result. If it did, it checks to ensure the changes do not violate any integrity constraints, and
|
|
|
|
|
-- if not, incorporates them into the schema cache.
|
2021-07-23 02:06:10 +03:00
|
|
|
|
-- TODO(antoine): shouldn't this be generalized?
|
2021-02-14 09:07:52 +03:00
|
|
|
|
withMetadataCheck ::
|
2021-05-21 05:46:58 +03:00
|
|
|
|
forall (pgKind :: PostgresKind) a m.
|
2021-05-27 18:06:13 +03:00
|
|
|
|
( BackendMetadata ('Postgres pgKind),
|
2021-05-21 05:46:58 +03:00
|
|
|
|
ToMetadataFetchQuery pgKind,
|
2022-08-24 12:36:30 +03:00
|
|
|
|
FetchTableMetadata pgKind,
|
2022-08-24 17:32:08 +03:00
|
|
|
|
FetchFunctionMetadata pgKind,
|
2021-05-21 05:46:58 +03:00
|
|
|
|
CacheRWM m,
|
|
|
|
|
HasServerConfigCtx m,
|
|
|
|
|
MetadataM m,
|
|
|
|
|
MonadBaseControl IO m,
|
|
|
|
|
MonadError QErr m,
|
|
|
|
|
MonadIO m
|
2021-09-15 23:45:49 +03:00
|
|
|
|
) =>
|
|
|
|
|
SourceName ->
|
|
|
|
|
Bool ->
|
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.TxAccess ->
|
|
|
|
|
PG.TxET QErr m a ->
|
2021-09-15 23:45:49 +03:00
|
|
|
|
m a
|
2022-03-08 16:02:13 +03:00
|
|
|
|
withMetadataCheck source cascade txAccess runSQLQuery = do
|
|
|
|
|
SourceInfo _ tableCache functionCache sourceConfig _ _ <- askSourceInfo @('Postgres pgKind) source
|
|
|
|
|
|
|
|
|
|
-- Run SQL query and metadata checker in a transaction
|
2022-05-10 16:46:13 +03:00
|
|
|
|
(queryResult, metadataUpdater) <- runTxWithMetadataCheck source sourceConfig txAccess tableCache functionCache cascade runSQLQuery
|
2021-02-14 09:07:52 +03:00
|
|
|
|
|
|
|
|
|
-- Build schema cache with updated metadata
|
|
|
|
|
withNewInconsistentObjsCheck $
|
|
|
|
|
buildSchemaCacheWithInvalidations mempty {ciSources = HS.singleton source} metadataUpdater
|
|
|
|
|
|
2022-03-08 16:02:13 +03:00
|
|
|
|
postRunSQLSchemaCache <- askSchemaCache
|
|
|
|
|
|
|
|
|
|
-- Recreate event triggers in hdb_catalog. Event triggers are dropped before executing @'runSQLQuery'.
|
|
|
|
|
recreateEventTriggers sourceConfig postRunSQLSchemaCache
|
2021-02-14 09:07:52 +03:00
|
|
|
|
|
2022-03-08 16:02:13 +03:00
|
|
|
|
pure queryResult
|
|
|
|
|
where
|
|
|
|
|
recreateEventTriggers :: PGSourceConfig -> SchemaCache -> m ()
|
|
|
|
|
recreateEventTriggers sourceConfig schemaCache = do
|
|
|
|
|
let tables = fromMaybe mempty $ unsafeTableCache @('Postgres pgKind) source $ scSources schemaCache
|
|
|
|
|
serverConfigCtx <- askServerConfigCtx
|
|
|
|
|
liftEitherM $
|
|
|
|
|
runPgSourceWriteTx sourceConfig $
|
|
|
|
|
forM_ (M.elems tables) $ \(TableInfo coreInfo _ eventTriggers _) -> do
|
|
|
|
|
let table = _tciName coreInfo
|
|
|
|
|
columns = getCols $ _tciFieldInfoMap coreInfo
|
2022-11-29 20:41:41 +03:00
|
|
|
|
forM_ (M.toList eventTriggers) $ \(triggerName, EventTriggerInfo {etiOpsDef, etiTriggerOnReplication}) -> do
|
|
|
|
|
flip runReaderT serverConfigCtx $ mkAllTriggersQ triggerName table etiTriggerOnReplication columns etiOpsDef
|
2022-03-08 16:02:13 +03:00
|
|
|
|
|
|
|
|
|
-- | @'runTxWithMetadataCheck source sourceConfig txAccess tableCache functionCache cascadeDependencies tx' checks for
|
|
|
|
|
-- changes in GraphQL Engine metadata when a @'tx' is executed on the database alters Postgres
|
|
|
|
|
-- schema of tables and functions. If any indirect dependencies (Eg. remote table dependence of a relationship) are
|
|
|
|
|
-- found and @'cascadeDependencies' is False, then an exception is raised.
|
|
|
|
|
runTxWithMetadataCheck ::
|
|
|
|
|
forall m a (pgKind :: PostgresKind).
|
|
|
|
|
( BackendMetadata ('Postgres pgKind),
|
|
|
|
|
ToMetadataFetchQuery pgKind,
|
2022-08-24 12:36:30 +03:00
|
|
|
|
FetchTableMetadata pgKind,
|
2022-08-24 17:32:08 +03:00
|
|
|
|
FetchFunctionMetadata pgKind,
|
2022-03-08 16:02:13 +03:00
|
|
|
|
CacheRWM m,
|
|
|
|
|
MonadIO m,
|
|
|
|
|
MonadBaseControl IO m,
|
|
|
|
|
MonadError QErr m
|
|
|
|
|
) =>
|
|
|
|
|
SourceName ->
|
|
|
|
|
SourceConfig ('Postgres pgKind) ->
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
PG.TxAccess ->
|
2022-03-08 16:02:13 +03:00
|
|
|
|
TableCache ('Postgres pgKind) ->
|
|
|
|
|
FunctionCache ('Postgres pgKind) ->
|
|
|
|
|
Bool ->
|
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.TxET QErr m a ->
|
2022-03-08 16:02:13 +03:00
|
|
|
|
m (a, MetadataModifier)
|
|
|
|
|
runTxWithMetadataCheck source sourceConfig txAccess tableCache functionCache cascadeDependencies tx =
|
2021-02-14 09:07:52 +03:00
|
|
|
|
liftEitherM $
|
2022-03-08 16:02:13 +03:00
|
|
|
|
runExceptT $
|
|
|
|
|
runTx (_pscExecCtx sourceConfig) txAccess $ do
|
|
|
|
|
-- Running in a transaction helps to rollback the @'tx' execution in case of any exceptions
|
|
|
|
|
|
|
|
|
|
-- Before running the @'tx', fetch metadata of existing tables and functions from Postgres.
|
2022-12-05 13:20:47 +03:00
|
|
|
|
let tableNames = M.keysSet tableCache
|
|
|
|
|
computedFieldFunctions = mconcat $ map getComputedFieldFunctions (M.elems tableCache)
|
2022-10-28 11:23:02 +03:00
|
|
|
|
functionNames = M.keysSet functionCache <> computedFieldFunctions
|
2022-03-08 16:02:13 +03:00
|
|
|
|
(preTxTablesMeta, preTxFunctionsMeta) <- fetchTablesFunctionsMetadata tableCache tableNames functionNames
|
|
|
|
|
|
|
|
|
|
-- Since the @'tx' may alter table/function names we use the OIDs of underlying tables
|
|
|
|
|
-- (sourced from 'pg_class' for tables and 'pg_proc' for functions), which remain unchanged in the
|
|
|
|
|
-- case if a table/function is renamed.
|
2022-12-05 13:20:47 +03:00
|
|
|
|
let tableOids = HS.fromList $ map (_ptmiOid . Diff.tmInfo) preTxTablesMeta
|
|
|
|
|
functionOids = HS.fromList $ map Diff.fmOid preTxFunctionsMeta
|
2022-03-08 16:02:13 +03:00
|
|
|
|
|
|
|
|
|
-- Run the transaction
|
|
|
|
|
txResult <- tx
|
|
|
|
|
|
|
|
|
|
(postTxTablesMeta, postTxFunctionMeta) <-
|
|
|
|
|
uncurry (fetchTablesFunctionsMetadata tableCache)
|
|
|
|
|
-- Fetch names of tables and functions using OIDs which also contains renamed items
|
|
|
|
|
=<< fetchTablesFunctionsFromOids tableOids functionOids
|
|
|
|
|
|
|
|
|
|
-- Calculate the tables diff (dropped & altered tables)
|
2022-12-05 13:20:47 +03:00
|
|
|
|
let tablesDiff = Diff.getTablesDiff preTxTablesMeta postTxTablesMeta
|
2022-03-08 16:02:13 +03:00
|
|
|
|
-- Calculate the functions diff. For calculating diff for functions, only consider
|
|
|
|
|
-- query/mutation functions and exclude functions underpinning computed fields.
|
|
|
|
|
-- Computed field functions are being processed under each table diff.
|
2022-12-05 13:20:47 +03:00
|
|
|
|
-- See @'getTablesDiff' and @'Diff.processTablesDiff'
|
|
|
|
|
excludeComputedFieldFunctions = filter ((`M.member` functionCache) . Diff.fmFunction)
|
2022-03-08 16:02:13 +03:00
|
|
|
|
functionsDiff =
|
2022-12-05 13:20:47 +03:00
|
|
|
|
Diff.getFunctionsDiff
|
2022-03-08 16:02:13 +03:00
|
|
|
|
(excludeComputedFieldFunctions preTxFunctionsMeta)
|
|
|
|
|
(excludeComputedFieldFunctions postTxFunctionMeta)
|
|
|
|
|
|
|
|
|
|
dontAllowFunctionOverloading $
|
2022-12-05 13:20:47 +03:00
|
|
|
|
Diff.getOverloadedFunctions
|
2022-03-08 16:02:13 +03:00
|
|
|
|
(M.keys functionCache)
|
|
|
|
|
(excludeComputedFieldFunctions postTxFunctionMeta)
|
|
|
|
|
|
|
|
|
|
-- Update metadata with schema change caused by @'tx'
|
|
|
|
|
metadataUpdater <- execWriterT do
|
|
|
|
|
-- Collect indirect dependencies of altered tables
|
2022-12-05 13:20:47 +03:00
|
|
|
|
tableIndirectDeps <- Diff.getIndirectDependenciesFromTableDiff source tablesDiff
|
2022-03-08 16:02:13 +03:00
|
|
|
|
|
|
|
|
|
-- If table indirect dependencies exist and cascading is not enabled then report an exception
|
2022-07-01 13:49:31 +03:00
|
|
|
|
unless (null tableIndirectDeps || cascadeDependencies) $ reportDependentObjectsExist tableIndirectDeps
|
2022-03-08 16:02:13 +03:00
|
|
|
|
|
|
|
|
|
-- Purge all the table dependents
|
2022-05-27 18:40:02 +03:00
|
|
|
|
traverse_ purgeSourceAndSchemaDependencies tableIndirectDeps
|
2022-03-08 16:02:13 +03:00
|
|
|
|
|
|
|
|
|
-- Collect function names from purged table dependencies
|
|
|
|
|
let purgedFunctions = collectFunctionsInDeps tableIndirectDeps
|
2022-12-05 13:20:47 +03:00
|
|
|
|
Diff.FunctionsDiff droppedFunctions alteredFunctions = functionsDiff
|
2022-03-08 16:02:13 +03:00
|
|
|
|
|
|
|
|
|
-- Drop functions in metadata. Exclude functions that were already dropped as part of table indirect dependencies
|
|
|
|
|
purgeFunctionsFromMetadata $ droppedFunctions \\ purgedFunctions
|
|
|
|
|
|
|
|
|
|
-- If any function type is altered to VOLATILE then raise an exception
|
|
|
|
|
dontAllowFunctionAlteredVolatile alteredFunctions
|
|
|
|
|
|
|
|
|
|
-- Propagate table changes to metadata
|
2022-12-05 13:20:47 +03:00
|
|
|
|
Diff.processTablesDiff source tableCache tablesDiff
|
2022-03-08 16:02:13 +03:00
|
|
|
|
|
|
|
|
|
pure (txResult, metadataUpdater)
|
|
|
|
|
where
|
|
|
|
|
dontAllowFunctionOverloading ::
|
|
|
|
|
MonadError QErr n =>
|
|
|
|
|
[FunctionName ('Postgres pgKind)] ->
|
|
|
|
|
n ()
|
|
|
|
|
dontAllowFunctionOverloading overloadedFunctions =
|
|
|
|
|
unless (null overloadedFunctions) $
|
|
|
|
|
throw400 NotSupported $
|
|
|
|
|
"the following tracked function(s) cannot be overloaded: "
|
|
|
|
|
<> commaSeparated overloadedFunctions
|
|
|
|
|
|
|
|
|
|
dontAllowFunctionAlteredVolatile ::
|
|
|
|
|
MonadError QErr n =>
|
|
|
|
|
[(FunctionName ('Postgres pgKind), FunctionVolatility)] ->
|
|
|
|
|
n ()
|
|
|
|
|
dontAllowFunctionAlteredVolatile alteredFunctions =
|
|
|
|
|
forM_ alteredFunctions $ \(qf, newTy) -> do
|
|
|
|
|
when (newTy == FTVOLATILE) $
|
|
|
|
|
throw400 NotSupported $
|
|
|
|
|
"type of function " <> qf <<> " is altered to \"VOLATILE\" which is not supported now"
|
|
|
|
|
|
|
|
|
|
purgeFunctionsFromMetadata ::
|
|
|
|
|
Monad n =>
|
|
|
|
|
[FunctionName ('Postgres pgKind)] ->
|
|
|
|
|
WriterT MetadataModifier n ()
|
|
|
|
|
purgeFunctionsFromMetadata functions =
|
|
|
|
|
for_ functions $ tell . dropFunctionInMetadata @('Postgres pgKind) source
|
|
|
|
|
|
|
|
|
|
collectFunctionsInDeps :: [SchemaObjId] -> [FunctionName ('Postgres pgKind)]
|
|
|
|
|
collectFunctionsInDeps deps =
|
|
|
|
|
flip mapMaybe deps \case
|
|
|
|
|
SOSourceObj _ objectID
|
|
|
|
|
| Just (SOIFunction qf) <- AB.unpackAnyBackend @('Postgres pgKind) objectID ->
|
|
|
|
|
Just qf
|
|
|
|
|
_ -> Nothing
|
|
|
|
|
|
|
|
|
|
-- | Fetch list of tables and functions with provided oids
|
|
|
|
|
fetchTablesFunctionsFromOids ::
|
|
|
|
|
(MonadIO m) =>
|
2022-12-05 13:20:47 +03:00
|
|
|
|
HashSet OID ->
|
|
|
|
|
HashSet OID ->
|
|
|
|
|
PG.TxET
|
|
|
|
|
QErr
|
|
|
|
|
m
|
|
|
|
|
( HS.HashSet (TableName ('Postgres pgKind)),
|
|
|
|
|
HS.HashSet (FunctionName ('Postgres pgKind))
|
|
|
|
|
)
|
2022-03-08 16:02:13 +03:00
|
|
|
|
fetchTablesFunctionsFromOids tableOids functionOids =
|
2022-09-21 21:40:41 +03:00
|
|
|
|
((PG.getViaJSON *** PG.getViaJSON) . PG.getRow)
|
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.withQE
|
2022-03-08 16:02:13 +03:00
|
|
|
|
defaultTxErrorHandler
|
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.sql|
|
2022-03-08 16:02:13 +03:00
|
|
|
|
SELECT
|
|
|
|
|
COALESCE(
|
|
|
|
|
( SELECT
|
|
|
|
|
json_agg(
|
|
|
|
|
row_to_json(
|
|
|
|
|
(
|
|
|
|
|
SELECT e
|
|
|
|
|
FROM ( SELECT "table".relname AS "name",
|
|
|
|
|
"schema".nspname AS "schema"
|
|
|
|
|
) AS e
|
|
|
|
|
)
|
|
|
|
|
)
|
|
|
|
|
) AS "item"
|
|
|
|
|
FROM jsonb_to_recordset($1::jsonb) AS oid_table("oid" int)
|
|
|
|
|
JOIN pg_catalog.pg_class "table" ON ("table".oid = "oid_table".oid)
|
|
|
|
|
JOIN pg_catalog.pg_namespace "schema" ON ("schema".oid = "table".relnamespace)
|
|
|
|
|
),
|
|
|
|
|
'[]'
|
|
|
|
|
) AS "tables",
|
|
|
|
|
|
|
|
|
|
COALESCE(
|
|
|
|
|
( SELECT
|
|
|
|
|
json_agg(
|
|
|
|
|
row_to_json(
|
|
|
|
|
(
|
|
|
|
|
SELECT e
|
|
|
|
|
FROM ( SELECT "function".proname AS "name",
|
|
|
|
|
"schema".nspname AS "schema"
|
|
|
|
|
) AS e
|
|
|
|
|
)
|
|
|
|
|
)
|
|
|
|
|
) AS "item"
|
|
|
|
|
FROM jsonb_to_recordset($2::jsonb) AS oid_table("oid" int)
|
|
|
|
|
JOIN pg_catalog.pg_proc "function" ON ("function".oid = "oid_table".oid)
|
|
|
|
|
JOIN pg_catalog.pg_namespace "schema" ON ("schema".oid = "function".pronamespace)
|
|
|
|
|
),
|
|
|
|
|
'[]'
|
|
|
|
|
) AS "functions"
|
|
|
|
|
|]
|
2022-12-05 13:20:47 +03:00
|
|
|
|
(PG.ViaJSON $ map mkOidObject $ HS.toList tableOids, PG.ViaJSON $ map mkOidObject $ HS.toList $ functionOids)
|
2022-03-08 16:02:13 +03:00
|
|
|
|
True
|
|
|
|
|
where
|
|
|
|
|
mkOidObject oid = object ["oid" .= oid]
|
|
|
|
|
|
|
|
|
|
------ helpers ------------
|
|
|
|
|
|
|
|
|
|
getComputedFields :: TableInfo ('Postgres pgKind) -> [ComputedFieldInfo ('Postgres pgKind)]
|
|
|
|
|
getComputedFields = getComputedFieldInfos . _tciFieldInfoMap . _tiCoreInfo
|
|
|
|
|
|
2022-12-05 13:20:47 +03:00
|
|
|
|
getComputedFieldFunctions :: TableInfo ('Postgres pgKind) -> HashSet (FunctionName ('Postgres pgKind))
|
|
|
|
|
getComputedFieldFunctions = HS.fromList . map (_cffName . _cfiFunction) . getComputedFields
|