mirror of
https://github.com/hasura/graphql-engine.git
synced 2024-12-17 12:31:52 +03:00
8e88e73a52
<!-- 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
188 lines
6.2 KiB
Haskell
188 lines
6.2 KiB
Haskell
module Hasura.RQL.DDL.Schema.Source where
|
|
|
|
import Control.Lens (at, (.~), (^.))
|
|
import Control.Monad.Trans.Control (MonadBaseControl)
|
|
import Data.Aeson
|
|
import Data.Aeson qualified as J
|
|
import Data.Aeson.TH
|
|
import Data.Has
|
|
import Data.HashMap.Strict qualified as HM
|
|
import Data.HashMap.Strict.InsOrd qualified as OMap
|
|
import Data.Text.Extended
|
|
import Hasura.Base.Error
|
|
import Hasura.EncJSON
|
|
import Hasura.Logging qualified as L
|
|
import Hasura.Prelude
|
|
import Hasura.RQL.Types
|
|
import Hasura.SQL.AnyBackend qualified as AB
|
|
import Hasura.Server.Logging (MetadataLog (..))
|
|
|
|
--------------------------------------------------------------------------------
|
|
-- Add source
|
|
|
|
data AddSource b = AddSource
|
|
{ _asName :: !SourceName,
|
|
_asConfiguration :: !(SourceConnConfiguration b),
|
|
_asReplaceConfiguration :: !Bool
|
|
}
|
|
|
|
instance (Backend b) => FromJSON (AddSource b) where
|
|
parseJSON = withObject "AddSource" $ \o ->
|
|
AddSource
|
|
<$> o .: "name"
|
|
<*> o .: "configuration"
|
|
<*> o .:? "replace_configuration" .!= False
|
|
|
|
runAddSource ::
|
|
forall m b.
|
|
(MonadError QErr m, CacheRWM m, MetadataM m, BackendMetadata b) =>
|
|
AddSource b ->
|
|
m EncJSON
|
|
runAddSource (AddSource name sourceConfig replaceConfiguration) = do
|
|
sources <- scSources <$> askSchemaCache
|
|
|
|
metadataModifier <-
|
|
MetadataModifier
|
|
<$> if HM.member name sources
|
|
then
|
|
if replaceConfiguration
|
|
then pure $ metaSources . ix name . toSourceMetadata @b . smConfiguration .~ sourceConfig
|
|
else throw400 AlreadyExists $ "source with name " <> name <<> " already exists"
|
|
else do
|
|
let sourceMetadata = mkSourceMetadata @b name sourceConfig
|
|
pure $ metaSources %~ OMap.insert name sourceMetadata
|
|
|
|
buildSchemaCacheFor (MOSource name) metadataModifier
|
|
pure successMsg
|
|
|
|
--------------------------------------------------------------------------------
|
|
-- Rename source
|
|
|
|
data RenameSource = RenameSource
|
|
{ _rmName :: !SourceName,
|
|
_rmNewName :: !SourceName
|
|
}
|
|
|
|
$(deriveFromJSON hasuraJSON ''RenameSource)
|
|
|
|
runRenameSource ::
|
|
forall m.
|
|
(MonadError QErr m, CacheRWM m, MetadataM m) =>
|
|
RenameSource ->
|
|
m EncJSON
|
|
runRenameSource RenameSource {..} = do
|
|
sources <- scSources <$> askSchemaCache
|
|
|
|
unless (HM.member _rmName sources) $
|
|
throw400 NotExists $ "Could not find source with name " <>> _rmName
|
|
|
|
when (HM.member _rmNewName sources) $
|
|
throw400 AlreadyExists $ "Source with name " <> _rmNewName <<> " already exists"
|
|
|
|
let metadataModifier =
|
|
MetadataModifier $
|
|
metaSources %~ renameBackendSourceMetadata _rmName _rmNewName
|
|
buildSchemaCacheFor (MOSource _rmNewName) metadataModifier
|
|
|
|
pure successMsg
|
|
where
|
|
renameBackendSourceMetadata ::
|
|
SourceName ->
|
|
SourceName ->
|
|
OMap.InsOrdHashMap SourceName BackendSourceMetadata ->
|
|
OMap.InsOrdHashMap SourceName BackendSourceMetadata
|
|
renameBackendSourceMetadata oldKey newKey m =
|
|
case OMap.lookup oldKey m of
|
|
Just val ->
|
|
OMap.insert
|
|
newKey
|
|
(AB.mapBackend val (renameSource newKey))
|
|
. OMap.delete oldKey
|
|
$ m
|
|
Nothing -> m
|
|
|
|
renameSource :: forall b. SourceName -> SourceMetadata b -> SourceMetadata b
|
|
renameSource newName metadata = metadata {_smName = newName}
|
|
|
|
--------------------------------------------------------------------------------
|
|
-- Drop source
|
|
|
|
data DropSource = DropSource
|
|
{ _dsName :: !SourceName,
|
|
_dsCascade :: !Bool
|
|
}
|
|
deriving (Show, Eq)
|
|
|
|
instance FromJSON DropSource where
|
|
parseJSON = withObject "DropSource" $ \o ->
|
|
DropSource <$> o .: "name" <*> o .:? "cascade" .!= False
|
|
|
|
runDropSource ::
|
|
forall m r.
|
|
( MonadError QErr m,
|
|
CacheRWM m,
|
|
MonadIO m,
|
|
MonadBaseControl IO m,
|
|
MetadataM m,
|
|
MonadReader r m,
|
|
Has (L.Logger L.Hasura) r
|
|
) =>
|
|
DropSource ->
|
|
m EncJSON
|
|
runDropSource (DropSource name cascade) = do
|
|
sc <- askSchemaCache
|
|
logger <- asks getter
|
|
let sources = scSources sc
|
|
case HM.lookup name sources of
|
|
Just backendSourceInfo ->
|
|
AB.dispatchAnyBackend @BackendMetadata backendSourceInfo $ dropSource logger sc
|
|
Nothing -> do
|
|
metadata <- getMetadata
|
|
void $
|
|
onNothing (metadata ^. metaSources . at name) $
|
|
throw400 NotExists $ "source with name " <> name <<> " does not exist"
|
|
if cascade
|
|
then -- Without sourceInfo we can't cascade, so throw an error
|
|
throw400 Unexpected $ "source with name " <> name <<> " is inconsistent"
|
|
else -- Drop source from metadata
|
|
buildSchemaCacheFor (MOSource name) dropSourceMetadataModifier
|
|
pure successMsg
|
|
where
|
|
dropSource :: forall b. (BackendMetadata b) => L.Logger L.Hasura -> SchemaCache -> SourceInfo b -> m ()
|
|
dropSource logger sc sourceInfo = do
|
|
let sourceConfig = _siConfiguration sourceInfo
|
|
let indirectDeps =
|
|
mapMaybe getIndirectDep $
|
|
getDependentObjs sc (SOSource name)
|
|
|
|
when (not cascade && indirectDeps /= []) $
|
|
reportDependentObjectsExist (map (SOSourceObj name . AB.mkAnyBackend) indirectDeps)
|
|
|
|
metadataModifier <- execWriterT $ do
|
|
mapM_ (purgeDependentObject name >=> tell) indirectDeps
|
|
tell dropSourceMetadataModifier
|
|
|
|
buildSchemaCacheFor (MOSource name) metadataModifier
|
|
|
|
-- We only log errors that arise from 'postDropSourceHook' here, and not
|
|
-- surface them as end-user errors. See comment
|
|
-- https://github.com/hasura/graphql-engine/issues/7092#issuecomment-873845282
|
|
runExceptT (postDropSourceHook @b sourceConfig) >>= either logDropSourceHookError pure
|
|
where
|
|
logDropSourceHookError err =
|
|
let msg =
|
|
"Error executing cleanup actions after removing source '" <> toTxt name
|
|
<> "'. Consider cleaning up tables in hdb_catalog schema manually."
|
|
in L.unLogger logger $ MetadataLog L.LevelWarn msg (J.toJSON err)
|
|
|
|
getIndirectDep :: SchemaObjId -> Maybe (SourceObjId b)
|
|
getIndirectDep = \case
|
|
SOSourceObj s o ->
|
|
if s == name
|
|
then Nothing
|
|
else -- consider only *this* backend specific dependencies
|
|
AB.unpackAnyBackend o
|
|
_ -> Nothing
|
|
|
|
dropSourceMetadataModifier = MetadataModifier $ metaSources %~ OMap.delete name
|