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-02-24 21:09:36 +03:00
|
|
|
import Control.Monad.Trans.Managed (ManagedT (..))
|
2022-11-17 15:55:05 +03:00
|
|
|
import Control.Natural ((:~>) (..))
|
|
|
|
import Data.Aeson qualified as A
|
|
|
|
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
|
Rewrite `Tracing` to allow for only one `TraceT` in the entire stack.
This PR is on top of #7789.
### Description
This PR entirely rewrites the API of the Tracing library, to make `interpTraceT` a thing of the past. Before this change, we ran traces by sticking a `TraceT` on top of whatever we were doing. This had several major drawbacks:
- we were carrying a bunch of `TraceT` across the codebase, and the entire codebase had to know about it
- we needed to carry a second class constraint around (`HasReporterM`) to be able to run all of those traces
- we kept having to do stack rewriting with `interpTraceT`, which went from inconvenient to horrible
- we had to declare several behavioral instances on `TraceT m`
This PR rewrite all of `Tracing` using a more conventional model: there is ONE `TraceT` at the bottom of the stack, and there is an associated class constraint `MonadTrace`: any part of the code that happens to satisfy `MonadTrace` is able to create new traces. We NEVER have to do stack rewriting, `interpTraceT` is gone, and `TraceT` and `Reporter` become implementation details that 99% of the code is blissfully unaware of: code that needs to do tracing only needs to declare that the monad in which it operates implements `MonadTrace`.
In doing so, this PR revealed **several bugs in the codebase**: places where we were expecting to trace something, but due to the default instance of `HasReporterM IO` we would actually not do anything. This PR also splits the code of `Tracing` in more byte-sized modules, with the goal of potentially moving to `server/lib` down the line.
### Remaining work
This PR is a draft; what's left to do is:
- [x] make Pro compile; i haven't updated `HasuraPro/Main` yet
- [x] document Tracing by writing a note that explains how to use the library, and the meaning of "reporter", "trace" and "span", as well as the pitfalls
- [x] discuss some of the trade-offs in the implementation, which is why i'm opening this PR already despite it not fully building yet
- [x] it depends on #7789 being merged first
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7791
GitOrigin-RevId: cadd32d039134c93ddbf364599a2f4dd988adea8
2023-03-13 20:37:16 +03:00
|
|
|
( PGMetadataStorageAppT,
|
2023-02-24 21:09:36 +03:00
|
|
|
initGlobalCtx,
|
|
|
|
initialiseContext,
|
2022-11-17 15:55:05 +03:00
|
|
|
mkMSSQLSourceResolver,
|
|
|
|
mkPgSourceResolver,
|
Rewrite `Tracing` to allow for only one `TraceT` in the entire stack.
This PR is on top of #7789.
### Description
This PR entirely rewrites the API of the Tracing library, to make `interpTraceT` a thing of the past. Before this change, we ran traces by sticking a `TraceT` on top of whatever we were doing. This had several major drawbacks:
- we were carrying a bunch of `TraceT` across the codebase, and the entire codebase had to know about it
- we needed to carry a second class constraint around (`HasReporterM`) to be able to run all of those traces
- we kept having to do stack rewriting with `interpTraceT`, which went from inconvenient to horrible
- we had to declare several behavioral instances on `TraceT m`
This PR rewrite all of `Tracing` using a more conventional model: there is ONE `TraceT` at the bottom of the stack, and there is an associated class constraint `MonadTrace`: any part of the code that happens to satisfy `MonadTrace` is able to create new traces. We NEVER have to do stack rewriting, `interpTraceT` is gone, and `TraceT` and `Reporter` become implementation details that 99% of the code is blissfully unaware of: code that needs to do tracing only needs to declare that the monad in which it operates implements `MonadTrace`.
In doing so, this PR revealed **several bugs in the codebase**: places where we were expecting to trace something, but due to the default instance of `HasReporterM IO` we would actually not do anything. This PR also splits the code of `Tracing` in more byte-sized modules, with the goal of potentially moving to `server/lib` down the line.
### Remaining work
This PR is a draft; what's left to do is:
- [x] make Pro compile; i haven't updated `HasuraPro/Main` yet
- [x] document Tracing by writing a note that explains how to use the library, and the meaning of "reporter", "trace" and "span", as well as the pitfalls
- [x] discuss some of the trade-offs in the implementation, which is why i'm opening this PR already despite it not fully building yet
- [x] it depends on #7789 being merged first
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7791
GitOrigin-RevId: cadd32d039134c93ddbf364599a2f4dd988adea8
2023-03-13 20:37:16 +03:00
|
|
|
runPGMetadataStorageAppT,
|
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
|
2022-11-17 15:55:05 +03:00
|
|
|
import Hasura.GraphQL.Schema.Options qualified as Options
|
|
|
|
import Hasura.Logging
|
|
|
|
import Hasura.Prelude
|
|
|
|
import Hasura.RQL.DDL.Schema.Cache
|
|
|
|
import Hasura.RQL.DDL.Schema.Cache.Common
|
|
|
|
import Hasura.RQL.Types.Common
|
|
|
|
import Hasura.RQL.Types.Metadata (emptyMetadataDefaults)
|
|
|
|
import Hasura.RQL.Types.ResizePool
|
|
|
|
import Hasura.RQL.Types.SchemaCache.Build
|
|
|
|
import Hasura.Server.Init
|
2023-01-23 16:35:48 +03:00
|
|
|
import Hasura.Server.Init.FeatureFlag as FF
|
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-02-24 00:43:08 +03:00
|
|
|
{-# ANN main ("HLINT: ignore Use env_from_function_argument" :: String) #-}
|
2022-11-17 15:55:05 +03:00
|
|
|
main :: IO ()
|
|
|
|
main = do
|
|
|
|
env <- getEnvironment
|
|
|
|
let envMap = Env.mkEnvironment env
|
|
|
|
|
|
|
|
pgUrlText <- flip onLeft printErrExit $
|
|
|
|
runWithEnv env $ do
|
|
|
|
let envVar = _envVar databaseUrlOption
|
|
|
|
maybeV <- considerEnv envVar
|
|
|
|
onNothing maybeV $
|
|
|
|
throwError $
|
|
|
|
"Expected: " <> envVar
|
|
|
|
|
|
|
|
let pgConnInfo = PG.ConnInfo 1 $ PG.CDDatabaseURI $ txtToBs pgUrlText
|
|
|
|
urlConf = UrlValue $ InputWebhook $ mkPlainURLTemplate pgUrlText
|
|
|
|
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
|
|
|
|
|
|
|
pgPool <- PG.initPGPool pgConnInfo PG.defaultConnParams {PG.cpConns = 1} print
|
|
|
|
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
|
|
|
|
liftIO $ putStrLn $ LBS.toString $ A.encode $ EngineLog t logLevel logType logDetail
|
|
|
|
|
|
|
|
setupCacheRef = do
|
|
|
|
httpManager <- HTTP.newManager HTTP.tlsManagerSettings
|
2023-02-24 21:09:36 +03:00
|
|
|
globalCtx <- initGlobalCtx envMap metadataDbUrl rci
|
|
|
|
(_, 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
|
|
|
|
Options.Don'tOptimizePermissionFilters
|
|
|
|
Options.EnableBigQueryStringNumericInput
|
|
|
|
maintenanceMode = MaintenanceModeDisabled
|
|
|
|
readOnlyMode = ReadOnlyModeDisabled
|
|
|
|
serverConfigCtx =
|
|
|
|
ServerConfigCtx
|
|
|
|
Options.InferFunctionPermissions
|
|
|
|
Options.DisableRemoteSchemaPermissions
|
|
|
|
sqlGenCtx
|
|
|
|
maintenanceMode
|
|
|
|
mempty
|
|
|
|
EventingEnabled
|
|
|
|
readOnlyMode
|
2023-01-30 07:59:30 +03:00
|
|
|
(_default defaultNamingConventionOption)
|
2022-11-17 15:55:05 +03:00
|
|
|
emptyMetadataDefaults
|
2023-03-22 13:46:54 +03:00
|
|
|
(CheckFeatureFlag $ FF.checkFeatureFlag mempty)
|
2023-03-15 11:14:20 +03:00
|
|
|
ApolloFederationDisabled
|
2022-11-17 15:55:05 +03:00
|
|
|
cacheBuildParams = CacheBuildParams httpManager (mkPgSourceResolver print) mkMSSQLSourceResolver serverConfigCtx
|
|
|
|
|
2023-03-17 13:29:07 +03:00
|
|
|
(_appStateRef, appEnv) <- runManagedT
|
2023-02-24 21:09:36 +03:00
|
|
|
( initialiseContext
|
|
|
|
envMap
|
|
|
|
globalCtx
|
|
|
|
serveOptions
|
|
|
|
Nothing
|
|
|
|
serverMetrics
|
|
|
|
prometheusMetrics
|
|
|
|
sampleAlways
|
|
|
|
)
|
2023-03-17 13:29:07 +03:00
|
|
|
$ \(appStateRef, appEnv) -> return (appStateRef, appEnv)
|
2023-02-24 21:09:36 +03:00
|
|
|
|
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
|
|
|
let run :: ExceptT QErr (PGMetadataStorageAppT IO) a -> IO a
|
2022-11-17 15:55:05 +03:00
|
|
|
run =
|
2023-02-03 04:03:23 +03:00
|
|
|
runExceptT
|
2023-03-17 13:29:07 +03:00
|
|
|
>>> runPGMetadataStorageAppT 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
|
|
|
|
|
|
|
(metadata, schemaCache) <- run do
|
|
|
|
metadata <-
|
|
|
|
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)
|
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
|
|
|
schemaCache <- runCacheBuild cacheBuildParams $ buildRebuildableSchemaCache logger envMap metadata
|
2022-11-17 15:55:05 +03:00
|
|
|
pure (metadata, schemaCache)
|
|
|
|
|
|
|
|
cacheRef <- newMVar schemaCache
|
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
|
|
|
pure $ NT (run . flip MigrateSuite.runCacheRefT (serverConfigCtx, cacheRef) . fmap fst . runMetadataT metadata emptyMetadataDefaults)
|
2022-11-17 15:55:05 +03:00
|
|
|
|
|
|
|
streamingSubscriptionSuite <- StreamingSubscriptionSuite.buildStreamingSubscriptionSuite
|
|
|
|
eventTriggerLogCleanupSuite <- EventTriggerCleanupSuite.buildEventTriggerCleanupSuite
|
|
|
|
|
|
|
|
hspec do
|
|
|
|
describe "Migrate suite" $
|
|
|
|
beforeAll setupCacheRef $
|
|
|
|
describe "Hasura.Server.Migrate" $
|
|
|
|
MigrateSuite.suite sourceConfig pgContext pgConnInfo
|
|
|
|
describe "Streaming subscription suite" $ streamingSubscriptionSuite
|
|
|
|
describe "Event trigger log cleanup suite" $ eventTriggerLogCleanupSuite
|
|
|
|
|
|
|
|
printErrExit :: String -> IO a
|
|
|
|
printErrExit = (*> exitFailure) . putStrLn
|
|
|
|
|
|
|
|
printErrJExit :: (A.ToJSON a) => a -> IO b
|
|
|
|
printErrJExit = (*> exitFailure) . BL.putStrLn . A.encode
|
2023-02-24 21:09:36 +03:00
|
|
|
|
|
|
|
-- | Used only for 'runApp' above.
|
|
|
|
data TestMetricsSpec name metricType tags
|
|
|
|
= ServerSubset (ServerMetricsSpec name metricType tags)
|