2022-03-16 03:39:21 +03:00
|
|
|
|
{-# LANGUAGE TemplateHaskell #-}
|
|
|
|
|
|
2019-10-21 19:01:05 +03:00
|
|
|
|
-- | Migrations for the Hasura catalog.
|
|
|
|
|
--
|
|
|
|
|
-- To add a new migration:
|
|
|
|
|
--
|
2020-02-24 17:33:56 +03:00
|
|
|
|
-- 1. Bump the catalog version number in @src-rsr/catalog_version.txt@.
|
2019-10-21 19:01:05 +03:00
|
|
|
|
-- 2. Add a migration script in the @src-rsr/migrations/@ directory with the name
|
|
|
|
|
-- @<old version>_to_<new version>.sql@.
|
2020-02-07 14:03:12 +03:00
|
|
|
|
-- 3. Create a downgrade script in the @src-rsr/migrations/@ directory with the name
|
|
|
|
|
-- @<new version>_to_<old version>.sql@.
|
|
|
|
|
-- 4. If making a new release, add the mapping from application version to catalog
|
2020-03-26 23:42:33 +03:00
|
|
|
|
-- schema version in @src-rsr/catalog_versions.txt@.
|
2020-03-27 07:50:45 +03:00
|
|
|
|
-- 5. If appropriate, add the change to @server/src-rsr/initialise.sql@ for fresh installations
|
|
|
|
|
-- of hasura.
|
2019-10-21 19:01:05 +03:00
|
|
|
|
--
|
|
|
|
|
-- The Template Haskell code in this module will automatically compile the new migration script into
|
|
|
|
|
-- the @graphql-engine@ executable.
|
2021-11-03 17:20:25 +03:00
|
|
|
|
--
|
|
|
|
|
-- NOTE: Please have a look at the `server/documentation/migration-guidelines.md` before adding any new migration
|
|
|
|
|
-- if you haven't already looked at it
|
2019-10-21 19:01:05 +03:00
|
|
|
|
module Hasura.Server.Migrate
|
|
|
|
|
( MigrationResult (..),
|
|
|
|
|
migrateCatalog,
|
|
|
|
|
latestCatalogVersion,
|
2020-02-07 14:03:12 +03:00
|
|
|
|
downgradeCatalog,
|
2019-10-21 19:01:05 +03:00
|
|
|
|
)
|
|
|
|
|
where
|
|
|
|
|
|
2020-12-28 15:56:00 +03:00
|
|
|
|
import Control.Monad.Trans.Control (MonadBaseControl)
|
2020-12-08 17:22:31 +03:00
|
|
|
|
import Data.Aeson qualified as A
|
2021-03-16 20:35:35 +03:00
|
|
|
|
import Data.FileEmbed (makeRelativeToProject)
|
2020-12-28 15:56:00 +03:00
|
|
|
|
import Data.HashMap.Strict.InsOrd qualified as OMap
|
2021-01-07 12:04:22 +03:00
|
|
|
|
import Data.Text qualified as T
|
2020-12-08 17:22:31 +03:00
|
|
|
|
import Data.Text.IO qualified as TIO
|
|
|
|
|
import Data.Time.Clock (UTCTime)
|
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
|
|
|
|
|
import Hasura.Backends.Postgres.Execute.Types
|
2020-10-27 16:53:49 +03:00
|
|
|
|
import Hasura.Backends.Postgres.SQL.Types
|
2021-05-11 18:18:31 +03:00
|
|
|
|
import Hasura.Base.Error
|
2020-12-08 17:22:31 +03:00
|
|
|
|
import Hasura.Logging (Hasura, LogLevel (..), ToEngineLog (..))
|
2019-10-21 19:01:05 +03:00
|
|
|
|
import Hasura.Prelude
|
2019-11-27 01:49:42 +03:00
|
|
|
|
import Hasura.RQL.DDL.Schema
|
2020-12-08 17:22:31 +03:00
|
|
|
|
import Hasura.RQL.DDL.Schema.LegacyCatalog
|
2022-04-27 16:57:28 +03:00
|
|
|
|
import Hasura.RQL.Types.ApiLimit
|
|
|
|
|
import Hasura.RQL.Types.Backend
|
|
|
|
|
import Hasura.RQL.Types.Common
|
|
|
|
|
import Hasura.RQL.Types.CustomTypes
|
|
|
|
|
import Hasura.RQL.Types.Metadata
|
|
|
|
|
import Hasura.RQL.Types.Network
|
2022-11-07 09:54:49 +03:00
|
|
|
|
import Hasura.RQL.Types.OpenTelemetry (emptyOpenTelemetryConfig)
|
2022-04-27 16:57:28 +03:00
|
|
|
|
import Hasura.RQL.Types.SourceCustomization
|
2020-12-08 17:22:31 +03:00
|
|
|
|
import Hasura.SQL.AnyBackend qualified as AB
|
2022-04-27 16:57:28 +03:00
|
|
|
|
import Hasura.SQL.Backend
|
2022-08-05 03:28:49 +03:00
|
|
|
|
import Hasura.Server.Init (DowngradeOptions (..), databaseUrlOption, _envVar)
|
2020-12-08 17:22:31 +03:00
|
|
|
|
import Hasura.Server.Logging (StartupLog (..))
|
2021-02-22 17:59:13 +03:00
|
|
|
|
import Hasura.Server.Migrate.Internal
|
2022-06-29 11:18:32 +03:00
|
|
|
|
import Hasura.Server.Migrate.LatestVersion
|
2020-12-08 17:22:31 +03:00
|
|
|
|
import Hasura.Server.Migrate.Version
|
2021-02-18 19:46:14 +03:00
|
|
|
|
import Hasura.Server.Types (MaintenanceMode (..))
|
2020-12-08 17:22:31 +03:00
|
|
|
|
import Language.Haskell.TH.Lib qualified as TH
|
|
|
|
|
import Language.Haskell.TH.Syntax qualified as TH
|
|
|
|
|
import System.Directory (doesFileExist)
|
2019-10-21 19:01:05 +03:00
|
|
|
|
|
|
|
|
|
data MigrationResult
|
|
|
|
|
= MRNothingToDo
|
|
|
|
|
| MRInitialized
|
2020-10-27 16:53:49 +03:00
|
|
|
|
| -- | old catalog version
|
|
|
|
|
MRMigrated Text
|
2021-02-18 19:46:14 +03:00
|
|
|
|
| MRMaintanenceMode
|
2019-10-21 19:01:05 +03:00
|
|
|
|
deriving (Show, Eq)
|
|
|
|
|
|
2019-11-26 15:14:21 +03:00
|
|
|
|
instance ToEngineLog MigrationResult Hasura where
|
2019-10-21 19:01:05 +03:00
|
|
|
|
toEngineLog result =
|
|
|
|
|
toEngineLog $
|
|
|
|
|
StartupLog
|
|
|
|
|
{ slLogLevel = LevelInfo,
|
2020-08-05 13:23:14 +03:00
|
|
|
|
slKind = "catalog_migrate",
|
2019-10-21 19:01:05 +03:00
|
|
|
|
slInfo = A.toJSON $ case result of
|
|
|
|
|
MRNothingToDo ->
|
|
|
|
|
"Already at the latest catalog version ("
|
|
|
|
|
<> latestCatalogVersionString
|
|
|
|
|
<> "); nothing to do."
|
|
|
|
|
MRInitialized ->
|
|
|
|
|
"Successfully initialized the catalog (at version " <> latestCatalogVersionString <> ")."
|
|
|
|
|
MRMigrated oldVersion ->
|
|
|
|
|
"Successfully migrated from catalog version "
|
|
|
|
|
<> oldVersion
|
|
|
|
|
<> " to version "
|
|
|
|
|
<> latestCatalogVersionString
|
|
|
|
|
<> "."
|
2021-02-18 19:46:14 +03:00
|
|
|
|
MRMaintanenceMode ->
|
|
|
|
|
"Catalog migrations are skipped because the graphql-engine is in maintenance mode"
|
2019-10-21 19:01:05 +03:00
|
|
|
|
}
|
|
|
|
|
|
2020-02-07 14:03:12 +03:00
|
|
|
|
-- A migration and (hopefully) also its inverse if we have it.
|
2020-05-13 15:33:16 +03:00
|
|
|
|
-- Polymorphic because `m` can be any `MonadTx`, `MonadIO` when
|
2020-02-07 14:03:12 +03:00
|
|
|
|
-- used in the `migrations` function below.
|
|
|
|
|
data MigrationPair m = MigrationPair
|
|
|
|
|
{ mpMigrate :: m (),
|
2020-10-27 16:53:49 +03:00
|
|
|
|
mpDown :: Maybe (m ())
|
2020-02-07 14:03:12 +03:00
|
|
|
|
}
|
|
|
|
|
|
2019-10-21 19:01:05 +03:00
|
|
|
|
migrateCatalog ::
|
2019-11-20 21:21:30 +03:00
|
|
|
|
forall m.
|
2020-12-28 15:56:00 +03:00
|
|
|
|
( MonadTx m,
|
2020-01-23 00:55:55 +03:00
|
|
|
|
MonadIO m,
|
2020-12-28 15:56:00 +03:00
|
|
|
|
MonadBaseControl IO m
|
2019-11-20 21:21:30 +03:00
|
|
|
|
) =>
|
2021-04-22 00:44:37 +03:00
|
|
|
|
Maybe (SourceConnConfiguration ('Postgres 'Vanilla)) ->
|
2022-08-09 14:42:12 +03:00
|
|
|
|
ExtensionsSchema ->
|
2022-04-28 23:55:13 +03:00
|
|
|
|
MaintenanceMode () ->
|
2020-07-14 22:00:58 +03:00
|
|
|
|
UTCTime ->
|
2020-12-28 15:56:00 +03:00
|
|
|
|
m (MigrationResult, Metadata)
|
2022-08-09 14:42:12 +03:00
|
|
|
|
migrateCatalog maybeDefaultSourceConfig extensionsSchema maintenanceMode migrationTime = do
|
2021-02-18 19:46:14 +03:00
|
|
|
|
catalogSchemaExists <- doesSchemaExist (SchemaName "hdb_catalog")
|
|
|
|
|
versionTableExists <- doesTableExist (SchemaName "hdb_catalog") (TableName "hdb_version")
|
2021-04-21 13:55:18 +03:00
|
|
|
|
metadataTableExists <- doesTableExist (SchemaName "hdb_catalog") (TableName "hdb_metadata")
|
2021-02-18 19:46:14 +03:00
|
|
|
|
migrationResult <-
|
|
|
|
|
if
|
2022-04-28 23:55:13 +03:00
|
|
|
|
| maintenanceMode == (MaintenanceModeEnabled ()) -> do
|
2021-02-18 19:46:14 +03:00
|
|
|
|
if
|
|
|
|
|
| not catalogSchemaExists ->
|
|
|
|
|
throw500 "unexpected: hdb_catalog schema not found in maintenance mode"
|
|
|
|
|
| not versionTableExists ->
|
|
|
|
|
throw500 "unexpected: hdb_catalog.hdb_version table not found in maintenance mode"
|
2021-04-21 13:55:18 +03:00
|
|
|
|
| not metadataTableExists ->
|
|
|
|
|
throw500 $
|
|
|
|
|
"the \"hdb_catalog.hdb_metadata\" table is expected to exist and contain"
|
|
|
|
|
<> " the metadata of the graphql-engine"
|
2021-02-18 19:46:14 +03:00
|
|
|
|
| otherwise -> pure MRMaintanenceMode
|
|
|
|
|
| otherwise -> case catalogSchemaExists of
|
|
|
|
|
False -> initialize True
|
|
|
|
|
True -> case versionTableExists of
|
|
|
|
|
False -> initialize False
|
2021-04-21 13:55:18 +03:00
|
|
|
|
True -> migrateFrom =<< liftTx getCatalogVersion
|
2021-02-19 11:46:12 +03:00
|
|
|
|
metadata <- liftTx fetchMetadataFromCatalog
|
2020-12-28 15:56:00 +03:00
|
|
|
|
pure (migrationResult, metadata)
|
2019-10-21 19:01:05 +03:00
|
|
|
|
where
|
|
|
|
|
-- initializes the catalog, creating the schema if necessary
|
2020-12-14 07:30:19 +03:00
|
|
|
|
initialize :: Bool -> m MigrationResult
|
2019-10-21 19:01:05 +03:00
|
|
|
|
initialize createSchema = do
|
|
|
|
|
liftTx $
|
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.catchE defaultTxErrorHandler $
|
|
|
|
|
when createSchema $
|
|
|
|
|
PG.unitQ "CREATE SCHEMA hdb_catalog" () False
|
2022-08-09 14:42:12 +03:00
|
|
|
|
enablePgcryptoExtension extensionsSchema
|
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
|
|
|
|
multiQ $(makeRelativeToProject "src-rsr/initialise.sql" >>= PG.sqlFromFile)
|
2019-10-21 19:01:05 +03:00
|
|
|
|
updateCatalogVersion
|
2021-01-07 12:04:22 +03:00
|
|
|
|
|
|
|
|
|
let emptyMetadata' = case maybeDefaultSourceConfig of
|
|
|
|
|
Nothing -> emptyMetadata
|
|
|
|
|
Just defaultSourceConfig ->
|
|
|
|
|
-- insert metadata with default source
|
2021-03-15 16:02:58 +03:00
|
|
|
|
let defaultSourceMetadata =
|
|
|
|
|
AB.mkAnyBackend $
|
2022-08-10 12:40:57 +03:00
|
|
|
|
SourceMetadata
|
|
|
|
|
@('Postgres 'Vanilla)
|
|
|
|
|
defaultSource
|
|
|
|
|
PostgresVanillaKind
|
|
|
|
|
mempty
|
|
|
|
|
mempty
|
|
|
|
|
defaultSourceConfig
|
|
|
|
|
Nothing
|
|
|
|
|
emptySourceCustomization
|
2022-09-02 09:33:21 +03:00
|
|
|
|
Nothing
|
2022-08-29 03:58:03 +03:00
|
|
|
|
sources = OMap.singleton defaultSource $ BackendSourceMetadata defaultSourceMetadata
|
2021-01-07 12:04:22 +03:00
|
|
|
|
in emptyMetadata {_metaSources = sources}
|
|
|
|
|
|
2021-02-19 11:46:12 +03:00
|
|
|
|
liftTx $ insertMetadataInCatalog emptyMetadata'
|
2020-12-14 07:30:19 +03:00
|
|
|
|
pure MRInitialized
|
2019-10-21 19:01:05 +03:00
|
|
|
|
|
|
|
|
|
-- migrates an existing catalog to the latest version from an existing verion
|
2022-07-04 12:30:53 +03:00
|
|
|
|
migrateFrom :: MetadataCatalogVersion -> m MigrationResult
|
2019-10-21 19:01:05 +03:00
|
|
|
|
migrateFrom previousVersion
|
2022-06-29 11:18:32 +03:00
|
|
|
|
| previousVersion == latestCatalogVersion = pure MRNothingToDo
|
2019-11-20 21:21:30 +03:00
|
|
|
|
| otherwise = do
|
2021-11-03 17:20:25 +03:00
|
|
|
|
let upMigrations = migrations maybeDefaultSourceConfig False maintenanceMode
|
|
|
|
|
case neededMigrations previousVersion upMigrations of
|
|
|
|
|
[] ->
|
|
|
|
|
throw400 NotSupported $
|
|
|
|
|
"Cannot use database previously used with a newer version of graphql-engine (expected"
|
|
|
|
|
<> " a catalog version <="
|
|
|
|
|
<> latestCatalogVersionString
|
|
|
|
|
<> ", but the current version"
|
|
|
|
|
<> " is "
|
2022-06-29 11:18:32 +03:00
|
|
|
|
<> tshow previousVersion
|
2021-11-03 17:20:25 +03:00
|
|
|
|
<> ")."
|
|
|
|
|
migrationsToBeApplied -> do
|
|
|
|
|
traverse_ (mpMigrate . snd) migrationsToBeApplied
|
|
|
|
|
updateCatalogVersion
|
2022-06-29 11:18:32 +03:00
|
|
|
|
pure . MRMigrated $ tshow previousVersion
|
2019-10-21 19:01:05 +03:00
|
|
|
|
where
|
2021-11-03 17:20:25 +03:00
|
|
|
|
neededMigrations prevVersion upMigrations =
|
|
|
|
|
dropWhile ((< prevVersion) . fst) upMigrations
|
2020-05-13 15:33:16 +03:00
|
|
|
|
|
2020-06-19 09:42:32 +03:00
|
|
|
|
updateCatalogVersion = setCatalogVersion latestCatalogVersionString migrationTime
|
|
|
|
|
|
2020-12-08 17:22:31 +03:00
|
|
|
|
downgradeCatalog ::
|
|
|
|
|
forall m.
|
|
|
|
|
(MonadIO m, MonadTx m) =>
|
2021-04-22 00:44:37 +03:00
|
|
|
|
Maybe (SourceConnConfiguration ('Postgres 'Vanilla)) ->
|
2021-02-14 09:07:52 +03:00
|
|
|
|
DowngradeOptions ->
|
|
|
|
|
UTCTime ->
|
|
|
|
|
m MigrationResult
|
2020-12-28 15:56:00 +03:00
|
|
|
|
downgradeCatalog defaultSourceConfig opts time = do
|
2021-11-03 17:20:25 +03:00
|
|
|
|
currentCatalogVersion <- liftTx getCatalogVersion
|
2022-07-04 12:30:53 +03:00
|
|
|
|
targetVersionFloat :: MetadataCatalogVersion <-
|
2021-11-03 17:20:25 +03:00
|
|
|
|
onLeft (readEither (T.unpack $ dgoTargetVersion opts)) $ \err ->
|
|
|
|
|
throw500 $ "Unexpected: couldn't convert " <> dgoTargetVersion opts <> " to a float, error: " <> tshow err
|
|
|
|
|
downgradeFrom currentCatalogVersion targetVersionFloat
|
2020-02-07 14:03:12 +03:00
|
|
|
|
where
|
|
|
|
|
-- downgrades an existing catalog to the specified version
|
2022-07-04 12:30:53 +03:00
|
|
|
|
downgradeFrom :: MetadataCatalogVersion -> MetadataCatalogVersion -> m MigrationResult
|
2021-11-03 17:20:25 +03:00
|
|
|
|
downgradeFrom previousVersion targetVersion
|
|
|
|
|
| previousVersion == targetVersion = pure MRNothingToDo
|
2020-05-13 15:33:16 +03:00
|
|
|
|
| otherwise =
|
2021-11-03 17:20:25 +03:00
|
|
|
|
case neededDownMigrations targetVersion of
|
2020-05-13 15:33:16 +03:00
|
|
|
|
Left reason ->
|
2020-02-07 14:03:12 +03:00
|
|
|
|
throw400 NotSupported $
|
|
|
|
|
"This downgrade path (from "
|
2021-11-03 17:20:25 +03:00
|
|
|
|
<> tshow previousVersion
|
2020-05-13 15:33:16 +03:00
|
|
|
|
<> " to "
|
|
|
|
|
<> dgoTargetVersion opts
|
2020-02-07 14:03:12 +03:00
|
|
|
|
<> ") is not supported, because "
|
|
|
|
|
<> reason
|
|
|
|
|
Right path -> do
|
2020-05-13 15:33:16 +03:00
|
|
|
|
sequence_ path
|
2020-03-05 08:42:38 +03:00
|
|
|
|
unless (dgoDryRun opts) do
|
|
|
|
|
setCatalogVersion (dgoTargetVersion opts) time
|
2021-11-03 17:20:25 +03:00
|
|
|
|
pure (MRMigrated (dgoTargetVersion opts))
|
2020-02-07 14:03:12 +03:00
|
|
|
|
where
|
2020-05-13 15:33:16 +03:00
|
|
|
|
neededDownMigrations newVersion =
|
|
|
|
|
downgrade
|
|
|
|
|
previousVersion
|
|
|
|
|
newVersion
|
2021-02-18 19:46:14 +03:00
|
|
|
|
(reverse (migrations defaultSourceConfig (dgoDryRun opts) MaintenanceModeDisabled))
|
2020-02-07 14:03:12 +03:00
|
|
|
|
|
2020-05-13 15:33:16 +03:00
|
|
|
|
downgrade ::
|
2022-07-04 12:30:53 +03:00
|
|
|
|
MetadataCatalogVersion ->
|
|
|
|
|
MetadataCatalogVersion ->
|
|
|
|
|
[(MetadataCatalogVersion, MigrationPair m)] ->
|
2020-10-27 16:53:49 +03:00
|
|
|
|
Either Text [m ()]
|
2020-02-07 14:03:12 +03:00
|
|
|
|
downgrade lower upper = skipFutureDowngrades
|
|
|
|
|
where
|
|
|
|
|
-- We find the list of downgrade scripts to run by first
|
|
|
|
|
-- dropping any downgrades which correspond to newer versions
|
|
|
|
|
-- of the schema than the one we're running currently.
|
|
|
|
|
-- Then we take migrations as needed until we reach the target
|
|
|
|
|
-- version, dropping any remaining migrations from the end of the
|
|
|
|
|
-- (reversed) list.
|
2022-07-04 12:30:53 +03:00
|
|
|
|
skipFutureDowngrades, dropOlderDowngrades :: [(MetadataCatalogVersion, MigrationPair m)] -> Either Text [m ()]
|
2020-02-07 14:03:12 +03:00
|
|
|
|
skipFutureDowngrades xs | previousVersion == lower = dropOlderDowngrades xs
|
|
|
|
|
skipFutureDowngrades [] = Left "the starting version is unrecognized."
|
|
|
|
|
skipFutureDowngrades ((x, _) : xs)
|
|
|
|
|
| x == lower = dropOlderDowngrades xs
|
|
|
|
|
| otherwise = skipFutureDowngrades xs
|
|
|
|
|
|
|
|
|
|
dropOlderDowngrades [] = Left "the target version is unrecognized."
|
2020-05-13 15:33:16 +03:00
|
|
|
|
dropOlderDowngrades ((x, MigrationPair {mpDown = Nothing}) : _) =
|
2021-11-03 17:20:25 +03:00
|
|
|
|
Left $ "there is no available migration back to version " <> tshow x <> "."
|
2020-02-07 14:03:12 +03:00
|
|
|
|
dropOlderDowngrades ((x, MigrationPair {mpDown = Just y}) : xs)
|
|
|
|
|
| x == upper = Right [y]
|
|
|
|
|
| otherwise = (y :) <$> dropOlderDowngrades xs
|
|
|
|
|
|
2020-12-08 17:22:31 +03:00
|
|
|
|
migrations ::
|
|
|
|
|
forall m.
|
|
|
|
|
(MonadIO m, MonadTx m) =>
|
2021-04-22 00:44:37 +03:00
|
|
|
|
Maybe (SourceConnConfiguration ('Postgres 'Vanilla)) ->
|
|
|
|
|
Bool ->
|
2022-04-28 23:55:13 +03:00
|
|
|
|
MaintenanceMode () ->
|
2022-07-04 12:30:53 +03:00
|
|
|
|
[(MetadataCatalogVersion, MigrationPair m)]
|
2021-02-18 19:46:14 +03:00
|
|
|
|
migrations maybeDefaultSourceConfig dryRun maintenanceMode =
|
2020-02-07 14:03:12 +03:00
|
|
|
|
-- We need to build the list of migrations at compile-time so that we can compile the SQL
|
|
|
|
|
-- directly into the executable using `Q.sqlFromFile`. The GHC stage restriction makes
|
|
|
|
|
-- doing this a little bit awkward (we can’t use any definitions in this module at
|
|
|
|
|
-- compile-time), but putting a `let` inside the splice itself is allowed.
|
|
|
|
|
$( let migrationFromFile from to =
|
|
|
|
|
let path = "src-rsr/migrations/" <> from <> "_to_" <> to <> ".sql"
|
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
|
|
|
|
in [|runTxOrPrint $(makeRelativeToProject path >>= PG.sqlFromFile)|]
|
2020-02-07 14:03:12 +03:00
|
|
|
|
migrationFromFileMaybe from to = do
|
2021-03-16 20:35:35 +03:00
|
|
|
|
path <- makeRelativeToProject $ "src-rsr/migrations/" <> from <> "_to_" <> to <> ".sql"
|
2020-02-07 14:03:12 +03:00
|
|
|
|
exists <- TH.runIO (doesFileExist path)
|
|
|
|
|
if exists
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
then [|Just (runTxOrPrint $(PG.sqlFromFile path))|]
|
2020-02-07 14:03:12 +03:00
|
|
|
|
else [|Nothing|]
|
2020-05-13 15:33:16 +03:00
|
|
|
|
|
2022-07-04 12:30:53 +03:00
|
|
|
|
migrationsFromFile = map $ \(to :: MetadataCatalogVersion) ->
|
2022-06-29 11:18:32 +03:00
|
|
|
|
let from = pred to
|
2020-12-08 17:22:31 +03:00
|
|
|
|
in [|
|
2021-11-03 17:20:25 +03:00
|
|
|
|
( $(TH.lift from),
|
2020-02-07 14:03:12 +03:00
|
|
|
|
MigrationPair
|
2022-06-29 11:18:32 +03:00
|
|
|
|
$(migrationFromFile (show from) (show to))
|
|
|
|
|
$(migrationFromFileMaybe (show to) (show from))
|
2020-02-07 14:03:12 +03:00
|
|
|
|
)
|
|
|
|
|
|]
|
|
|
|
|
in TH.listE
|
|
|
|
|
-- version 0.8 is the only non-integral catalog version
|
2021-11-03 17:20:25 +03:00
|
|
|
|
-- The 40_to_41 migration is consciously omitted from below because its contents
|
|
|
|
|
-- have been moved to the `0_to_1.sql` because the `40_to_41` migration only contained
|
|
|
|
|
-- source catalog changes and we'd like to keep source catalog migrations in a different
|
|
|
|
|
-- path than metadata catalog migrations.
|
2020-10-28 19:40:33 +03:00
|
|
|
|
$
|
2022-07-04 12:30:53 +03:00
|
|
|
|
[|(MetadataCatalogVersion08, MigrationPair $(migrationFromFile "08" "1") Nothing)|]
|
|
|
|
|
: migrationsFromFile [MetadataCatalogVersion 2 .. MetadataCatalogVersion 3]
|
|
|
|
|
++ [|(MetadataCatalogVersion 3, MigrationPair from3To4 Nothing)|]
|
|
|
|
|
: (migrationsFromFile [MetadataCatalogVersion 5 .. MetadataCatalogVersion 40] ++ migrationsFromFile [MetadataCatalogVersion 42])
|
|
|
|
|
++ [|(MetadataCatalogVersion 42, MigrationPair from42To43 (Just from43To42))|]
|
|
|
|
|
: migrationsFromFile [MetadataCatalogVersion 44 .. latestCatalogVersion]
|
2020-12-08 17:22:31 +03:00
|
|
|
|
)
|
2020-02-07 14:03: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
|
|
|
|
runTxOrPrint :: PG.Query -> m ()
|
2020-02-07 14:03:12 +03:00
|
|
|
|
runTxOrPrint
|
2020-05-13 15:33:16 +03:00
|
|
|
|
| dryRun =
|
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
|
|
|
|
liftIO . TIO.putStrLn . PG.getQueryText
|
2021-09-15 23:45:49 +03:00
|
|
|
|
| otherwise = multiQ
|
2020-02-07 14:03:12 +03:00
|
|
|
|
|
2020-12-08 17:22:31 +03:00
|
|
|
|
from42To43 = do
|
2022-04-28 23:55:13 +03:00
|
|
|
|
when (maintenanceMode == MaintenanceModeEnabled ()) $
|
2021-02-18 19:46:14 +03:00
|
|
|
|
throw500 "cannot migrate to catalog version 43 in maintenance mode"
|
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 query = $(makeRelativeToProject "src-rsr/migrations/42_to_43.sql" >>= PG.sqlFromFile)
|
2020-12-08 17:22:31 +03:00
|
|
|
|
if dryRun
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
then (liftIO . TIO.putStrLn . PG.getQueryText) query
|
2020-12-08 17:22:31 +03:00
|
|
|
|
else do
|
2020-12-28 15:56:00 +03:00
|
|
|
|
metadataV2 <- fetchMetadataFromHdbTables
|
2021-09-15 23:45:49 +03:00
|
|
|
|
multiQ query
|
2021-01-07 12:04:22 +03:00
|
|
|
|
defaultSourceConfig <-
|
|
|
|
|
onNothing maybeDefaultSourceConfig $
|
|
|
|
|
throw400 NotSupported $
|
2022-08-05 03:28:49 +03:00
|
|
|
|
"cannot migrate to catalog version 43 without --database-url or env var " <> tshow (_envVar databaseUrlOption)
|
2020-12-28 15:56:00 +03:00
|
|
|
|
let metadataV3 =
|
|
|
|
|
let MetadataNoSources {..} = metadataV2
|
2021-03-15 16:02:58 +03:00
|
|
|
|
defaultSourceMetadata =
|
2022-08-29 03:58:03 +03:00
|
|
|
|
BackendSourceMetadata $
|
|
|
|
|
AB.mkAnyBackend $
|
2022-09-02 09:33:21 +03:00
|
|
|
|
SourceMetadata defaultSource PostgresVanillaKind _mnsTables _mnsFunctions defaultSourceConfig Nothing emptySourceCustomization Nothing
|
2020-12-28 15:56:00 +03:00
|
|
|
|
in Metadata
|
|
|
|
|
(OMap.singleton defaultSource defaultSourceMetadata)
|
2021-01-29 04:02:34 +03:00
|
|
|
|
_mnsRemoteSchemas
|
|
|
|
|
_mnsQueryCollections
|
|
|
|
|
_mnsAllowlist
|
|
|
|
|
_mnsCustomTypes
|
|
|
|
|
_mnsActions
|
|
|
|
|
_mnsCronTriggers
|
|
|
|
|
mempty
|
2021-09-23 15:37:56 +03:00
|
|
|
|
emptyApiLimit
|
|
|
|
|
emptyMetricsConfig
|
|
|
|
|
mempty
|
|
|
|
|
mempty
|
|
|
|
|
emptyNetwork
|
2022-04-29 05:13:13 +03:00
|
|
|
|
mempty
|
2022-11-07 09:54:49 +03:00
|
|
|
|
emptyOpenTelemetryConfig
|
2021-02-19 11:46:12 +03:00
|
|
|
|
liftTx $ insertMetadataInCatalog metadataV3
|
2020-01-14 10:09:10 +03:00
|
|
|
|
|
2020-12-08 17:22:31 +03:00
|
|
|
|
from43To42 = do
|
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 query = $(makeRelativeToProject "src-rsr/migrations/43_to_42.sql" >>= PG.sqlFromFile)
|
2020-12-08 17:22:31 +03:00
|
|
|
|
if dryRun
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
then (liftIO . TIO.putStrLn . PG.getQueryText) query
|
2020-12-08 17:22:31 +03:00
|
|
|
|
else do
|
2021-02-19 11:46:12 +03:00
|
|
|
|
Metadata {..} <- liftTx fetchMetadataFromCatalog
|
2021-09-15 23:45:49 +03:00
|
|
|
|
multiQ query
|
2021-02-14 09:07:52 +03:00
|
|
|
|
let emptyMetadataNoSources =
|
|
|
|
|
MetadataNoSources mempty mempty mempty mempty mempty emptyCustomTypes mempty mempty
|
2020-12-28 15:56:00 +03:00
|
|
|
|
metadataV2 <- case OMap.toList _metaSources of
|
2021-02-14 09:07:52 +03:00
|
|
|
|
[] -> pure emptyMetadataNoSources
|
2022-08-29 03:58:03 +03:00
|
|
|
|
[(_, BackendSourceMetadata exists)] ->
|
2021-03-15 16:02:58 +03:00
|
|
|
|
pure $ case AB.unpackAnyBackend exists of
|
2021-02-14 09:07:52 +03:00
|
|
|
|
Nothing -> emptyMetadataNoSources
|
|
|
|
|
Just SourceMetadata {..} ->
|
|
|
|
|
MetadataNoSources
|
|
|
|
|
_smTables
|
|
|
|
|
_smFunctions
|
|
|
|
|
_metaRemoteSchemas
|
|
|
|
|
_metaQueryCollections
|
|
|
|
|
_metaAllowlist
|
|
|
|
|
_metaCustomTypes
|
|
|
|
|
_metaActions
|
|
|
|
|
_metaCronTriggers
|
2020-12-28 15:56:00 +03:00
|
|
|
|
_ -> throw400 NotSupported "Cannot downgrade since there are more than one source"
|
2021-08-17 10:01:14 +03:00
|
|
|
|
liftTx $ do
|
2022-04-22 19:01:07 +03:00
|
|
|
|
flip runReaderT (SystemDefined False) $ saveMetadataToHdbTables metadataV2
|
2021-08-17 10:01:14 +03:00
|
|
|
|
-- when the graphql-engine is migrated from v1 to v2, we drop the foreign key
|
|
|
|
|
-- constraint of the `hdb_catalog.hdb_cron_event` table because the cron triggers
|
|
|
|
|
-- in v2 are saved in the `hdb_catalog.hdb_metadata` table. So, when a downgrade
|
|
|
|
|
-- happens, we need to delay adding the foreign key constraint until the
|
|
|
|
|
-- cron triggers are added in the `hdb_catalog.hdb_cron_triggers`
|
|
|
|
|
addCronTriggerForeignKeyConstraint
|
2020-12-08 17:22:31 +03:00
|
|
|
|
recreateSystemMetadata
|
2021-09-15 23:45:49 +03:00
|
|
|
|
|
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
|
|
|
|
multiQ :: (MonadTx m) => PG.Query -> m ()
|
|
|
|
|
multiQ = liftTx . PG.multiQE defaultTxErrorHandler
|