graphql-engine/server/src-lib/Hasura/Backends/MSSQL/DDL/Source.hs

Ignoring revisions in .git-blame-ignore-revs. Click here to bypass and see the normal blame view.

171 lines
6.0 KiB
Haskell
Raw Normal View History

{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
-- | MSSQL Source
--
-- Implements the Source related methods of the
-- 'Hasura.RQL.Types.Metadata.Backend.BackendMetadata' type class
-- for the MSSQL backend, which provides an interface for identifying the
-- MSSQL database instance (source) and manipulate it.
--
-- The actual instance is defined in "Hasura.Backends.MSSQL.Instances.Metadata".
module Hasura.Backends.MSSQL.DDL.Source
( resolveSourceConfig,
resolveDatabaseMetadata,
postDropSourceHook,
prepareCatalog,
)
where
server/mssql: add cascade to mssql_run_sql <!-- Thank you for ss in the Title above ^ --> ## Description <!-- Please fill thier. --> <!-- Describe the changes from a user's perspective --> We don't have dependency reporting mechanism for `mssql_run_sql` API i.e when a database object (table, column etc.) is dropped through the API we should raise an exception if any dependencies (relationships, permissions etc.) with the database object exists in the metadata. This PR addresses the above mentioned problem by -> Integrating transaction to the API to rollback the SQL query execution if dependencies exists and exception is thrown -> Accepting `cascade` optional field in the API payload to drop the dependencies, if any -> Accepting `check_metadata_consistency` optional field to bypass (if value set to `false`) the dependency check ### Related Issues <!-- Please make surt title --> <!-- Add the issue number below (e.g. #234) --> Close #1853 ### Solution and Design <!-- How is this iss --> <!-- It's better if we elaborate --> The design/solution follows the `run_sql` API implementation for Postgres backend. ### Steps to test and verify <!-- If this is a fehis is a bug-fix, how do we verify the fix? --> - Create author - article tables and track them - Defined object and array relationships - Try to drop the article table without cascade or cascade set to `false` - The server should raise the relationship dependency exists exception ## Changelog - ✅ `CHANGELOG.md` is updated with user-facing content relevant to this PR. If no changelog is required, then add the `no-changelog-required` label. ## Affected components <!-- Remove non-affected components from the list --> - ✅ Server - ❎ Console - ❎ CLI - ❎ Docs - ❎ Community Content - ❎ Build System - ✅ Tests - ❎ Other (list it) PR-URL: https://github.com/hasura/graphql-engine-mono/pull/2636 GitOrigin-RevId: 0ab152295394056c4ca6f02923142a1658ad25dc
2021-10-22 17:49:15 +03:00
import Control.Monad.Trans.Control (MonadBaseControl)
import Data.Environment qualified as Env
import Data.FileEmbed (makeRelativeToProject)
import Database.MSSQL.Transaction
import Database.MSSQL.Transaction qualified as Tx
import Database.ODBC.SQLServer
import Database.ODBC.TH qualified as ODBC
import Hasura.Backends.MSSQL.Connection
import Hasura.Backends.MSSQL.DDL.EventTrigger
import Hasura.Backends.MSSQL.DDL.Source.Version
import Hasura.Backends.MSSQL.Meta
import Hasura.Backends.MSSQL.SQL.Error qualified as HGE
import Hasura.Backends.MSSQL.Types
import Hasura.Base.Error
import Hasura.Prelude
import Hasura.RQL.Types.Backend (BackendConfig)
import Hasura.RQL.Types.Common
import Hasura.RQL.Types.EventTrigger (RecreateEventTriggers (..))
import Hasura.RQL.Types.Source
import Hasura.RQL.Types.SourceCustomization
import Hasura.SQL.Backend
import Language.Haskell.TH.Lib qualified as TH
import Language.Haskell.TH.Syntax qualified as TH
import Text.Shakespeare.Text qualified as ST
resolveSourceConfig ::
(MonadIO m, MonadResolveSource m) =>
SourceName ->
MSSQLConnConfiguration ->
BackendSourceKind 'MSSQL ->
BackendConfig 'MSSQL ->
Env.Environment ->
m (Either QErr MSSQLSourceConfig)
resolveSourceConfig name config _backendKind _backendConfig _env = runExceptT do
sourceResolver <- getMSSQLSourceResolver
liftEitherM $ liftIO $ sourceResolver name config
resolveDatabaseMetadata ::
server/mssql: add cascade to mssql_run_sql <!-- Thank you for ss in the Title above ^ --> ## Description <!-- Please fill thier. --> <!-- Describe the changes from a user's perspective --> We don't have dependency reporting mechanism for `mssql_run_sql` API i.e when a database object (table, column etc.) is dropped through the API we should raise an exception if any dependencies (relationships, permissions etc.) with the database object exists in the metadata. This PR addresses the above mentioned problem by -> Integrating transaction to the API to rollback the SQL query execution if dependencies exists and exception is thrown -> Accepting `cascade` optional field in the API payload to drop the dependencies, if any -> Accepting `check_metadata_consistency` optional field to bypass (if value set to `false`) the dependency check ### Related Issues <!-- Please make surt title --> <!-- Add the issue number below (e.g. #234) --> Close #1853 ### Solution and Design <!-- How is this iss --> <!-- It's better if we elaborate --> The design/solution follows the `run_sql` API implementation for Postgres backend. ### Steps to test and verify <!-- If this is a fehis is a bug-fix, how do we verify the fix? --> - Create author - article tables and track them - Defined object and array relationships - Try to drop the article table without cascade or cascade set to `false` - The server should raise the relationship dependency exists exception ## Changelog - ✅ `CHANGELOG.md` is updated with user-facing content relevant to this PR. If no changelog is required, then add the `no-changelog-required` label. ## Affected components <!-- Remove non-affected components from the list --> - ✅ Server - ❎ Console - ❎ CLI - ❎ Docs - ❎ Community Content - ❎ Build System - ✅ Tests - ❎ Other (list it) PR-URL: https://github.com/hasura/graphql-engine-mono/pull/2636 GitOrigin-RevId: 0ab152295394056c4ca6f02923142a1658ad25dc
2021-10-22 17:49:15 +03:00
(MonadIO m, MonadBaseControl IO m) =>
MSSQLSourceConfig ->
SourceTypeCustomization ->
m (Either QErr (ResolvedSource 'MSSQL))
resolveDatabaseMetadata config customization = runExceptT do
dbTablesMetadata <- mssqlRunReadOnly mssqlExecCtx $ loadDBMetadata
pure $ ResolvedSource config customization dbTablesMetadata mempty mempty
where
MSSQLSourceConfig _connString mssqlExecCtx = config
postDropSourceHook ::
(MonadIO m, MonadBaseControl IO m) =>
MSSQLSourceConfig ->
m ()
postDropSourceHook (MSSQLSourceConfig _ mssqlExecCtx) = do
_ <- runExceptT $ mssqlRunReadWrite mssqlExecCtx dropSourceCatalog
-- Close the connection
liftIO $ mssqlDestroyConn mssqlExecCtx
doesSchemaExist :: MonadMSSQLTx m => SchemaName -> m Bool
doesSchemaExist (SchemaName schemaName) = do
liftMSSQLTx $
Tx.singleRowQueryE
HGE.defaultMSSQLTxErrorHandler
[ODBC.sql|
SELECT CAST (
CASE
WHEN EXISTS( SELECT 1 FROM sys.schemas WHERE name = $schemaName )
THEN 1
ELSE 0
END
AS BIT)
|]
doesTableExist :: MonadMSSQLTx m => TableName -> m Bool
doesTableExist tableName = do
liftMSSQLTx $
Tx.singleRowQueryE
HGE.defaultMSSQLTxErrorHandler
[ODBC.sql|
SELECT CAST (
CASE
WHEN (Select OBJECT_ID($qualifiedTable)) IS NOT NULL
THEN 1
ELSE 0
END
AS BIT)
|]
where
qualifiedTable = qualifyTableName tableName
-- | Initialise catalog tables for a source, including those required by the event delivery subsystem.
prepareCatalog ::
(MonadIO m, MonadBaseControl IO m) =>
MSSQLSourceConfig ->
ExceptT QErr m RecreateEventTriggers
prepareCatalog sourceConfig = mssqlRunReadWrite (_mscExecCtx sourceConfig) do
hdbCatalogExist <- doesSchemaExist "hdb_catalog"
eventLogTableExist <- doesTableExist $ TableName "event_log" "hdb_catalog"
sourceVersionTableExist <- doesTableExist $ TableName "hdb_source_catalog_version" "hdb_catalog"
if
-- Fresh database
| not hdbCatalogExist -> liftMSSQLTx do
unitQueryE HGE.defaultMSSQLTxErrorHandler "CREATE SCHEMA hdb_catalog"
initSourceCatalog
return RETDoNothing
-- Only 'hdb_catalog' schema defined
| not sourceVersionTableExist && not eventLogTableExist -> do
liftMSSQLTx initSourceCatalog
return RETDoNothing
| otherwise -> migrateSourceCatalog
where
initSourceCatalog = do
unitQueryE HGE.defaultMSSQLTxErrorHandler $(makeRelativeToProject "src-rsr/mssql/init_mssql_source.sql" >>= ODBC.sqlFile)
setSourceCatalogVersion latestSourceCatalogVersion
dropSourceCatalog :: MonadMSSQLTx m => m ()
dropSourceCatalog = do
let sql = $(makeRelativeToProject "src-rsr/mssql/drop_mssql_source.sql" >>= ODBC.sqlFile)
liftMSSQLTx $ unitQueryE HGE.defaultMSSQLTxErrorHandler sql
migrateSourceCatalog :: MonadMSSQLTx m => m RecreateEventTriggers
migrateSourceCatalog =
getSourceCatalogVersion >>= migrateSourceCatalogFrom
migrateSourceCatalogFrom :: MonadMSSQLTx m => Int -> m RecreateEventTriggers
migrateSourceCatalogFrom prevVersion
| prevVersion == latestSourceCatalogVersion = pure RETDoNothing
| [] <- neededMigrations =
throw400 NotSupported $
"Expected source catalog version <= "
<> latestSourceCatalogVersionText
<> ", but the current version is "
<> (tshow prevVersion)
| otherwise = do
liftMSSQLTx $ traverse_ snd neededMigrations
setSourceCatalogVersion latestSourceCatalogVersion
pure RETRecreate
where
neededMigrations =
dropWhile ((/= prevVersion) . fst) sourceMigrations
sourceMigrations :: [(Int, TxE QErr ())]
sourceMigrations =
$( let migrationFromFile from =
let to = from + 1
path = "src-rsr/mssql_source_migrations/" <> show from <> "_to_" <> show to <> ".sql"
in [|multiRowQueryE defaultTxErrorHandler $(makeRelativeToProject path >>= ST.stextFile)|]
migrationsFromFile = map $ \(from :: Int) ->
[|($(TH.lift $ from), $(migrationFromFile from))|]
in TH.listE $ migrationsFromFile [1 .. (latestSourceCatalogVersion - 1)]
)