2021-09-24 01:56:37 +03:00
|
|
|
{-# LANGUAGE NamedFieldPuns #-}
|
2019-11-26 15:14:21 +03:00
|
|
|
{-# LANGUAGE RecordWildCards #-}
|
2018-06-27 16:11:32 +03:00
|
|
|
|
2021-10-20 19:14:00 +03:00
|
|
|
module Main (main) where
|
2019-03-12 08:46:27 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
import Control.Concurrent.Extended qualified as C
|
|
|
|
import Control.Exception
|
|
|
|
import Control.Monad.Trans.Managed (ManagedT (..), lowerManagedT)
|
|
|
|
import Data.ByteString.Char8 qualified as BC
|
|
|
|
import Data.Environment qualified as Env
|
|
|
|
import Data.Int (Int64)
|
|
|
|
import Data.Kind (Type)
|
|
|
|
import Data.Text.Conversions (convertText)
|
|
|
|
import Data.Time.Clock (getCurrentTime)
|
|
|
|
import Data.Time.Clock.POSIX (getPOSIXTime)
|
|
|
|
import Database.PG.Query qualified as Q
|
|
|
|
import GHC.TypeLits (Symbol)
|
|
|
|
import Hasura.App
|
|
|
|
import Hasura.GC qualified as GC
|
|
|
|
import Hasura.Logging (Hasura, LogLevel (..), defaultEnabledEngineLogTypes)
|
|
|
|
import Hasura.Prelude
|
|
|
|
import Hasura.RQL.DDL.Schema
|
|
|
|
import Hasura.RQL.Types
|
|
|
|
import Hasura.Server.Init
|
|
|
|
import Hasura.Server.Metrics (ServerMetricsSpec, createServerMetrics)
|
|
|
|
import Hasura.Server.Migrate (downgradeCatalog)
|
|
|
|
import Hasura.Server.Version
|
|
|
|
import System.Exit qualified as Sys
|
|
|
|
import System.Metrics qualified as EKG
|
|
|
|
import System.Posix.Signals qualified as Signals
|
2018-06-27 16:11:32 +03:00
|
|
|
|
|
|
|
main :: IO ()
|
2020-07-14 22:00:58 +03:00
|
|
|
main = do
|
|
|
|
tryExit $ do
|
|
|
|
args <- parseArgs
|
2021-09-24 01:56:37 +03:00
|
|
|
env <- Env.getEnvironment
|
2020-11-25 13:56:44 +03:00
|
|
|
runApp env args
|
2020-07-14 22:00:58 +03:00
|
|
|
where
|
2021-09-24 01:56:37 +03:00
|
|
|
tryExit io =
|
|
|
|
try io >>= \case
|
|
|
|
Left (ExitException _code msg) -> BC.putStrLn msg >> Sys.exitFailure
|
|
|
|
Right r -> return r
|
2018-07-27 12:34:50 +03:00
|
|
|
|
2020-11-25 13:56:44 +03:00
|
|
|
runApp :: Env.Environment -> HGEOptions Hasura -> IO ()
|
2020-12-28 15:56:00 +03:00
|
|
|
runApp env (HGEOptionsG rci metadataDbUrl hgeCmd) = do
|
2020-11-24 09:10:04 +03:00
|
|
|
initTime <- liftIO getCurrentTime
|
2021-09-24 01:56:37 +03:00
|
|
|
globalCtx@GlobalCtx {..} <- initGlobalCtx env metadataDbUrl rci
|
|
|
|
let (maybeDefaultPgConnInfo, maybeRetries) = _gcDefaultPostgresConnInfo
|
2020-11-24 09:10:04 +03:00
|
|
|
|
2021-10-13 19:38:56 +03:00
|
|
|
case hgeCmd of
|
2019-11-26 15:14:21 +03:00
|
|
|
HCServe serveOptions -> do
|
2021-08-06 00:07:17 +03:00
|
|
|
(ekgStore, serverMetrics) <- liftIO $ do
|
|
|
|
store <- EKG.newStore @AppMetricsSpec
|
2021-09-22 18:34:53 +03:00
|
|
|
void $ EKG.register (EKG.subset GcSubset store) EKG.registerGcMetrics
|
2020-11-12 12:25:48 +03:00
|
|
|
|
2020-09-08 21:13:35 +03:00
|
|
|
let getTimeMs :: IO Int64
|
|
|
|
getTimeMs = (round . (* 1000)) `fmap` getPOSIXTime
|
2021-09-22 18:34:53 +03:00
|
|
|
void $ EKG.register store $ EKG.registerCounter ServerTimestampMs () getTimeMs
|
2020-09-08 21:13:35 +03:00
|
|
|
|
2021-08-06 00:07:17 +03:00
|
|
|
serverMetrics <-
|
|
|
|
liftIO $ createServerMetrics $ EKG.subset ServerSubset store
|
|
|
|
|
|
|
|
pure (EKG.subset EKG.emptyOf store, serverMetrics)
|
2020-11-12 12:25:48 +03:00
|
|
|
|
2020-12-21 21:56:00 +03:00
|
|
|
-- It'd be nice if we didn't have to call runManagedT twice here, but
|
|
|
|
-- there is a data dependency problem since the call to runPGMetadataStorageApp
|
|
|
|
-- below depends on serveCtx.
|
|
|
|
runManagedT (initialiseServeCtx env globalCtx serveOptions) $ \serveCtx -> do
|
|
|
|
-- Catches the SIGTERM signal and initiates a graceful shutdown.
|
|
|
|
-- Graceful shutdown for regular HTTP requests is already implemented in
|
|
|
|
-- Warp, and is triggered by invoking the 'closeSocket' callback.
|
|
|
|
-- We only catch the SIGTERM signal once, that is, if the user hits CTRL-C
|
|
|
|
-- once again, we terminate the process immediately.
|
2021-02-12 04:34:00 +03:00
|
|
|
|
|
|
|
-- The function is written in this style to avoid the shutdown
|
|
|
|
-- handler retaining a reference to the entire serveCtx (see #344)
|
|
|
|
-- If you modify this code then you should check the core to see
|
|
|
|
-- that serveCtx is not retained.
|
|
|
|
_ <- case serveCtx of
|
2021-09-24 01:56:37 +03:00
|
|
|
ServeCtx {_scShutdownLatch} ->
|
|
|
|
liftIO $ do
|
|
|
|
void $ Signals.installHandler Signals.sigTERM (Signals.CatchOnce (shutdownGracefully _scShutdownLatch)) Nothing
|
|
|
|
void $ Signals.installHandler Signals.sigINT (Signals.CatchOnce (shutdownGracefully _scShutdownLatch)) Nothing
|
2020-12-28 15:56:00 +03:00
|
|
|
|
|
|
|
let Loggers _ logger pgLogger = _scLoggers serveCtx
|
2021-04-06 06:25:02 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
_idleGCThread <-
|
|
|
|
C.forkImmortal "ourIdleGC" logger $
|
|
|
|
GC.ourIdleGC logger (seconds 0.3) (seconds 10) (seconds 60)
|
2020-12-28 15:56:00 +03:00
|
|
|
|
2021-05-26 19:19:26 +03:00
|
|
|
flip runPGMetadataStorageAppT (_scMetadataDbPool serveCtx, pgLogger) . lowerManagedT $ do
|
2021-02-13 03:05:23 +03:00
|
|
|
runHGEServer (const $ pure ()) env serveOptions serveCtx initTime Nothing serverMetrics ekgStore
|
2018-12-19 14:38:33 +03:00
|
|
|
HCExport -> do
|
2021-01-07 12:04:22 +03:00
|
|
|
res <- runTxWithMinimalPool _gcMetadataDbConnInfo fetchMetadataFromCatalog
|
2020-07-14 22:00:58 +03:00
|
|
|
either (printErrJExit MetadataExportError) printJSON res
|
2018-12-19 14:38:33 +03:00
|
|
|
HCClean -> do
|
2021-01-07 12:04:22 +03:00
|
|
|
res <- runTxWithMinimalPool _gcMetadataDbConnInfo dropHdbCatalogSchema
|
2020-11-24 09:10:04 +03:00
|
|
|
let cleanSuccessMsg = "successfully cleaned graphql-engine related data"
|
|
|
|
either (printErrJExit MetadataCleanError) (const $ liftIO $ putStrLn cleanSuccessMsg) res
|
2020-02-07 14:03:12 +03:00
|
|
|
HCDowngrade opts -> do
|
2021-09-24 01:56:37 +03:00
|
|
|
let defaultSourceConfig =
|
|
|
|
maybeDefaultPgConnInfo <&> \(dbUrlConf, _) ->
|
|
|
|
let pgSourceConnInfo =
|
|
|
|
PostgresSourceConnInfo
|
|
|
|
dbUrlConf
|
|
|
|
(Just setPostgresPoolSettings {_ppsRetries = maybeRetries <|> Just 1})
|
|
|
|
False
|
|
|
|
Q.ReadCommitted
|
|
|
|
Nothing
|
|
|
|
in PostgresConnConfiguration pgSourceConnInfo Nothing
|
2020-12-28 15:56:00 +03:00
|
|
|
res <- runTxWithMinimalPool _gcMetadataDbConnInfo $ downgradeCatalog defaultSourceConfig opts initTime
|
2020-07-14 22:00:58 +03:00
|
|
|
either (printErrJExit DowngradeProcessError) (liftIO . print) res
|
2020-01-23 00:55:55 +03:00
|
|
|
HCVersion -> liftIO $ putStrLn $ "Hasura GraphQL Engine: " ++ convertText currentVersion
|
2019-11-26 15:14:21 +03:00
|
|
|
where
|
2020-12-21 21:56:00 +03:00
|
|
|
runTxWithMinimalPool connInfo tx = lowerManagedT $ do
|
2020-11-24 09:10:04 +03:00
|
|
|
minimalPool <- mkMinimalPool connInfo
|
|
|
|
liftIO $ runExceptT $ Q.runTx minimalPool (Q.ReadCommitted, Nothing) tx
|
|
|
|
|
|
|
|
mkMinimalPool connInfo = do
|
|
|
|
pgLogger <- _lsPgLogger <$> mkLoggers defaultEnabledEngineLogTypes LevelInfo
|
2021-09-24 01:56:37 +03:00
|
|
|
let connParams = Q.defaultConnParams {Q.cpConns = 1}
|
2020-11-24 09:10:04 +03:00
|
|
|
liftIO $ Q.initPGPool connInfo connParams pgLogger
|
2021-08-06 00:07:17 +03:00
|
|
|
|
|
|
|
-- | A specification of all EKG metrics tracked in `runApp`.
|
2021-09-24 01:56:37 +03:00
|
|
|
data
|
|
|
|
AppMetricsSpec ::
|
|
|
|
Symbol -> -- Metric name
|
|
|
|
EKG.MetricType -> -- Metric type, e.g. Counter, Gauge
|
|
|
|
Type -> -- Tag structure
|
|
|
|
Type
|
2021-08-06 00:07:17 +03:00
|
|
|
where
|
2021-09-24 01:56:37 +03:00
|
|
|
ServerSubset ::
|
|
|
|
ServerMetricsSpec name metricType tags ->
|
|
|
|
AppMetricsSpec name metricType tags
|
|
|
|
GcSubset ::
|
|
|
|
EKG.GcMetrics name metricType tags ->
|
|
|
|
AppMetricsSpec name metricType tags
|
|
|
|
ServerTimestampMs ::
|
|
|
|
AppMetricsSpec "ekg.server_timestamp_ms" 'EKG.CounterType ()
|