2020-12-28 15:56:00 +03:00
|
|
|
module Hasura.RQL.DDL.Schema.Source where
|
|
|
|
|
2021-03-15 16:02:58 +03:00
|
|
|
import Hasura.Prelude
|
|
|
|
|
|
|
|
import qualified Data.Environment as Env
|
|
|
|
import qualified Data.HashMap.Strict as HM
|
|
|
|
import qualified Data.HashMap.Strict.InsOrd as OMap
|
|
|
|
import qualified Database.PG.Query as Q
|
|
|
|
|
2021-03-30 13:09:29 +03:00
|
|
|
import Control.Lens (at, (.~), (^.))
|
2020-12-28 15:56:00 +03:00
|
|
|
import Control.Monad.Trans.Control (MonadBaseControl)
|
2021-01-07 12:04:22 +03:00
|
|
|
import Data.Text.Extended
|
2021-03-15 16:02:58 +03:00
|
|
|
|
|
|
|
import qualified Hasura.SQL.AnyBackend as AB
|
2021-01-07 12:04:22 +03:00
|
|
|
|
2020-12-28 15:56:00 +03:00
|
|
|
import Hasura.Backends.Postgres.Connection
|
2021-05-11 18:18:31 +03:00
|
|
|
import Hasura.Base.Error
|
2021-01-07 12:04:22 +03:00
|
|
|
import Hasura.EncJSON
|
|
|
|
import Hasura.RQL.DDL.Deps
|
2020-12-28 15:56:00 +03:00
|
|
|
import Hasura.RQL.DDL.Schema.Common
|
|
|
|
import Hasura.RQL.Types
|
|
|
|
|
|
|
|
|
|
|
|
mkPgSourceResolver :: Q.PGLogger -> SourceResolver
|
2021-01-07 12:04:22 +03:00
|
|
|
mkPgSourceResolver pgLogger _ config = runExceptT do
|
2020-12-28 15:56:00 +03:00
|
|
|
env <- lift Env.getEnvironment
|
2021-04-28 19:49:23 +03:00
|
|
|
let PostgresSourceConnInfo urlConf poolSettings allowPrepare isoLevel = _pccConnectionInfo config
|
2021-03-16 18:27:51 +03:00
|
|
|
-- If the user does not provide values for the pool settings, then use the default values
|
2021-04-28 19:49:23 +03:00
|
|
|
let (maxConns, idleTimeout, retries) = getDefaultPGPoolSettingIfNotExists poolSettings defaultPostgresPoolSettings
|
2020-12-28 15:56:00 +03:00
|
|
|
urlText <- resolveUrlConf env urlConf
|
|
|
|
let connInfo = Q.ConnInfo retries $ Q.CDDatabaseURI $ txtToBs urlText
|
|
|
|
connParams = Q.defaultConnParams{ Q.cpIdleTime = idleTimeout
|
|
|
|
, Q.cpConns = maxConns
|
2021-04-14 20:51:02 +03:00
|
|
|
, Q.cpAllowPrepare = allowPrepare
|
2021-04-28 19:49:23 +03:00
|
|
|
, Q.cpMbLifetime = _ppsConnectionLifetime =<< poolSettings
|
|
|
|
, Q.cpTimeout = _ppsPoolTimeout =<< poolSettings
|
2020-12-28 15:56:00 +03:00
|
|
|
}
|
|
|
|
pgPool <- liftIO $ Q.initPGPool connInfo connParams pgLogger
|
2021-04-28 19:49:23 +03:00
|
|
|
let pgExecCtx = mkPGExecCtx isoLevel pgPool
|
2020-12-28 15:56:00 +03:00
|
|
|
pure $ PGSourceConfig pgExecCtx connInfo Nothing
|
|
|
|
|
2021-01-07 12:04:22 +03:00
|
|
|
--- Metadata APIs related
|
2021-02-23 20:37:27 +03:00
|
|
|
runAddSource
|
|
|
|
:: forall m b
|
|
|
|
. (MonadError QErr m, CacheRWM m, MetadataM m, BackendMetadata b)
|
|
|
|
=> AddSource b -> m EncJSON
|
2021-03-30 13:09:29 +03:00
|
|
|
runAddSource (AddSource name sourceConfig replaceConfiguration) = do
|
2021-02-23 20:37:27 +03:00
|
|
|
sources <- scSources <$> askSchemaCache
|
2021-03-30 13:09:29 +03:00
|
|
|
let sourceMetadata = mkSourceMetadata @b name sourceConfig
|
|
|
|
|
|
|
|
metadataModifier <- MetadataModifier <$>
|
|
|
|
if HM.member name sources then
|
|
|
|
if replaceConfiguration then pure $ metaSources.ix name .~ sourceMetadata
|
|
|
|
else throw400 AlreadyExists $ "source with name " <> name <<> " already exists"
|
|
|
|
else pure $ metaSources %~ OMap.insert name sourceMetadata
|
|
|
|
|
|
|
|
buildSchemaCacheFor (MOSource name) metadataModifier
|
2021-01-07 12:04:22 +03:00
|
|
|
pure successMsg
|
|
|
|
|
2021-02-23 20:37:27 +03:00
|
|
|
runDropSource
|
|
|
|
:: forall m. (MonadError QErr m, CacheRWM m, MonadIO m, MonadBaseControl IO m, MetadataM m)
|
|
|
|
=> DropSource -> m EncJSON
|
|
|
|
runDropSource (DropSource name cascade) = do
|
2021-01-07 12:04:22 +03:00
|
|
|
sc <- askSchemaCache
|
2021-02-23 20:37:27 +03:00
|
|
|
let sources = scSources sc
|
2021-03-02 07:26:31 +03:00
|
|
|
case HM.lookup name sources of
|
|
|
|
Just backendSourceInfo ->
|
2021-03-15 16:02:58 +03:00
|
|
|
AB.dispatchAnyBackend @BackendMetadata backendSourceInfo $ dropSource sc
|
|
|
|
|
2021-03-02 07:26:31 +03:00
|
|
|
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
|
2021-02-23 20:37:27 +03:00
|
|
|
pure successMsg
|
|
|
|
where
|
|
|
|
dropSource :: forall b. (BackendMetadata b) => SchemaCache -> SourceInfo b -> m ()
|
|
|
|
dropSource sc sourceInfo = do
|
|
|
|
let sourceConfig = _siConfiguration sourceInfo
|
|
|
|
let indirectDeps = mapMaybe getIndirectDep $
|
|
|
|
getDependentObjs sc (SOSource name)
|
2021-01-07 12:04:22 +03:00
|
|
|
|
2021-03-15 16:02:58 +03:00
|
|
|
when (not cascade && indirectDeps /= [])
|
|
|
|
$ reportDepsExt
|
|
|
|
(map (SOSourceObj name . AB.mkAnyBackend) indirectDeps)
|
|
|
|
[]
|
2021-01-07 12:04:22 +03:00
|
|
|
|
2021-02-23 20:37:27 +03:00
|
|
|
metadataModifier <- execWriterT $ do
|
|
|
|
mapM_ (purgeDependentObject name >=> tell) indirectDeps
|
2021-03-02 07:26:31 +03:00
|
|
|
tell dropSourceMetadataModifier
|
2021-01-07 12:04:22 +03:00
|
|
|
|
2021-02-23 20:37:27 +03:00
|
|
|
buildSchemaCacheFor (MOSource name) metadataModifier
|
2021-04-22 00:44:37 +03:00
|
|
|
postDropSourceHook @b sourceConfig
|
2021-02-23 20:37:27 +03:00
|
|
|
where
|
|
|
|
getIndirectDep :: SchemaObjId -> Maybe (SourceObjId b)
|
|
|
|
getIndirectDep = \case
|
2021-03-15 16:02:58 +03:00
|
|
|
SOSourceObj s o ->
|
|
|
|
if s == name
|
|
|
|
then Nothing
|
|
|
|
-- consider only *this* backend specific dependencies
|
|
|
|
else AB.unpackAnyBackend o
|
2021-02-23 20:37:27 +03:00
|
|
|
_ -> Nothing
|
2021-03-02 07:26:31 +03:00
|
|
|
|
|
|
|
dropSourceMetadataModifier = MetadataModifier $ metaSources %~ OMap.delete name
|