2022-11-17 15:55:05 +03:00
|
|
|
{-# LANGUAGE UndecidableInstances #-}
|
|
|
|
|
|
|
|
module Main (main) where
|
|
|
|
|
2023-03-02 17:44:25 +03:00
|
|
|
import Constants qualified
|
2022-11-17 15:55:05 +03:00
|
|
|
import Control.Concurrent.MVar
|
2023-03-27 13:25:55 +03:00
|
|
|
import Control.Monad.Trans.Managed (lowerManagedT)
|
2022-11-17 15:55:05 +03:00
|
|
|
import Control.Natural ((:~>) (..))
|
2023-04-26 20:28:48 +03:00
|
|
|
import Data.Aeson qualified as J
|
2022-11-17 15:55:05 +03:00
|
|
|
import Data.ByteString.Lazy.Char8 qualified as BL
|
|
|
|
import Data.ByteString.Lazy.UTF8 qualified as LBS
|
|
|
|
import Data.Environment qualified as Env
|
2023-02-24 21:09:36 +03:00
|
|
|
import Data.Text qualified as T
|
2022-11-17 15:55:05 +03:00
|
|
|
import Data.Time.Clock (getCurrentTime)
|
|
|
|
import Data.URL.Template
|
|
|
|
import Database.PG.Query qualified as PG
|
|
|
|
import Hasura.App
|
2023-03-23 18:51:18 +03:00
|
|
|
( AppM,
|
|
|
|
BasicConnectionInfo (..),
|
2023-03-23 00:40:26 +03:00
|
|
|
initMetadataConnectionInfo,
|
2023-03-27 13:25:55 +03:00
|
|
|
initialiseAppEnv,
|
2022-11-17 15:55:05 +03:00
|
|
|
mkMSSQLSourceResolver,
|
|
|
|
mkPgSourceResolver,
|
2023-03-23 18:51:18 +03:00
|
|
|
runAppM,
|
2022-11-17 15:55:05 +03:00
|
|
|
)
|
|
|
|
import Hasura.Backends.Postgres.Connection.Settings
|
|
|
|
import Hasura.Backends.Postgres.Execute.Types
|
2023-02-03 04:03:23 +03:00
|
|
|
import Hasura.Base.Error
|
2023-08-25 12:55:20 +03:00
|
|
|
import Hasura.GraphQL.Schema.Common
|
2022-11-17 15:55:05 +03:00
|
|
|
import Hasura.Logging
|
|
|
|
import Hasura.Prelude
|
|
|
|
import Hasura.RQL.DDL.Schema.Cache
|
|
|
|
import Hasura.RQL.DDL.Schema.Cache.Common
|
Remove `ServerConfigCtx`.
### Description
This PR removes `ServerConfigCtx` and `HasServerConfigCtx`. Instead, it favours different approaches:
- when the code was only using one field, it passes that field explicitly (usually `SQLGenCtx` or `CheckFeatureFlag`)
- when the code was using several fields, but in only one function, it inlines
- for the cache build, it introduces `CacheStaticConfig` and `CacheDynamicConfig`, which are subsets of `AppEnv` and `AppContext` respectively
The main goal of this is to help with the modularization of the engine: as `ServerConfigCtx` had fields whose types were imported from several unrelated parts of the engine, using it tied together parts of the engine that should not be aware of one another (such as tying together `Hasura.LogicalModel` and `Hasura.GraphQL.Schema`).
The bulk of this PR is a change to the cache build, as a follow up to #8509: instead of giving the entire `ServerConfigCtx` as a incremental rule argument, we only give the new `CacheDynamicConfig` struct, which has fewer fields. The other required fields, that were coming from the `AppEnv`, are now given via the `HasCacheStaticConfig` constraint, which is a "subset" of `HasAppEnv`.
(Some further work could include moving `StringifyNumbers` out of `GraphQL.Schema.Options`, given how it is used all across the codebase, including in `RQL.DML`.)
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/8513
GitOrigin-RevId: 818cbcd71494e3cd946b06adbb02ca328a8a298e
2023-04-04 18:59:58 +03:00
|
|
|
import Hasura.RQL.DDL.Schema.Cache.Config
|
2022-11-17 15:55:05 +03:00
|
|
|
import Hasura.RQL.Types.Common
|
|
|
|
import Hasura.RQL.Types.Metadata (emptyMetadataDefaults)
|
|
|
|
import Hasura.RQL.Types.ResizePool
|
2023-04-24 18:17:15 +03:00
|
|
|
import Hasura.RQL.Types.Schema.Options qualified as Options
|
2023-03-28 16:26:08 +03:00
|
|
|
import Hasura.RQL.Types.SchemaCache
|
2022-11-17 15:55:05 +03:00
|
|
|
import Hasura.RQL.Types.SchemaCache.Build
|
|
|
|
import Hasura.Server.Init
|
2023-02-24 21:09:36 +03:00
|
|
|
import Hasura.Server.Metrics (ServerMetricsSpec, createServerMetrics)
|
2022-11-17 15:55:05 +03:00
|
|
|
import Hasura.Server.Migrate
|
2023-02-24 21:09:36 +03:00
|
|
|
import Hasura.Server.Prometheus (makeDummyPrometheusMetrics)
|
2022-11-17 15:55:05 +03:00
|
|
|
import Hasura.Server.Types
|
2023-02-24 21:09:36 +03:00
|
|
|
import Hasura.Tracing (sampleAlways)
|
2022-11-17 15:55:05 +03:00
|
|
|
import Network.HTTP.Client qualified as HTTP
|
|
|
|
import Network.HTTP.Client.TLS qualified as HTTP
|
|
|
|
import System.Environment (getEnvironment)
|
|
|
|
import System.Exit (exitFailure)
|
2023-02-24 21:09:36 +03:00
|
|
|
import System.Metrics qualified as EKG
|
2023-02-20 20:41:55 +03:00
|
|
|
import Test.Hasura.EventTriggerCleanupSuite qualified as EventTriggerCleanupSuite
|
|
|
|
import Test.Hasura.Server.MigrateSuite qualified as MigrateSuite
|
|
|
|
import Test.Hasura.StreamingSubscriptionSuite qualified as StreamingSubscriptionSuite
|
2022-11-17 15:55:05 +03:00
|
|
|
import Test.Hspec
|
|
|
|
|
2023-03-30 17:30:19 +03:00
|
|
|
{-# ANN main ("HLINT: ignore avoid getEnvironment" :: String) #-}
|
2022-11-17 15:55:05 +03:00
|
|
|
main :: IO ()
|
|
|
|
main = do
|
|
|
|
env <- getEnvironment
|
|
|
|
let envMap = Env.mkEnvironment env
|
|
|
|
|
2023-05-24 16:51:56 +03:00
|
|
|
pgUrlText <- flip onLeft printErrExit
|
|
|
|
$ runWithEnv env
|
|
|
|
$ do
|
2022-11-17 15:55:05 +03:00
|
|
|
let envVar = _envVar databaseUrlOption
|
|
|
|
maybeV <- considerEnv envVar
|
2023-05-24 16:51:56 +03:00
|
|
|
onNothing maybeV
|
|
|
|
$ throwError
|
|
|
|
$ "Expected: "
|
|
|
|
<> envVar
|
2022-11-17 15:55:05 +03:00
|
|
|
|
|
|
|
let pgConnInfo = PG.ConnInfo 1 $ PG.CDDatabaseURI $ txtToBs pgUrlText
|
2023-06-23 11:37:26 +03:00
|
|
|
urlConf = UrlValue $ InputWebhook $ mkPlainTemplate pgUrlText
|
2022-11-17 15:55:05 +03:00
|
|
|
sourceConnInfo =
|
|
|
|
PostgresSourceConnInfo urlConf (Just setPostgresPoolSettings) True PG.ReadCommitted Nothing
|
2023-01-25 10:12:53 +03:00
|
|
|
sourceConfig = PostgresConnConfiguration sourceConnInfo Nothing defaultPostgresExtensionsSchema Nothing mempty
|
2023-02-24 21:09:36 +03:00
|
|
|
rci =
|
|
|
|
PostgresConnInfo
|
|
|
|
{ _pciDatabaseConn = Nothing,
|
|
|
|
_pciRetries = Nothing
|
|
|
|
}
|
|
|
|
serveOptions = Constants.serveOptions
|
|
|
|
metadataDbUrl = Just (T.unpack pgUrlText)
|
2022-11-17 15:55:05 +03:00
|
|
|
|
2023-07-20 14:18:18 +03:00
|
|
|
pgPool <- PG.initPGPool pgConnInfo J.Null PG.defaultConnParams {PG.cpConns = 1} print
|
2022-11-17 15:55:05 +03:00
|
|
|
let pgContext = mkPGExecCtx PG.Serializable pgPool NeverResizePool
|
|
|
|
|
|
|
|
logger :: Logger Hasura = Logger $ \l -> do
|
|
|
|
let (logLevel, logType :: EngineLogType Hasura, logDetail) = toEngineLog l
|
|
|
|
t <- liftIO $ getFormattedTime Nothing
|
2023-08-18 13:56:25 +03:00
|
|
|
liftIO $ putStrLn $ LBS.toString $ J.encode $ EngineLog t logLevel logType logDetail Nothing Nothing
|
2022-11-17 15:55:05 +03:00
|
|
|
|
|
|
|
setupCacheRef = do
|
|
|
|
httpManager <- HTTP.newManager HTTP.tlsManagerSettings
|
2023-03-23 00:40:26 +03:00
|
|
|
metadataConnectionInfo <- initMetadataConnectionInfo envMap metadataDbUrl rci
|
|
|
|
let globalCtx = BasicConnectionInfo metadataConnectionInfo Nothing
|
2023-02-24 21:09:36 +03:00
|
|
|
(_, serverMetrics) <-
|
|
|
|
liftIO $ do
|
|
|
|
store <- EKG.newStore @TestMetricsSpec
|
|
|
|
serverMetrics <-
|
|
|
|
liftIO $ createServerMetrics $ EKG.subset ServerSubset store
|
|
|
|
pure (EKG.subset EKG.emptyOf store, serverMetrics)
|
|
|
|
prometheusMetrics <- makeDummyPrometheusMetrics
|
2022-11-17 15:55:05 +03:00
|
|
|
let sqlGenCtx =
|
|
|
|
SQLGenCtx
|
|
|
|
Options.Don'tStringifyNumbers
|
|
|
|
Options.Don'tDangerouslyCollapseBooleans
|
2023-07-21 18:10:53 +03:00
|
|
|
Options.RemoteForwardAccurately
|
2022-11-17 15:55:05 +03:00
|
|
|
Options.Don'tOptimizePermissionFilters
|
|
|
|
Options.EnableBigQueryStringNumericInput
|
|
|
|
maintenanceMode = MaintenanceModeDisabled
|
|
|
|
readOnlyMode = ReadOnlyModeDisabled
|
Remove `ServerConfigCtx`.
### Description
This PR removes `ServerConfigCtx` and `HasServerConfigCtx`. Instead, it favours different approaches:
- when the code was only using one field, it passes that field explicitly (usually `SQLGenCtx` or `CheckFeatureFlag`)
- when the code was using several fields, but in only one function, it inlines
- for the cache build, it introduces `CacheStaticConfig` and `CacheDynamicConfig`, which are subsets of `AppEnv` and `AppContext` respectively
The main goal of this is to help with the modularization of the engine: as `ServerConfigCtx` had fields whose types were imported from several unrelated parts of the engine, using it tied together parts of the engine that should not be aware of one another (such as tying together `Hasura.LogicalModel` and `Hasura.GraphQL.Schema`).
The bulk of this PR is a change to the cache build, as a follow up to #8509: instead of giving the entire `ServerConfigCtx` as a incremental rule argument, we only give the new `CacheDynamicConfig` struct, which has fewer fields. The other required fields, that were coming from the `AppEnv`, are now given via the `HasCacheStaticConfig` constraint, which is a "subset" of `HasAppEnv`.
(Some further work could include moving `StringifyNumbers` out of `GraphQL.Schema.Options`, given how it is used all across the codebase, including in `RQL.DML`.)
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/8513
GitOrigin-RevId: 818cbcd71494e3cd946b06adbb02ca328a8a298e
2023-04-04 18:59:58 +03:00
|
|
|
staticConfig =
|
|
|
|
CacheStaticConfig
|
|
|
|
maintenanceMode
|
|
|
|
EventingEnabled
|
|
|
|
readOnlyMode
|
2023-06-06 11:49:53 +03:00
|
|
|
logger
|
2023-06-14 16:19:47 +03:00
|
|
|
(const False)
|
2023-05-04 15:43:59 +03:00
|
|
|
False
|
Remove `ServerConfigCtx`.
### Description
This PR removes `ServerConfigCtx` and `HasServerConfigCtx`. Instead, it favours different approaches:
- when the code was only using one field, it passes that field explicitly (usually `SQLGenCtx` or `CheckFeatureFlag`)
- when the code was using several fields, but in only one function, it inlines
- for the cache build, it introduces `CacheStaticConfig` and `CacheDynamicConfig`, which are subsets of `AppEnv` and `AppContext` respectively
The main goal of this is to help with the modularization of the engine: as `ServerConfigCtx` had fields whose types were imported from several unrelated parts of the engine, using it tied together parts of the engine that should not be aware of one another (such as tying together `Hasura.LogicalModel` and `Hasura.GraphQL.Schema`).
The bulk of this PR is a change to the cache build, as a follow up to #8509: instead of giving the entire `ServerConfigCtx` as a incremental rule argument, we only give the new `CacheDynamicConfig` struct, which has fewer fields. The other required fields, that were coming from the `AppEnv`, are now given via the `HasCacheStaticConfig` constraint, which is a "subset" of `HasAppEnv`.
(Some further work could include moving `StringifyNumbers` out of `GraphQL.Schema.Options`, given how it is used all across the codebase, including in `RQL.DML`.)
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/8513
GitOrigin-RevId: 818cbcd71494e3cd946b06adbb02ca328a8a298e
2023-04-04 18:59:58 +03:00
|
|
|
dynamicConfig =
|
|
|
|
CacheDynamicConfig
|
2022-11-17 15:55:05 +03:00
|
|
|
Options.InferFunctionPermissions
|
|
|
|
Options.DisableRemoteSchemaPermissions
|
|
|
|
sqlGenCtx
|
|
|
|
mempty
|
2023-01-30 07:59:30 +03:00
|
|
|
(_default defaultNamingConventionOption)
|
2022-11-17 15:55:05 +03:00
|
|
|
emptyMetadataDefaults
|
2023-03-15 11:14:20 +03:00
|
|
|
ApolloFederationDisabled
|
2023-06-13 12:22:36 +03:00
|
|
|
(_default closeWebsocketsOnMetadataChangeOption)
|
2023-08-25 12:55:20 +03:00
|
|
|
(SchemaSampledFeatureFlags [])
|
Remove `ServerConfigCtx`.
### Description
This PR removes `ServerConfigCtx` and `HasServerConfigCtx`. Instead, it favours different approaches:
- when the code was only using one field, it passes that field explicitly (usually `SQLGenCtx` or `CheckFeatureFlag`)
- when the code was using several fields, but in only one function, it inlines
- for the cache build, it introduces `CacheStaticConfig` and `CacheDynamicConfig`, which are subsets of `AppEnv` and `AppContext` respectively
The main goal of this is to help with the modularization of the engine: as `ServerConfigCtx` had fields whose types were imported from several unrelated parts of the engine, using it tied together parts of the engine that should not be aware of one another (such as tying together `Hasura.LogicalModel` and `Hasura.GraphQL.Schema`).
The bulk of this PR is a change to the cache build, as a follow up to #8509: instead of giving the entire `ServerConfigCtx` as a incremental rule argument, we only give the new `CacheDynamicConfig` struct, which has fewer fields. The other required fields, that were coming from the `AppEnv`, are now given via the `HasCacheStaticConfig` constraint, which is a "subset" of `HasAppEnv`.
(Some further work could include moving `StringifyNumbers` out of `GraphQL.Schema.Options`, given how it is used all across the codebase, including in `RQL.DML`.)
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/8513
GitOrigin-RevId: 818cbcd71494e3cd946b06adbb02ca328a8a298e
2023-04-04 18:59:58 +03:00
|
|
|
cacheBuildParams = CacheBuildParams httpManager (mkPgSourceResolver print) mkMSSQLSourceResolver staticConfig
|
2022-11-17 15:55:05 +03:00
|
|
|
|
2023-03-27 13:25:55 +03:00
|
|
|
(_appInit, appEnv) <-
|
2023-05-24 16:51:56 +03:00
|
|
|
lowerManagedT
|
|
|
|
$ initialiseAppEnv
|
2023-02-24 21:09:36 +03:00
|
|
|
envMap
|
|
|
|
globalCtx
|
|
|
|
serveOptions
|
|
|
|
Nothing
|
|
|
|
serverMetrics
|
|
|
|
prometheusMetrics
|
|
|
|
sampleAlways
|
|
|
|
|
2023-03-23 18:51:18 +03:00
|
|
|
let run :: ExceptT QErr AppM a -> IO a
|
2022-11-17 15:55:05 +03:00
|
|
|
run =
|
2023-02-03 04:03:23 +03:00
|
|
|
runExceptT
|
2023-03-23 18:51:18 +03:00
|
|
|
>>> runAppM appEnv
|
Clean `AppEnv` and `AppContext` passing, remove `RunT`, reduce `ServerConfigCtx` uses
## Description
This PR does several different things that happen to overlap; the most important being:
- it removes `RunT`: it was redundant in places where we already had `Handler`, and only used in one other place, `SchemaUpdate`, for which a local `SchemaUpdateT` is more than enough;
- it reduces the number of places where we create a `ServerConfigCtx`, since now `HasServerConfigCtx` can be implemented directly by `SchemaUpdateT` and `Handler` based on the full `AppContext`;
- it drastically reduces the number of arguments we pass around in the app init code, by introducing `HasAppEnv`;
- it simplifies `HandlerCtx` to reduce duplication
In doing so, this changes paves the way towards removing `ServerConfigCtx`, since there are only very few places where we construct it: we can now introduce smaller classes than `HasServerConfigCtx`, that expose only a relevant subset of fields, and implement them where we now implement `HasServerConfigCtx`.
This PR is loosely based on ideas in #8337, that are no longer applicable due to the changes introduced in #8159. A challenge of this PR was the postgres tests, which were running in `PGMetadataStorageAppT CacheBuild` :scream_cat:
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/8392
GitOrigin-RevId: b90c1359066d20dbea329c87762ccdd1217b4d69
2023-03-21 13:44:21 +03:00
|
|
|
>>> flip onLeftM printErrJExit
|
2022-11-17 15:55:05 +03:00
|
|
|
|
2023-03-23 00:40:26 +03:00
|
|
|
-- why are we building the schema cache here? it's already built in initialiseContext
|
2022-11-17 15:55:05 +03:00
|
|
|
(metadata, schemaCache) <- run do
|
2023-03-28 16:26:08 +03:00
|
|
|
metadataWithVersion <-
|
2022-11-17 15:55:05 +03:00
|
|
|
snd
|
2023-01-25 10:12:53 +03:00
|
|
|
<$> (liftEitherM . runExceptT . _pecRunTx pgContext (PGExecCtxInfo (Tx PG.ReadWrite Nothing) InternalRawQuery))
|
2022-11-17 15:55:05 +03:00
|
|
|
(migrateCatalog (Just sourceConfig) defaultPostgresExtensionsSchema maintenanceMode =<< liftIO getCurrentTime)
|
2023-05-24 15:49:31 +03:00
|
|
|
schemaCache <- runCacheBuild cacheBuildParams $ buildRebuildableSchemaCache logger envMap metadataWithVersion dynamicConfig Nothing
|
2023-03-28 16:26:08 +03:00
|
|
|
pure (_mwrvMetadata metadataWithVersion, schemaCache)
|
2022-11-17 15:55:05 +03:00
|
|
|
|
|
|
|
cacheRef <- newMVar schemaCache
|
Remove `ServerConfigCtx`.
### Description
This PR removes `ServerConfigCtx` and `HasServerConfigCtx`. Instead, it favours different approaches:
- when the code was only using one field, it passes that field explicitly (usually `SQLGenCtx` or `CheckFeatureFlag`)
- when the code was using several fields, but in only one function, it inlines
- for the cache build, it introduces `CacheStaticConfig` and `CacheDynamicConfig`, which are subsets of `AppEnv` and `AppContext` respectively
The main goal of this is to help with the modularization of the engine: as `ServerConfigCtx` had fields whose types were imported from several unrelated parts of the engine, using it tied together parts of the engine that should not be aware of one another (such as tying together `Hasura.LogicalModel` and `Hasura.GraphQL.Schema`).
The bulk of this PR is a change to the cache build, as a follow up to #8509: instead of giving the entire `ServerConfigCtx` as a incremental rule argument, we only give the new `CacheDynamicConfig` struct, which has fewer fields. The other required fields, that were coming from the `AppEnv`, are now given via the `HasCacheStaticConfig` constraint, which is a "subset" of `HasAppEnv`.
(Some further work could include moving `StringifyNumbers` out of `GraphQL.Schema.Options`, given how it is used all across the codebase, including in `RQL.DML`.)
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/8513
GitOrigin-RevId: 818cbcd71494e3cd946b06adbb02ca328a8a298e
2023-04-04 18:59:58 +03:00
|
|
|
pure $ NT (run . flip MigrateSuite.runCacheRefT (dynamicConfig, cacheRef) . fmap fst . runMetadataT metadata emptyMetadataDefaults)
|
2022-11-17 15:55:05 +03:00
|
|
|
|
|
|
|
streamingSubscriptionSuite <- StreamingSubscriptionSuite.buildStreamingSubscriptionSuite
|
|
|
|
eventTriggerLogCleanupSuite <- EventTriggerCleanupSuite.buildEventTriggerCleanupSuite
|
|
|
|
|
|
|
|
hspec do
|
2023-05-24 16:51:56 +03:00
|
|
|
describe "Migrate suite"
|
|
|
|
$ beforeAll setupCacheRef
|
|
|
|
$ describe "Hasura.Server.Migrate"
|
|
|
|
$ MigrateSuite.suite sourceConfig pgContext pgConnInfo
|
2022-11-17 15:55:05 +03:00
|
|
|
describe "Streaming subscription suite" $ streamingSubscriptionSuite
|
|
|
|
describe "Event trigger log cleanup suite" $ eventTriggerLogCleanupSuite
|
|
|
|
|
|
|
|
printErrExit :: String -> IO a
|
|
|
|
printErrExit = (*> exitFailure) . putStrLn
|
|
|
|
|
2023-04-26 20:28:48 +03:00
|
|
|
printErrJExit :: (J.ToJSON a) => a -> IO b
|
|
|
|
printErrJExit = (*> exitFailure) . BL.putStrLn . J.encode
|
2023-02-24 21:09:36 +03:00
|
|
|
|
|
|
|
-- | Used only for 'runApp' above.
|
|
|
|
data TestMetricsSpec name metricType tags
|
|
|
|
= ServerSubset (ServerMetricsSpec name metricType tags)
|