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.
|
|
|
|
|
module Hasura.Server.Migrate
|
|
|
|
|
( MigrationResult(..)
|
2021-01-07 12:04:22 +03:00
|
|
|
|
, getMigratedFrom
|
2019-10-21 19:01:05 +03:00
|
|
|
|
, migrateCatalog
|
|
|
|
|
, latestCatalogVersion
|
2020-02-07 14:03:12 +03:00
|
|
|
|
, downgradeCatalog
|
2019-10-21 19:01:05 +03:00
|
|
|
|
) where
|
|
|
|
|
|
|
|
|
|
import Hasura.Prelude
|
|
|
|
|
|
2020-12-08 17:22:31 +03:00
|
|
|
|
import qualified Data.Aeson as A
|
2020-12-28 15:56:00 +03:00
|
|
|
|
import qualified Data.HashMap.Strict.InsOrd as OMap
|
2021-01-07 12:04:22 +03:00
|
|
|
|
import qualified Data.Text as T
|
2020-12-08 17:22:31 +03:00
|
|
|
|
import qualified Data.Text.IO as TIO
|
|
|
|
|
import qualified Database.PG.Query as Q
|
|
|
|
|
import qualified Language.Haskell.TH.Lib as TH
|
|
|
|
|
import qualified Language.Haskell.TH.Syntax as TH
|
2019-10-21 19:01:05 +03:00
|
|
|
|
|
2020-12-28 15:56:00 +03:00
|
|
|
|
import Control.Monad.Trans.Control (MonadBaseControl)
|
2021-03-16 20:35:35 +03:00
|
|
|
|
import Data.FileEmbed (makeRelativeToProject)
|
2020-12-08 17:22:31 +03:00
|
|
|
|
import Data.Time.Clock (UTCTime)
|
|
|
|
|
import System.Directory (doesFileExist)
|
2020-10-27 16:53:49 +03:00
|
|
|
|
|
2021-03-15 16:02:58 +03:00
|
|
|
|
import qualified Hasura.SQL.AnyBackend as AB
|
|
|
|
|
|
2020-10-27 16:53:49 +03:00
|
|
|
|
import Hasura.Backends.Postgres.SQL.Types
|
2020-12-08 17:22:31 +03:00
|
|
|
|
import Hasura.Logging (Hasura, LogLevel (..), ToEngineLog (..))
|
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
|
2019-10-21 19:01:05 +03:00
|
|
|
|
import Hasura.RQL.Types
|
2021-01-07 12:04:22 +03:00
|
|
|
|
import Hasura.Server.Init (DowngradeOptions (..), databaseUrlEnv)
|
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
|
2020-12-08 17:22:31 +03:00
|
|
|
|
import Hasura.Server.Migrate.Version (latestCatalogVersion,
|
|
|
|
|
latestCatalogVersionString)
|
2021-02-18 19:46:14 +03:00
|
|
|
|
import Hasura.Server.Types (MaintenanceMode (..))
|
2019-10-21 19:01:05 +03:00
|
|
|
|
|
|
|
|
|
data MigrationResult
|
|
|
|
|
= MRNothingToDo
|
|
|
|
|
| MRInitialized
|
2020-10-27 16:53:49 +03:00
|
|
|
|
| MRMigrated Text -- ^ old catalog version
|
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
|
|
|
|
}
|
|
|
|
|
|
2021-01-07 12:04:22 +03:00
|
|
|
|
getMigratedFrom
|
|
|
|
|
:: MigrationResult
|
|
|
|
|
-> Maybe Float -- ^ We have version 0.8 as non integral catalog version
|
|
|
|
|
getMigratedFrom = \case
|
2021-02-18 19:46:14 +03:00
|
|
|
|
MRNothingToDo -> Nothing
|
|
|
|
|
MRInitialized -> Nothing
|
|
|
|
|
MRMigrated t -> readMaybe (T.unpack t)
|
|
|
|
|
MRMaintanenceMode -> Nothing
|
2021-01-07 12:04:22 +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))
|
2021-02-18 19:46:14 +03:00
|
|
|
|
-> MaintenanceMode
|
2020-07-14 22:00:58 +03:00
|
|
|
|
-> UTCTime
|
2020-12-28 15:56:00 +03:00
|
|
|
|
-> m (MigrationResult, Metadata)
|
2021-02-18 19:46:14 +03:00
|
|
|
|
migrateCatalog maybeDefaultSourceConfig maintenanceMode migrationTime = do
|
|
|
|
|
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 | maintenanceMode == MaintenanceModeEnabled -> do
|
|
|
|
|
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 $ Q.catchE defaultTxErrorHandler $
|
2020-11-12 12:25:48 +03:00
|
|
|
|
when createSchema $ Q.unitQ "CREATE SCHEMA hdb_catalog" () False
|
2020-12-28 15:56:00 +03:00
|
|
|
|
enablePgcryptoExtension
|
2021-03-16 20:35:35 +03:00
|
|
|
|
runTx $(makeRelativeToProject "src-rsr/initialise.sql" >>= Q.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 $
|
2021-04-22 00:44:37 +03:00
|
|
|
|
SourceMetadata @('Postgres 'Vanilla) defaultSource mempty mempty defaultSourceConfig
|
2021-01-07 12:04:22 +03:00
|
|
|
|
sources = OMap.singleton defaultSource defaultSourceMetadata
|
|
|
|
|
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
|
2020-12-14 07:30:19 +03:00
|
|
|
|
migrateFrom :: Text -> m MigrationResult
|
2019-10-21 19:01:05 +03:00
|
|
|
|
migrateFrom previousVersion
|
2020-12-14 07:30:19 +03:00
|
|
|
|
| previousVersion == latestCatalogVersionString = pure MRNothingToDo
|
2020-02-07 14:03:12 +03:00
|
|
|
|
| [] <- neededMigrations =
|
|
|
|
|
throw400 NotSupported $
|
|
|
|
|
"Cannot use database previously used with a newer version of graphql-engine (expected"
|
|
|
|
|
<> " a catalog version <=" <> latestCatalogVersionString <> ", but the current version"
|
|
|
|
|
<> " is " <> previousVersion <> ")."
|
2019-11-20 21:21:30 +03:00
|
|
|
|
| otherwise = do
|
2020-02-07 14:03:12 +03:00
|
|
|
|
traverse_ (mpMigrate . snd) neededMigrations
|
2019-11-20 21:21:30 +03:00
|
|
|
|
updateCatalogVersion
|
2020-12-14 07:30:19 +03:00
|
|
|
|
pure $ MRMigrated previousVersion
|
2019-10-21 19:01:05 +03:00
|
|
|
|
where
|
2020-12-08 17:22:31 +03:00
|
|
|
|
neededMigrations =
|
2021-02-18 19:46:14 +03:00
|
|
|
|
dropWhile ((/= previousVersion) . fst) (migrations maybeDefaultSourceConfig False maintenanceMode)
|
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-04-21 13:55:18 +03:00
|
|
|
|
downgradeFrom =<< liftTx getCatalogVersion
|
2020-02-07 14:03:12 +03:00
|
|
|
|
where
|
|
|
|
|
-- downgrades an existing catalog to the specified version
|
2020-10-27 16:53:49 +03:00
|
|
|
|
downgradeFrom :: Text -> m MigrationResult
|
2020-02-07 14:03:12 +03:00
|
|
|
|
downgradeFrom previousVersion
|
|
|
|
|
| previousVersion == dgoTargetVersion opts = do
|
|
|
|
|
pure MRNothingToDo
|
2020-05-13 15:33:16 +03:00
|
|
|
|
| otherwise =
|
2020-02-07 14:03:12 +03:00
|
|
|
|
case neededDownMigrations (dgoTargetVersion opts) 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 "
|
2020-05-13 15:33:16 +03:00
|
|
|
|
<> previousVersion <> " 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
|
2020-02-07 14:03:12 +03:00
|
|
|
|
pure (MRMigrated previousVersion)
|
2020-05-13 15:33:16 +03:00
|
|
|
|
|
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
|
2020-10-27 16:53:49 +03:00
|
|
|
|
:: Text
|
|
|
|
|
-> Text
|
|
|
|
|
-> [(Text, MigrationPair m)]
|
|
|
|
|
-> 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.
|
2020-10-27 16:53:49 +03:00
|
|
|
|
skipFutureDowngrades, dropOlderDowngrades :: [(Text, 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 }):_) =
|
2020-02-07 14:03:12 +03:00
|
|
|
|
Left $ "there is no available migration back to version " <> x <> "."
|
|
|
|
|
dropOlderDowngrades ((x, MigrationPair{ mpDown = Just y }):xs)
|
|
|
|
|
| x == upper = Right [y]
|
|
|
|
|
| otherwise = (y:) <$> dropOlderDowngrades xs
|
|
|
|
|
|
|
|
|
|
setCatalogVersion :: MonadTx m => Text -> UTCTime -> m ()
|
|
|
|
|
setCatalogVersion ver time = liftTx $ Q.unitQE defaultTxErrorHandler [Q.sql|
|
|
|
|
|
INSERT INTO hdb_catalog.hdb_version (version, upgraded_on) VALUES ($1, $2)
|
|
|
|
|
ON CONFLICT ((version IS NOT NULL))
|
|
|
|
|
DO UPDATE SET version = $1, upgraded_on = $2
|
|
|
|
|
|] (ver, time) False
|
|
|
|
|
|
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 -> MaintenanceMode -> [(Text, 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"
|
2021-03-16 20:35:35 +03:00
|
|
|
|
in [| runTxOrPrint $(makeRelativeToProject path >>= Q.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
|
|
|
|
|
then [| Just (runTxOrPrint $(Q.sqlFromFile path)) |]
|
|
|
|
|
else [| Nothing |]
|
2020-05-13 15:33:16 +03:00
|
|
|
|
|
2020-02-07 14:03:12 +03:00
|
|
|
|
migrationsFromFile = map $ \(to :: Integer) ->
|
|
|
|
|
let from = to - 1
|
2020-12-08 17:22:31 +03:00
|
|
|
|
in [| ( $(TH.lift $ tshow from)
|
2020-02-07 14:03:12 +03:00
|
|
|
|
, MigrationPair
|
|
|
|
|
$(migrationFromFile (show from) (show to))
|
|
|
|
|
$(migrationFromFileMaybe (show to) (show from))
|
|
|
|
|
) |]
|
|
|
|
|
in TH.listE
|
|
|
|
|
-- version 0.8 is the only non-integral catalog version
|
2020-10-28 19:40:33 +03:00
|
|
|
|
$ [| ("0.8", MigrationPair $(migrationFromFile "08" "1") Nothing) |]
|
2020-02-07 14:03:12 +03:00
|
|
|
|
: migrationsFromFile [2..3]
|
2020-10-28 19:40:33 +03:00
|
|
|
|
++ [| ("3", MigrationPair from3To4 Nothing) |]
|
2020-12-08 17:22:31 +03:00
|
|
|
|
: migrationsFromFile [5..42]
|
2021-02-19 05:39:30 +03:00
|
|
|
|
++ [| ("42", MigrationPair from42To43 (Just from43To42)) |]
|
2021-04-21 09:48:21 +03:00
|
|
|
|
: migrationsFromFile [44..46]
|
2020-12-08 17:22:31 +03:00
|
|
|
|
)
|
2020-02-07 14:03:12 +03:00
|
|
|
|
where
|
|
|
|
|
runTxOrPrint :: Q.Query -> m ()
|
|
|
|
|
runTxOrPrint
|
2020-05-13 15:33:16 +03:00
|
|
|
|
| dryRun =
|
2020-02-07 14:03:12 +03:00
|
|
|
|
liftIO . TIO.putStrLn . Q.getQueryText
|
|
|
|
|
| otherwise = runTx
|
|
|
|
|
|
2020-12-08 17:22:31 +03:00
|
|
|
|
from42To43 = do
|
2021-02-18 19:46:14 +03:00
|
|
|
|
when (maintenanceMode == MaintenanceModeEnabled) $
|
|
|
|
|
throw500 "cannot migrate to catalog version 43 in maintenance mode"
|
2021-03-16 20:35:35 +03:00
|
|
|
|
let query = $(makeRelativeToProject "src-rsr/migrations/42_to_43.sql" >>= Q.sqlFromFile)
|
2020-12-08 17:22:31 +03:00
|
|
|
|
if dryRun then (liftIO . TIO.putStrLn . Q.getQueryText) query
|
|
|
|
|
else do
|
2020-12-28 15:56:00 +03:00
|
|
|
|
metadataV2 <- fetchMetadataFromHdbTables
|
2020-12-08 17:22:31 +03:00
|
|
|
|
runTx query
|
2021-01-07 12:04:22 +03:00
|
|
|
|
defaultSourceConfig <- onNothing maybeDefaultSourceConfig $ throw400 NotSupported $
|
|
|
|
|
"cannot migrate to catalog version 43 without --database-url or env var " <> tshow (fst databaseUrlEnv)
|
2020-12-28 15:56:00 +03:00
|
|
|
|
let metadataV3 =
|
|
|
|
|
let MetadataNoSources{..} = metadataV2
|
2021-03-15 16:02:58 +03:00
|
|
|
|
defaultSourceMetadata = AB.mkAnyBackend $
|
2020-12-28 15:56:00 +03:00
|
|
|
|
SourceMetadata defaultSource _mnsTables _mnsFunctions defaultSourceConfig
|
|
|
|
|
in Metadata (OMap.singleton defaultSource defaultSourceMetadata)
|
2021-01-29 04:02:34 +03:00
|
|
|
|
_mnsRemoteSchemas _mnsQueryCollections _mnsAllowlist _mnsCustomTypes _mnsActions _mnsCronTriggers mempty
|
[Preview] Inherited roles for postgres read queries
fixes #3868
docker image - `hasura/graphql-engine:inherited-roles-preview-48b73a2de`
Note:
To be able to use the inherited roles feature, the graphql-engine should be started with the env variable `HASURA_GRAPHQL_EXPERIMENTAL_FEATURES` set to `inherited_roles`.
Introduction
------------
This PR implements the idea of multiple roles as presented in this [paper](https://www.microsoft.com/en-us/research/wp-content/uploads/2016/02/FGALanguageICDE07.pdf). The multiple roles feature in this PR can be used via inherited roles. An inherited role is a role which can be created by combining multiple singular roles. For example, if there are two roles `author` and `editor` configured in the graphql-engine, then we can create a inherited role with the name of `combined_author_editor` role which will combine the select permissions of the `author` and `editor` roles and then make GraphQL queries using the `combined_author_editor`.
How are select permissions of different roles are combined?
------------------------------------------------------------
A select permission includes 5 things:
1. Columns accessible to the role
2. Row selection filter
3. Limit
4. Allow aggregation
5. Scalar computed fields accessible to the role
Suppose there are two roles, `role1` gives access to the `address` column with row filter `P1` and `role2` gives access to both the `address` and the `phone` column with row filter `P2` and we create a new role `combined_roles` which combines `role1` and `role2`.
Let's say the following GraphQL query is queried with the `combined_roles` role.
```graphql
query {
employees {
address
phone
}
}
```
This will translate to the following SQL query:
```sql
select
(case when (P1 or P2) then address else null end) as address,
(case when P2 then phone else null end) as phone
from employee
where (P1 or P2)
```
The other parameters of the select permission will be combined in the following manner:
1. Limit - Minimum of the limits will be the limit of the inherited role
2. Allow aggregations - If any of the role allows aggregation, then the inherited role will allow aggregation
3. Scalar computed fields - same as table column fields, as in the above example
APIs for inherited roles:
----------------------
1. `add_inherited_role`
`add_inherited_role` is the [metadata API](https://hasura.io/docs/1.0/graphql/core/api-reference/index.html#schema-metadata-api) to create a new inherited role. It accepts two arguments
`role_name`: the name of the inherited role to be added (String)
`role_set`: list of roles that need to be combined (Array of Strings)
Example:
```json
{
"type": "add_inherited_role",
"args": {
"role_name":"combined_user",
"role_set":[
"user",
"user1"
]
}
}
```
After adding the inherited role, the inherited role can be used like single roles like earlier
Note:
An inherited role can only be created with non-inherited/singular roles.
2. `drop_inherited_role`
The `drop_inherited_role` API accepts the name of the inherited role and drops it from the metadata. It accepts a single argument:
`role_name`: name of the inherited role to be dropped
Example:
```json
{
"type": "drop_inherited_role",
"args": {
"role_name":"combined_user"
}
}
```
Metadata
---------
The derived roles metadata will be included under the `experimental_features` key while exporting the metadata.
```json
{
"experimental_features": {
"derived_roles": [
{
"role_name": "manager_is_employee_too",
"role_set": [
"employee",
"manager"
]
}
]
}
}
```
Scope
------
Only postgres queries and subscriptions are supported in this PR.
Important points:
-----------------
1. All columns exposed to an inherited role will be marked as `nullable`, this is done so that cell value nullification can be done.
TODOs
-------
- [ ] Tests
- [ ] Test a GraphQL query running with a inherited role without enabling inherited roles in experimental features
- [] Tests for aggregate queries, limit, computed fields, functions, subscriptions (?)
- [ ] Introspection test with a inherited role (nullability changes in a inherited role)
- [ ] Docs
- [ ] Changelog
Co-authored-by: Vamshi Surabhi <6562944+0x777@users.noreply.github.com>
GitOrigin-RevId: 3b8ee1e11f5ceca80fe294f8c074d42fbccfec63
2021-03-08 14:14:13 +03:00
|
|
|
|
emptyApiLimit emptyMetricsConfig mempty
|
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
|
2021-03-16 20:35:35 +03:00
|
|
|
|
let query = $(makeRelativeToProject "src-rsr/migrations/43_to_42.sql" >>= Q.sqlFromFile)
|
2020-12-08 17:22:31 +03:00
|
|
|
|
if dryRun then (liftIO . TIO.putStrLn . Q.getQueryText) query
|
|
|
|
|
else do
|
2021-02-19 11:46:12 +03:00
|
|
|
|
Metadata{..} <- liftTx fetchMetadataFromCatalog
|
2020-12-08 17:22:31 +03:00
|
|
|
|
runTx 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
|
2021-03-15 16:02:58 +03:00
|
|
|
|
[(_, exists)] ->
|
|
|
|
|
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"
|
|
|
|
|
liftTx $ runHasSystemDefinedT (SystemDefined False) $ saveMetadataToHdbTables metadataV2
|
2020-12-08 17:22:31 +03:00
|
|
|
|
recreateSystemMetadata
|