2021-05-27 18:06:13 +03:00
|
|
|
module Hasura.RQL.DDL.Schema.Diff where
|
2018-06-27 16:11:32 +03:00
|
|
|
|
2018-08-10 15:44:44 +03:00
|
|
|
import Hasura.Prelude
|
2018-06-27 16:11:32 +03:00
|
|
|
|
2020-10-27 16:53:49 +03:00
|
|
|
import qualified Data.HashMap.Strict as M
|
2021-05-27 18:06:13 +03:00
|
|
|
import qualified Data.HashMap.Strict.InsOrd as OMap
|
2020-10-27 16:53:49 +03:00
|
|
|
import qualified Data.HashSet as HS
|
|
|
|
import qualified Data.List.NonEmpty as NE
|
2021-05-27 18:06:13 +03:00
|
|
|
import qualified Language.GraphQL.Draft.Syntax as G
|
2018-06-27 16:11:32 +03:00
|
|
|
|
2021-05-27 18:06:13 +03:00
|
|
|
import Control.Lens ((.~))
|
|
|
|
import Data.Aeson
|
|
|
|
import Data.List.Extended
|
|
|
|
import Data.Text.Extended
|
2021-03-15 16:02:58 +03:00
|
|
|
|
|
|
|
import qualified Hasura.SQL.AnyBackend as AB
|
2018-06-27 16:11:32 +03:00
|
|
|
|
2021-05-27 18:06:13 +03:00
|
|
|
import Hasura.Backends.Postgres.SQL.Types hiding (ConstraintName, FunctionName, TableName)
|
2021-05-11 18:18:31 +03:00
|
|
|
import Hasura.Base.Error
|
2021-05-27 18:06:13 +03:00
|
|
|
import Hasura.RQL.DDL.Schema.Rename
|
|
|
|
import Hasura.RQL.DDL.Schema.Table
|
|
|
|
import Hasura.RQL.Types hiding (fmFunction, tmComputedFields, tmTable)
|
2018-06-27 16:11:32 +03:00
|
|
|
|
2021-05-11 18:18:31 +03:00
|
|
|
|
2021-05-27 18:06:13 +03:00
|
|
|
data FunctionMeta b
|
2019-10-18 11:29:47 +03:00
|
|
|
= FunctionMeta
|
2019-12-09 07:18:53 +03:00
|
|
|
{ fmOid :: !OID
|
2021-05-27 18:06:13 +03:00
|
|
|
, fmFunction :: !(FunctionName b)
|
2020-11-18 21:04:57 +03:00
|
|
|
, fmType :: !FunctionVolatility
|
2021-05-27 18:06:13 +03:00
|
|
|
} deriving (Generic)
|
|
|
|
deriving instance (Backend b) => Show (FunctionMeta b)
|
|
|
|
deriving instance (Backend b) => Eq (FunctionMeta b)
|
|
|
|
|
|
|
|
instance (Backend b) => FromJSON (FunctionMeta b) where
|
|
|
|
parseJSON = genericParseJSON hasuraJSON
|
|
|
|
instance (Backend b) => ToJSON (FunctionMeta b) where
|
|
|
|
toJSON = genericToJSON hasuraJSON
|
2019-10-18 11:29:47 +03:00
|
|
|
|
2021-05-27 18:06:13 +03:00
|
|
|
data ComputedFieldMeta b
|
2019-10-18 11:29:47 +03:00
|
|
|
= ComputedFieldMeta
|
|
|
|
{ ccmName :: !ComputedFieldName
|
2021-05-27 18:06:13 +03:00
|
|
|
, ccmFunctionMeta :: !(FunctionMeta b)
|
|
|
|
} deriving (Generic, Show, Eq)
|
|
|
|
|
|
|
|
instance (Backend b) => FromJSON (ComputedFieldMeta b) where
|
|
|
|
parseJSON = genericParseJSON hasuraJSON{omitNothingFields=True}
|
|
|
|
instance (Backend b) => ToJSON (ComputedFieldMeta b) where
|
|
|
|
toJSON = genericToJSON hasuraJSON{omitNothingFields=True}
|
2019-10-18 11:29:47 +03:00
|
|
|
|
2020-12-17 14:37:16 +03:00
|
|
|
data TableMeta (b :: BackendType)
|
2018-06-27 16:11:32 +03:00
|
|
|
= TableMeta
|
2021-05-27 18:06:13 +03:00
|
|
|
{ tmTable :: !(TableName b)
|
2020-12-17 14:37:16 +03:00
|
|
|
, tmInfo :: !(DBTableMetadata b)
|
2021-05-27 18:06:13 +03:00
|
|
|
, tmComputedFields :: ![ComputedFieldMeta b]
|
2020-12-08 17:22:31 +03:00
|
|
|
} deriving (Show, Eq)
|
|
|
|
|
2021-05-27 18:06:13 +03:00
|
|
|
data ComputedFieldDiff (b :: BackendType)
|
2019-10-18 11:29:47 +03:00
|
|
|
= ComputedFieldDiff
|
|
|
|
{ _cfdDropped :: [ComputedFieldName]
|
2021-05-27 18:06:13 +03:00
|
|
|
, _cfdAltered :: [(ComputedFieldMeta b, ComputedFieldMeta b)]
|
|
|
|
, _cfdOverloaded :: [(ComputedFieldName, FunctionName b)]
|
|
|
|
}
|
|
|
|
deriving instance (Backend b) => Show (ComputedFieldDiff b)
|
|
|
|
deriving instance (Backend b) => Eq (ComputedFieldDiff b)
|
2019-10-18 11:29:47 +03:00
|
|
|
|
2020-11-12 12:25:48 +03:00
|
|
|
data TableDiff (b :: BackendType)
|
2018-06-27 16:11:32 +03:00
|
|
|
= TableDiff
|
2021-05-27 18:06:13 +03:00
|
|
|
{ _tdNewName :: !(Maybe (TableName b))
|
2020-10-22 23:42:27 +03:00
|
|
|
, _tdDroppedCols :: ![Column b]
|
|
|
|
, _tdAlteredCols :: ![(RawColumnInfo b, RawColumnInfo b)]
|
2021-05-27 18:06:13 +03:00
|
|
|
, _tdDroppedFKeyCons :: ![ConstraintName b]
|
|
|
|
, _tdComputedFields :: !(ComputedFieldDiff b)
|
2019-01-03 06:58:12 +03:00
|
|
|
-- The final list of uniq/primary constraint names
|
|
|
|
-- used for generating types on_conflict clauses
|
|
|
|
-- TODO: this ideally should't be part of TableDiff
|
2021-05-27 18:06:13 +03:00
|
|
|
, _tdUniqOrPriCons :: ![ConstraintName b]
|
2019-09-17 04:51:11 +03:00
|
|
|
, _tdNewDescription :: !(Maybe PGDescription)
|
2020-10-22 23:42:27 +03:00
|
|
|
}
|
2018-06-27 16:11:32 +03:00
|
|
|
|
2021-05-27 18:06:13 +03:00
|
|
|
getTableDiff
|
|
|
|
:: Backend b
|
|
|
|
=> TableMeta b
|
|
|
|
-> TableMeta b
|
|
|
|
-> TableDiff b
|
2018-06-27 16:11:32 +03:00
|
|
|
getTableDiff oldtm newtm =
|
2021-05-27 18:06:13 +03:00
|
|
|
TableDiff mNewName droppedCols alteredCols
|
2019-11-07 17:39:48 +03:00
|
|
|
droppedFKeyConstraints computedFieldDiff uniqueOrPrimaryCons mNewDesc
|
2018-06-27 16:11:32 +03:00
|
|
|
where
|
|
|
|
mNewName = bool (Just $ tmTable newtm) Nothing $ tmTable oldtm == tmTable newtm
|
2020-12-08 17:22:31 +03:00
|
|
|
oldCols = _ptmiColumns $ tmInfo oldtm
|
|
|
|
newCols = _ptmiColumns $ tmInfo newtm
|
2019-09-17 04:51:11 +03:00
|
|
|
|
2019-12-09 07:18:53 +03:00
|
|
|
uniqueOrPrimaryCons = map _cName $
|
2020-12-08 17:22:31 +03:00
|
|
|
maybeToList (_pkConstraint <$> _ptmiPrimaryKey (tmInfo newtm))
|
|
|
|
<> toList (_ptmiUniqueConstraints $ tmInfo newtm)
|
2018-06-27 16:11:32 +03:00
|
|
|
|
2020-12-08 17:22:31 +03:00
|
|
|
mNewDesc = _ptmiDescription $ tmInfo newtm
|
2018-06-27 16:11:32 +03:00
|
|
|
|
2021-05-27 18:06:13 +03:00
|
|
|
droppedCols = map prciName $ getDifferenceOn prciPosition oldCols newCols
|
|
|
|
existingCols = getOverlapWith prciPosition oldCols newCols
|
2019-12-09 07:18:53 +03:00
|
|
|
alteredCols = filter (uncurry (/=)) existingCols
|
2018-06-27 16:11:32 +03:00
|
|
|
|
2019-06-03 13:21:55 +03:00
|
|
|
-- foreign keys are considered dropped only if their oid
|
|
|
|
-- and (ref-table, column mapping) are changed
|
2019-12-09 07:18:53 +03:00
|
|
|
droppedFKeyConstraints = map (_cName . _fkConstraint) $ HS.toList $
|
2019-06-03 13:21:55 +03:00
|
|
|
droppedFKeysWithOid `HS.intersection` droppedFKeysWithUniq
|
2020-12-17 14:37:16 +03:00
|
|
|
tmForeignKeys = fmap unForeignKeyMetadata . toList . _ptmiForeignKeys . tmInfo
|
2019-06-03 13:21:55 +03:00
|
|
|
droppedFKeysWithOid = HS.fromList $
|
2021-05-27 18:06:13 +03:00
|
|
|
(getDifferenceOn (_cOid . _fkConstraint) `on` tmForeignKeys) oldtm newtm
|
2019-06-03 13:21:55 +03:00
|
|
|
droppedFKeysWithUniq = HS.fromList $
|
2021-05-27 18:06:13 +03:00
|
|
|
(getDifferenceOn mkFKeyUniqId `on` tmForeignKeys) oldtm newtm
|
2019-12-09 07:18:53 +03:00
|
|
|
mkFKeyUniqId (ForeignKey _ reftn colMap) = (reftn, colMap)
|
2018-06-27 16:11:32 +03:00
|
|
|
|
2019-10-18 11:29:47 +03:00
|
|
|
-- calculate computed field diff
|
|
|
|
oldComputedFieldMeta = tmComputedFields oldtm
|
|
|
|
newComputedFieldMeta = tmComputedFields newtm
|
|
|
|
|
|
|
|
droppedComputedFields = map ccmName $
|
2021-05-27 18:06:13 +03:00
|
|
|
getDifferenceOn (fmOid . ccmFunctionMeta) oldComputedFieldMeta newComputedFieldMeta
|
2019-10-18 11:29:47 +03:00
|
|
|
|
|
|
|
alteredComputedFields =
|
2021-05-27 18:06:13 +03:00
|
|
|
getOverlapWith (fmOid . ccmFunctionMeta) oldComputedFieldMeta newComputedFieldMeta
|
2019-10-18 11:29:47 +03:00
|
|
|
|
|
|
|
overloadedComputedFieldFunctions =
|
|
|
|
let getFunction = fmFunction . ccmFunctionMeta
|
|
|
|
getSecondElement (_ NE.:| list) = listToMaybe list
|
|
|
|
in mapMaybe (fmap ((&&&) ccmName getFunction) . getSecondElement) $
|
|
|
|
flip NE.groupBy newComputedFieldMeta $ \l r ->
|
|
|
|
ccmName l == ccmName r && getFunction l == getFunction r
|
|
|
|
|
2019-11-07 17:39:48 +03:00
|
|
|
computedFieldDiff = ComputedFieldDiff droppedComputedFields alteredComputedFields
|
2019-10-18 11:29:47 +03:00
|
|
|
overloadedComputedFieldFunctions
|
|
|
|
|
2018-12-13 10:26:15 +03:00
|
|
|
getTableChangeDeps
|
2021-05-27 18:06:13 +03:00
|
|
|
:: forall b m
|
|
|
|
. (QErrM m, CacheRM m, Backend b)
|
|
|
|
=> SourceName
|
|
|
|
-> TableName b
|
|
|
|
-> TableDiff b
|
|
|
|
-> m [SchemaObjId]
|
2020-12-28 15:56:00 +03:00
|
|
|
getTableChangeDeps source tn tableDiff = do
|
2018-06-27 16:11:32 +03:00
|
|
|
sc <- askSchemaCache
|
|
|
|
-- for all the dropped columns
|
|
|
|
droppedColDeps <- fmap concat $ forM droppedCols $ \droppedCol -> do
|
2021-03-15 16:02:58 +03:00
|
|
|
let objId = SOSourceObj source
|
|
|
|
$ AB.mkAnyBackend
|
2021-05-27 18:06:13 +03:00
|
|
|
$ SOITableObj @b tn
|
|
|
|
$ TOCol @b droppedCol
|
2018-06-27 16:11:32 +03:00
|
|
|
return $ getDependentObjs sc objId
|
|
|
|
-- for all dropped constraints
|
2019-01-03 06:58:12 +03:00
|
|
|
droppedConsDeps <- fmap concat $ forM droppedFKeyConstraints $ \droppedCons -> do
|
2021-03-15 16:02:58 +03:00
|
|
|
let objId = SOSourceObj source
|
|
|
|
$ AB.mkAnyBackend
|
2021-05-27 18:06:13 +03:00
|
|
|
$ SOITableObj @b tn
|
|
|
|
$ TOForeignKey @b droppedCons
|
2018-06-27 16:11:32 +03:00
|
|
|
return $ getDependentObjs sc objId
|
2019-10-18 11:29:47 +03:00
|
|
|
return $ droppedConsDeps <> droppedColDeps <> droppedComputedFieldDeps
|
2018-06-27 16:11:32 +03:00
|
|
|
where
|
2021-05-27 18:06:13 +03:00
|
|
|
TableDiff _ droppedCols _ droppedFKeyConstraints computedFieldDiff _ _ = tableDiff
|
2021-03-15 16:02:58 +03:00
|
|
|
droppedComputedFieldDeps =
|
|
|
|
map
|
|
|
|
(SOSourceObj source
|
|
|
|
. AB.mkAnyBackend
|
2021-05-27 18:06:13 +03:00
|
|
|
. SOITableObj @b tn
|
2021-03-15 16:02:58 +03:00
|
|
|
. TOComputedField)
|
|
|
|
$ _cfdDropped computedFieldDiff
|
2018-06-27 16:11:32 +03:00
|
|
|
|
2020-11-12 12:25:48 +03:00
|
|
|
data SchemaDiff (b :: BackendType)
|
2018-06-27 16:11:32 +03:00
|
|
|
= SchemaDiff
|
2021-05-27 18:06:13 +03:00
|
|
|
{ _sdDroppedTables :: ![TableName b]
|
|
|
|
, _sdAlteredTables :: ![(TableName b, TableDiff b)]
|
2020-10-22 23:42:27 +03:00
|
|
|
}
|
2018-06-27 16:11:32 +03:00
|
|
|
|
2021-05-27 18:06:13 +03:00
|
|
|
getSchemaDiff
|
|
|
|
:: (Backend b) => [TableMeta b] -> [TableMeta b] -> SchemaDiff b
|
2018-06-27 16:11:32 +03:00
|
|
|
getSchemaDiff oldMeta newMeta =
|
|
|
|
SchemaDiff droppedTables survivingTables
|
|
|
|
where
|
2021-05-27 18:06:13 +03:00
|
|
|
droppedTables = map tmTable $ getDifferenceOn (_ptmiOid . tmInfo) oldMeta newMeta
|
2018-06-27 16:11:32 +03:00
|
|
|
survivingTables =
|
2021-05-27 18:06:13 +03:00
|
|
|
flip map (getOverlapWith (_ptmiOid . tmInfo) oldMeta newMeta) $ \(oldtm, newtm) ->
|
2018-06-27 16:11:32 +03:00
|
|
|
(tmTable oldtm, getTableDiff oldtm newtm)
|
|
|
|
|
2018-12-13 10:26:15 +03:00
|
|
|
getSchemaChangeDeps
|
2021-07-23 02:06:10 +03:00
|
|
|
:: forall b m
|
|
|
|
. (QErrM m, CacheRM m, Backend b)
|
|
|
|
=> SourceName
|
|
|
|
-> SchemaDiff b
|
|
|
|
-> m [SchemaObjId]
|
2020-12-28 15:56:00 +03:00
|
|
|
getSchemaChangeDeps source schemaDiff = do
|
2018-06-27 16:11:32 +03:00
|
|
|
sc <- askSchemaCache
|
2021-07-23 02:06:10 +03:00
|
|
|
let tableIds = SOSourceObj source . AB.mkAnyBackend . SOITable @b <$> droppedTables
|
|
|
|
tableDropDeps = concatMap (getDependentObjs sc) tableIds
|
2020-12-28 15:56:00 +03:00
|
|
|
tableModDeps <- concat <$> traverse (uncurry (getTableChangeDeps source)) alteredTables
|
2021-07-23 02:06:10 +03:00
|
|
|
pure $ filter isIndirectDep $ HS.toList $ HS.fromList $ tableDropDeps <> tableModDeps
|
2018-06-27 16:11:32 +03:00
|
|
|
where
|
|
|
|
SchemaDiff droppedTables alteredTables = schemaDiff
|
2021-07-23 02:06:10 +03:00
|
|
|
-- we keep all table objects that are not tied to a deleted table
|
|
|
|
isIndirectDep :: SchemaObjId -> Bool
|
|
|
|
isIndirectDep = \case
|
|
|
|
-- table objects in the same source
|
|
|
|
SOSourceObj s obj
|
|
|
|
| s == source
|
|
|
|
, Just (SOITableObj tn _) <- AB.unpackAnyBackend @b obj
|
|
|
|
-> not $ tn `HS.member` HS.fromList droppedTables
|
|
|
|
-- table objects in any other source
|
|
|
|
SOSourceObj _ obj
|
|
|
|
-> AB.runBackend obj \case
|
|
|
|
SOITableObj {} -> True
|
|
|
|
_ -> False
|
|
|
|
-- any other kind of schema object
|
|
|
|
_ -> False
|
2021-05-27 18:06:13 +03:00
|
|
|
|
|
|
|
data FunctionDiff b
|
2019-02-05 08:57:03 +03:00
|
|
|
= FunctionDiff
|
2021-05-27 18:06:13 +03:00
|
|
|
{ fdDropped :: ![FunctionName b]
|
|
|
|
, fdAltered :: ![(FunctionName b, FunctionVolatility)]
|
|
|
|
}
|
|
|
|
deriving instance (Backend b) => Show (FunctionDiff b)
|
|
|
|
deriving instance (Backend b) => Eq (FunctionDiff b)
|
2019-02-05 08:57:03 +03:00
|
|
|
|
2021-05-27 18:06:13 +03:00
|
|
|
getFuncDiff :: [FunctionMeta b] -> [FunctionMeta b] -> FunctionDiff b
|
2019-02-05 08:57:03 +03:00
|
|
|
getFuncDiff oldMeta newMeta =
|
|
|
|
FunctionDiff droppedFuncs alteredFuncs
|
|
|
|
where
|
2021-05-27 18:06:13 +03:00
|
|
|
droppedFuncs = map fmFunction $ getDifferenceOn fmOid oldMeta newMeta
|
|
|
|
alteredFuncs = mapMaybe mkAltered $ getOverlapWith fmOid oldMeta newMeta
|
2019-02-05 08:57:03 +03:00
|
|
|
mkAltered (oldfm, newfm) =
|
|
|
|
let isTypeAltered = fmType oldfm /= fmType newfm
|
2019-11-20 21:21:30 +03:00
|
|
|
alteredFunc = (fmFunction oldfm, fmType newfm)
|
2021-05-27 18:06:13 +03:00
|
|
|
in bool Nothing (Just alteredFunc) isTypeAltered
|
2019-02-14 07:05:18 +03:00
|
|
|
|
|
|
|
getOverloadedFuncs
|
2021-05-27 18:06:13 +03:00
|
|
|
:: (Backend b) => [FunctionName b] -> [FunctionMeta b] -> [FunctionName b]
|
2019-02-14 07:05:18 +03:00
|
|
|
getOverloadedFuncs trackedFuncs newFuncMeta =
|
2020-05-27 18:02:58 +03:00
|
|
|
toList $ duplicates $ map fmFunction trackedMeta
|
2019-02-14 07:05:18 +03:00
|
|
|
where
|
|
|
|
trackedMeta = flip filter newFuncMeta $ \fm ->
|
2019-10-18 11:29:47 +03:00
|
|
|
fmFunction fm `elem` trackedFuncs
|
2021-05-27 18:06:13 +03:00
|
|
|
|
|
|
|
processSchemaDiff
|
|
|
|
:: forall b m
|
|
|
|
. ( MonadError QErr m
|
|
|
|
, CacheRM m
|
|
|
|
, MonadWriter MetadataModifier m
|
|
|
|
, BackendMetadata b
|
|
|
|
)
|
|
|
|
=> SourceName
|
|
|
|
-> TableCache b
|
|
|
|
-> SchemaDiff b
|
|
|
|
-> m ()
|
|
|
|
processSchemaDiff source preActionTables schemaDiff = do
|
|
|
|
-- Purge the dropped tables
|
|
|
|
dropTablesInMetadata @b source droppedTables
|
|
|
|
|
|
|
|
for_ alteredTables $ \(oldQtn, tableDiff) -> do
|
|
|
|
ti <- onNothing
|
|
|
|
(M.lookup oldQtn preActionTables)
|
|
|
|
(throw500 $ "old table metadata not found in cache : " <>> oldQtn)
|
|
|
|
alterTableInMetadata source (_tiCoreInfo ti) tableDiff
|
|
|
|
where
|
|
|
|
SchemaDiff droppedTables alteredTables = schemaDiff
|
|
|
|
|
|
|
|
alterTableInMetadata
|
|
|
|
:: forall m b
|
|
|
|
. ( MonadError QErr m
|
|
|
|
, CacheRM m
|
|
|
|
, MonadWriter MetadataModifier m
|
|
|
|
, BackendMetadata b
|
|
|
|
)
|
|
|
|
=> SourceName -> TableCoreInfo b -> TableDiff b -> m ()
|
|
|
|
alterTableInMetadata source ti tableDiff = do
|
|
|
|
-- If table rename occurs then don't replace constraints and
|
|
|
|
-- process dropped/added columns, because schema reload happens eventually
|
|
|
|
sc <- askSchemaCache
|
|
|
|
let tn = _tciName ti
|
|
|
|
withOldTabName = do
|
|
|
|
alterColumnsInMetadata source alteredCols tableFields sc tn
|
|
|
|
|
|
|
|
withNewTabName :: TableName b -> m ()
|
|
|
|
withNewTabName newTN = do
|
|
|
|
-- check for GraphQL schema conflicts on new name
|
|
|
|
liftEither (tableGraphQLName @b newTN) >>= checkConflictingNode sc . G.unName
|
|
|
|
alterColumnsInMetadata source alteredCols tableFields sc tn
|
|
|
|
-- update new table in metadata
|
|
|
|
renameTableInMetadata @b source newTN tn
|
|
|
|
|
|
|
|
-- Process computed field diff
|
|
|
|
processComputedFieldDiff tn
|
|
|
|
-- Drop custom column names for dropped columns
|
|
|
|
alterCustomColumnNamesInMetadata source droppedCols ti
|
|
|
|
maybe withOldTabName withNewTabName mNewName
|
|
|
|
where
|
|
|
|
TableDiff mNewName droppedCols alteredCols _ computedFieldDiff _ _ = tableDiff
|
|
|
|
tableFields = _tciFieldInfoMap ti
|
|
|
|
|
|
|
|
processComputedFieldDiff :: TableName b -> m ()
|
|
|
|
processComputedFieldDiff table = do
|
|
|
|
let ComputedFieldDiff _ altered overloaded = computedFieldDiff
|
|
|
|
getFunction = fmFunction . ccmFunctionMeta
|
|
|
|
forM_ overloaded $ \(columnName, function) ->
|
|
|
|
throw400 NotSupported $ "The function " <> function
|
|
|
|
<<> " associated with computed field" <> columnName
|
|
|
|
<<> " of table " <> table <<> " is being overloaded"
|
|
|
|
forM_ altered $ \(old, new) ->
|
|
|
|
if | (fmType . ccmFunctionMeta) new == FTVOLATILE ->
|
|
|
|
throw400 NotSupported $ "The type of function " <> getFunction old
|
|
|
|
<<> " associated with computed field " <> ccmName old
|
|
|
|
<<> " of table " <> table <<> " is being altered to \"VOLATILE\""
|
|
|
|
| otherwise -> pure ()
|
|
|
|
|
|
|
|
dropTablesInMetadata
|
|
|
|
:: forall b m
|
|
|
|
. ( MonadWriter MetadataModifier m
|
|
|
|
, BackendMetadata b
|
|
|
|
)
|
|
|
|
=> SourceName
|
|
|
|
-> [TableName b]
|
|
|
|
-> m ()
|
|
|
|
dropTablesInMetadata source droppedTables =
|
|
|
|
forM_ droppedTables $
|
|
|
|
\tn -> tell $ MetadataModifier $ metaSources.ix source.toSourceMetadata.(smTables @b) %~ OMap.delete tn
|
|
|
|
|
|
|
|
alterColumnsInMetadata
|
|
|
|
:: forall b m
|
|
|
|
. ( MonadError QErr m
|
|
|
|
, CacheRM m
|
|
|
|
, MonadWriter MetadataModifier m
|
|
|
|
, BackendMetadata b
|
|
|
|
)
|
|
|
|
=> SourceName
|
|
|
|
-> [(RawColumnInfo b, RawColumnInfo b)]
|
|
|
|
-> FieldInfoMap (FieldInfo b)
|
|
|
|
-> SchemaCache
|
|
|
|
-> TableName b
|
|
|
|
-> m ()
|
|
|
|
alterColumnsInMetadata source alteredCols fields sc tn = for_ alteredCols $
|
2021-08-31 16:34:43 +03:00
|
|
|
\( RawColumnInfo{prciName = oldName, prciType = oldType}
|
|
|
|
, RawColumnInfo{prciName = newName, prciType = newType}) -> do
|
2021-05-27 18:06:13 +03:00
|
|
|
if | oldName /= newName ->
|
|
|
|
renameColumnInMetadata oldName newName source tn fields
|
|
|
|
|
|
|
|
| oldType /= newType -> do
|
|
|
|
let colId =
|
|
|
|
SOSourceObj source
|
|
|
|
$ AB.mkAnyBackend
|
|
|
|
$ SOITableObj @b tn
|
|
|
|
$ TOCol @b oldName
|
|
|
|
typeDepObjs = getDependentObjsWith (== DROnType) sc colId
|
|
|
|
|
|
|
|
unless (null typeDepObjs) $ throw400 DependencyError $
|
|
|
|
"cannot change type of column " <> oldName <<> " in table "
|
|
|
|
<> tn <<> " because of the following dependencies : " <>
|
|
|
|
reportSchemaObjs typeDepObjs
|
|
|
|
|
|
|
|
| otherwise -> pure ()
|
|
|
|
|
|
|
|
alterCustomColumnNamesInMetadata
|
|
|
|
:: forall b m
|
|
|
|
. (MonadWriter MetadataModifier m, BackendMetadata b)
|
|
|
|
=> SourceName
|
|
|
|
-> [Column b]
|
|
|
|
-> TableCoreInfo b
|
|
|
|
-> m ()
|
|
|
|
alterCustomColumnNamesInMetadata source droppedCols ti = do
|
|
|
|
let TableConfig customFields customColumnNames customName = _tciCustomConfig ti
|
|
|
|
tn = _tciName ti
|
|
|
|
modifiedCustomColumnNames = foldl' (flip M.delete) customColumnNames droppedCols
|
|
|
|
when (modifiedCustomColumnNames /= customColumnNames) $
|
|
|
|
tell $ MetadataModifier $
|
|
|
|
tableMetadataSetter @b source tn.tmConfiguration .~
|
|
|
|
TableConfig @b customFields modifiedCustomColumnNames customName
|