graphql-engine/server/src-lib/Hasura/Server/Init.hs

Ignoring revisions in .git-blame-ignore-revs. Click here to bypass and see the normal blame view.

1484 lines
46 KiB
Haskell
Raw Normal View History

{-# LANGUAGE ApplicativeDo #-}
{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -O0 #-}
-- | Types and functions related to the server initialisation
module Hasura.Server.Init
( module Hasura.Server.Init,
module Hasura.Server.Init.Config,
)
where
import Data.Aeson qualified as J
import Data.Aeson.TH qualified as J
import Data.ByteString.Char8 (pack, unpack)
import Data.FileEmbed (embedStringFile, makeRelativeToProject)
import Data.HashSet qualified as Set
import Data.String qualified as DataString
import Data.Text qualified as T
import Data.Text.Encoding (encodeUtf8)
import Data.Time (NominalDiffTime)
import Data.URL.Template
import Database.PG.Query qualified as Q
import Hasura.Backends.Postgres.Connection
import Hasura.Base.Error
import Hasura.Cache.Bounded qualified as Cache (CacheSize, parseCacheSize)
import Hasura.Eventing.EventTrigger (defaultFetchBatchSize)
import Hasura.GraphQL.Execute.LiveQuery.Options qualified as LQ
import Hasura.Logging qualified as L
import Hasura.Prelude
import Hasura.RQL.Types
import Hasura.Server.Auth
import Hasura.Server.Cors
import Hasura.Server.Init.Config
import Hasura.Server.Logging
import Hasura.Server.Types
import Hasura.Server.Utils
import Hasura.Session
import Language.Haskell.TH.Syntax qualified as TH
import Network.HTTP.Types.URI
( Query,
QueryItem,
parseQuery,
renderQuery,
)
import Network.URI (URI (..), parseURI, uriQuery)
import Network.Wai.Handler.Warp (HostPreference)
import Network.WebSockets qualified as WS
import Options.Applicative
import Text.PrettyPrint.ANSI.Leijen qualified as PP
getDbId :: Q.TxE QErr Text
getDbId =
runIdentity . Q.getRow
<$> Q.withQE
defaultTxErrorHandler
[Q.sql|
SELECT (hasura_uuid :: text) FROM hdb_catalog.hdb_version
|]
()
False
getPgVersion :: Q.TxE QErr PGVersion
getPgVersion = PGVersion <$> Q.serverVersion
generateInstanceId :: IO InstanceId
generateInstanceId = InstanceId <$> generateFingerprint
data StartupTimeInfo = StartupTimeInfo
{ _stiMessage :: !Text,
_stiTimeTaken :: !Double
}
$(J.deriveJSON hasuraJSON ''StartupTimeInfo)
2018-06-27 16:11:32 +03:00
returnJust :: Monad m => a -> m (Maybe a)
returnJust = return . Just
considerEnv :: FromEnv a => String -> WithEnv (Maybe a)
considerEnv envVar = do
env <- ask
case lookup envVar env of
Nothing -> return Nothing
Just val -> either throwErr returnJust $ fromEnv val
where
throwErr s =
throwError $
"Fatal Error:- Environment variable " ++ envVar ++ ": " ++ s
considerEnvs :: FromEnv a => [String] -> WithEnv (Maybe a)
considerEnvs envVars = foldl1 (<|>) <$> mapM considerEnv envVars
withEnv :: FromEnv a => Maybe a -> String -> WithEnv (Maybe a)
withEnv mVal envVar =
maybe (considerEnv envVar) returnJust mVal
withEnvs :: FromEnv a => Maybe a -> [String] -> WithEnv (Maybe a)
withEnvs mVal envVars =
maybe (considerEnvs envVars) returnJust mVal
withEnvBool :: Bool -> String -> WithEnv Bool
withEnvBool bVal envVar =
bool considerEnv' (return True) bVal
where
considerEnv' = do
mEnvVal <- considerEnv envVar
return $ Just True == mEnvVal
withEnvJwtConf :: Maybe JWTConfig -> String -> WithEnv (Maybe JWTConfig)
withEnvJwtConf jVal envVar =
maybe (considerEnv envVar) returnJust jVal
mkHGEOptions ::
L.EnabledLogTypes impl => RawHGEOptions impl -> WithEnv (HGEOptions impl)
mkHGEOptions (HGEOptionsG rawDbUrl rawMetadataDbUrl rawCmd) =
HGEOptionsG <$> dbUrl <*> metadataDbUrl <*> cmd
where
dbUrl = processPostgresConnInfo rawDbUrl
metadataDbUrl = withEnv rawMetadataDbUrl $ fst metadataDbUrlEnv
cmd = case rawCmd of
HCServe rso -> HCServe <$> mkServeOptions rso
HCExport -> return HCExport
HCClean -> return HCClean
HCVersion -> return HCVersion
HCDowngrade tgt -> return (HCDowngrade tgt)
processPostgresConnInfo ::
PostgresConnInfo (Maybe PostgresRawConnInfo) ->
WithEnv (PostgresConnInfo (Maybe UrlConf))
processPostgresConnInfo PostgresConnInfo {..} = do
withEnvRetries <- withEnv _pciRetries $ fst retriesNumEnv
databaseUrl <- rawConnInfoToUrlConf _pciDatabaseConn
pure $ PostgresConnInfo databaseUrl withEnvRetries
rawConnInfoToUrlConf :: Maybe PostgresRawConnInfo -> WithEnv (Maybe UrlConf)
rawConnInfoToUrlConf maybeRawConnInfo = do
env <- ask
let databaseUrlEnvVar = fst databaseUrlEnv
hasDatabaseUrlEnv = any ((== databaseUrlEnvVar) . fst) env
pure $ case maybeRawConnInfo of
-- If no --database-url or connection options provided in CLI command
Nothing ->
if hasDatabaseUrlEnv
then -- Consider env variable as is in order to store it as @`UrlConf`
-- in default source configuration in metadata
Just $ UrlFromEnv $ T.pack databaseUrlEnvVar
else Nothing
Just databaseConn ->
Just . UrlValue . InputWebhook $ case databaseConn of
PGConnDatabaseUrl urlTemplate -> urlTemplate
PGConnDetails connDetails -> rawConnDetailsToUrl connDetails
mkServeOptions :: L.EnabledLogTypes impl => RawServeOptions impl -> WithEnv (ServeOptions impl)
mkServeOptions rso = do
port <-
fromMaybe 8080
<$> withEnv (rsoPort rso) (fst servePortEnv)
host <-
fromMaybe "*"
<$> withEnv (rsoHost rso) (fst serveHostEnv)
connParams <- mkConnParams $ rsoConnParams rso
txIso <- fromMaybe Q.ReadCommitted <$> withEnv (rsoTxIso rso) (fst txIsoEnv)
adminScrt <- withEnvs (rsoAdminSecret rso) $ map fst [adminSecretEnv, accessKeyEnv]
authHook <- mkAuthHook $ rsoAuthHook rso
jwtSecret <- withEnvJwtConf (rsoJwtSecret rso) $ fst jwtSecretEnv
unAuthRole <- withEnv (rsoUnAuthRole rso) $ fst unAuthRoleEnv
corsCfg <- mkCorsConfig $ rsoCorsConfig rso
enableConsole <-
withEnvBool (rsoEnableConsole rso) $
fst enableConsoleEnv
consoleAssetsDir <- withEnv (rsoConsoleAssetsDir rso) (fst consoleAssetsDirEnv)
enableTelemetry <-
fromMaybe True
<$> withEnv (rsoEnableTelemetry rso) (fst enableTelemetryEnv)
strfyNum <- withEnvBool (rsoStringifyNum rso) $ fst stringifyNumEnv
dangerousBooleanCollapse <-
fromMaybe False <$> withEnv (rsoDangerousBooleanCollapse rso) (fst dangerousBooleanCollapseEnv)
enabledAPIs <-
Set.fromList . fromMaybe defaultEnabledAPIs
<$> withEnv (rsoEnabledAPIs rso) (fst enabledAPIsEnv)
2019-04-17 12:48:41 +03:00
lqOpts <- mkLQOpts
enableAL <- withEnvBool (rsoEnableAllowlist rso) $ fst enableAllowlistEnv
enabledLogs <-
maybe L.defaultEnabledLogTypes Set.fromList
<$> withEnv (rsoEnabledLogTypes rso) (fst enabledLogsEnv)
serverLogLevel <- fromMaybe L.LevelInfo <$> withEnv (rsoLogLevel rso) (fst logLevelEnv)
devMode <- withEnvBool (rsoDevMode rso) $ fst devModeEnv
adminInternalErrors <-
fromMaybe True
<$> withEnv (rsoAdminInternalErrors rso) (fst adminInternalErrorsEnv) -- Default to `true` to enable backwards compatibility
let internalErrorsConfig =
if
| devMode -> InternalErrorsAllRequests
| adminInternalErrors -> InternalErrorsAdminOnly
| otherwise -> InternalErrorsDisabled
eventsHttpPoolSize <- withEnv (rsoEventsHttpPoolSize rso) (fst eventsHttpPoolSizeEnv)
eventsFetchInterval <- withEnv (rsoEventsFetchInterval rso) (fst eventsFetchIntervalEnv)
maybeAsyncActionsFetchInterval <- withEnv (rsoAsyncActionsFetchInterval rso) (fst asyncActionsFetchIntervalEnv)
logHeadersFromEnv <- withEnvBool (rsoLogHeadersFromEnv rso) (fst logHeadersFromEnvEnv)
enableRemoteSchemaPerms <-
bool RemoteSchemaPermsDisabled RemoteSchemaPermsEnabled
<$> withEnvBool (rsoEnableRemoteSchemaPermissions rso) (fst enableRemoteSchemaPermsEnv)
webSocketCompressionFromEnv <-
withEnvBool (rsoWebSocketCompression rso) $
fst webSocketCompressionEnv
Disable schema sync with an interval of 0 instead of an explicit flag Removing `schemaSyncDisable` flag and interpreting `schemaPollInterval` of `0` as disabling schema sync. This change brings the convention in line with how action and other intervals are used to disable processes. There is an opportunity to abstract the notion of an optional interval similar to how actions uses `AsyncActionsFetchInterval`. This can be used for the following fields of ServeOptions, with RawServeOptions having a milliseconds value where `0` is interpreted as disable. OptionalInterval: ``` -- | Sleep time interval for activities data OptionalInterval = Skip -- ^ No polling | Interval !Milliseconds -- ^ Interval time deriving (Show, Eq) ``` ServeOptions: ``` data ServeOptions impl = ServeOptions { ... , soEventsFetchInterval :: !OptionalInterval , soAsyncActionsFetchInterval :: !OptionalInterval , soSchemaPollInterval :: !OptionalInterval ... } ``` Rather than encoding a `Maybe OptionalInterval` in RawServeOptions, instead a `Maybe Milliseconds` can be used to more directly express the input format, with the ServeOptions constructor interpreting `0` as `Skip`. Current inconsistencies: * `soEventsFetchInterval` has no value interpreted as disabling the fetches * `soAsyncActionsFetchInterval` uses an `OptionalInterval` analog in `RawServeOptions` instead of `Milliseconds` * `soSchemaPollInterval` currently uses `Milliseconds` directly in `ServeOptions` --- ### Kodiak commit message Information used by [Kodiak bot](https://kodiakhq.com/) while merging this PR. #### Commit title Same as the title of this pull request GitOrigin-RevId: 3cda1656ae39ae95ba142512ed4e123d6ffeb7fe
2021-04-07 12:59:48 +03:00
maybeSchemaPollInterval <- withEnv (rsoSchemaPollInterval rso) (fst schemaPollIntervalEnv)
let connectionOptions =
WS.defaultConnectionOptions
{ WS.connectionCompressionOptions =
if webSocketCompressionFromEnv
then WS.PermessageDeflateCompression WS.defaultPermessageDeflate
else WS.NoCompression
}
Disable schema sync with an interval of 0 instead of an explicit flag Removing `schemaSyncDisable` flag and interpreting `schemaPollInterval` of `0` as disabling schema sync. This change brings the convention in line with how action and other intervals are used to disable processes. There is an opportunity to abstract the notion of an optional interval similar to how actions uses `AsyncActionsFetchInterval`. This can be used for the following fields of ServeOptions, with RawServeOptions having a milliseconds value where `0` is interpreted as disable. OptionalInterval: ``` -- | Sleep time interval for activities data OptionalInterval = Skip -- ^ No polling | Interval !Milliseconds -- ^ Interval time deriving (Show, Eq) ``` ServeOptions: ``` data ServeOptions impl = ServeOptions { ... , soEventsFetchInterval :: !OptionalInterval , soAsyncActionsFetchInterval :: !OptionalInterval , soSchemaPollInterval :: !OptionalInterval ... } ``` Rather than encoding a `Maybe OptionalInterval` in RawServeOptions, instead a `Maybe Milliseconds` can be used to more directly express the input format, with the ServeOptions constructor interpreting `0` as `Skip`. Current inconsistencies: * `soEventsFetchInterval` has no value interpreted as disabling the fetches * `soAsyncActionsFetchInterval` uses an `OptionalInterval` analog in `RawServeOptions` instead of `Milliseconds` * `soSchemaPollInterval` currently uses `Milliseconds` directly in `ServeOptions` --- ### Kodiak commit message Information used by [Kodiak bot](https://kodiakhq.com/) while merging this PR. #### Commit title Same as the title of this pull request GitOrigin-RevId: 3cda1656ae39ae95ba142512ed4e123d6ffeb7fe
2021-04-07 12:59:48 +03:00
asyncActionsFetchInterval = maybe defaultAsyncActionsFetchInterval msToOptionalInterval maybeAsyncActionsFetchInterval
schemaPollInterval = maybe defaultSchemaPollInterval msToOptionalInterval maybeSchemaPollInterval
webSocketKeepAlive <-
KeepAliveDelay . fromIntegral . fromMaybe 5
<$> withEnv (rsoWebSocketKeepAlive rso) (fst webSocketKeepAliveEnv)
[Preview] Inherited roles for postgres read queries fixes #3868 docker image - `hasura/graphql-engine:inherited-roles-preview-48b73a2de` Note: To be able to use the inherited roles feature, the graphql-engine should be started with the env variable `HASURA_GRAPHQL_EXPERIMENTAL_FEATURES` set to `inherited_roles`. Introduction ------------ This PR implements the idea of multiple roles as presented in this [paper](https://www.microsoft.com/en-us/research/wp-content/uploads/2016/02/FGALanguageICDE07.pdf). The multiple roles feature in this PR can be used via inherited roles. An inherited role is a role which can be created by combining multiple singular roles. For example, if there are two roles `author` and `editor` configured in the graphql-engine, then we can create a inherited role with the name of `combined_author_editor` role which will combine the select permissions of the `author` and `editor` roles and then make GraphQL queries using the `combined_author_editor`. How are select permissions of different roles are combined? ------------------------------------------------------------ A select permission includes 5 things: 1. Columns accessible to the role 2. Row selection filter 3. Limit 4. Allow aggregation 5. Scalar computed fields accessible to the role Suppose there are two roles, `role1` gives access to the `address` column with row filter `P1` and `role2` gives access to both the `address` and the `phone` column with row filter `P2` and we create a new role `combined_roles` which combines `role1` and `role2`. Let's say the following GraphQL query is queried with the `combined_roles` role. ```graphql query { employees { address phone } } ``` This will translate to the following SQL query: ```sql select (case when (P1 or P2) then address else null end) as address, (case when P2 then phone else null end) as phone from employee where (P1 or P2) ``` The other parameters of the select permission will be combined in the following manner: 1. Limit - Minimum of the limits will be the limit of the inherited role 2. Allow aggregations - If any of the role allows aggregation, then the inherited role will allow aggregation 3. Scalar computed fields - same as table column fields, as in the above example APIs for inherited roles: ---------------------- 1. `add_inherited_role` `add_inherited_role` is the [metadata API](https://hasura.io/docs/1.0/graphql/core/api-reference/index.html#schema-metadata-api) to create a new inherited role. It accepts two arguments `role_name`: the name of the inherited role to be added (String) `role_set`: list of roles that need to be combined (Array of Strings) Example: ```json { "type": "add_inherited_role", "args": { "role_name":"combined_user", "role_set":[ "user", "user1" ] } } ``` After adding the inherited role, the inherited role can be used like single roles like earlier Note: An inherited role can only be created with non-inherited/singular roles. 2. `drop_inherited_role` The `drop_inherited_role` API accepts the name of the inherited role and drops it from the metadata. It accepts a single argument: `role_name`: name of the inherited role to be dropped Example: ```json { "type": "drop_inherited_role", "args": { "role_name":"combined_user" } } ``` Metadata --------- The derived roles metadata will be included under the `experimental_features` key while exporting the metadata. ```json { "experimental_features": { "derived_roles": [ { "role_name": "manager_is_employee_too", "role_set": [ "employee", "manager" ] } ] } } ``` Scope ------ Only postgres queries and subscriptions are supported in this PR. Important points: ----------------- 1. All columns exposed to an inherited role will be marked as `nullable`, this is done so that cell value nullification can be done. TODOs ------- - [ ] Tests - [ ] Test a GraphQL query running with a inherited role without enabling inherited roles in experimental features - [] Tests for aggregate queries, limit, computed fields, functions, subscriptions (?) - [ ] Introspection test with a inherited role (nullability changes in a inherited role) - [ ] Docs - [ ] Changelog Co-authored-by: Vamshi Surabhi <6562944+0x777@users.noreply.github.com> GitOrigin-RevId: 3b8ee1e11f5ceca80fe294f8c074d42fbccfec63
2021-03-08 14:14:13 +03:00
experimentalFeatures <- maybe mempty Set.fromList <$> withEnv (rsoExperimentalFeatures rso) (fst experimentalFeaturesEnv)
inferFunctionPerms <-
maybe FunctionPermissionsInferred (bool FunctionPermissionsManual FunctionPermissionsInferred)
<$> withEnv (rsoInferFunctionPermissions rso) (fst inferFunctionPermsEnv)
maintenanceMode <-
bool MaintenanceModeDisabled MaintenanceModeEnabled
<$> withEnvBool (rsoEnableMaintenanceMode rso) (fst maintenanceModeEnv)
eventsFetchBatchSize <-
fromMaybe defaultFetchBatchSize
<$> withEnv (rsoEventsFetchBatchSize rso) (fst eventsFetchBatchSizeEnv)
gracefulShutdownTime <-
fromMaybe 60 <$> withEnv (rsoGracefulShutdownTimeout rso) (fst gracefulShutdownEnv)
webSocketConnectionInitTimeout <-
WSConnectionInitTimeout . fromIntegral . fromMaybe 3
<$> withEnv (rsoWebSocketConnectionInitTimeout rso) (fst webSocketConnectionInitTimeoutEnv)
pure $
ServeOptions
port
host
connParams
txIso
adminScrt
authHook
jwtSecret
unAuthRole
corsCfg
enableConsole
consoleAssetsDir
enableTelemetry
strfyNum
dangerousBooleanCollapse
enabledAPIs
lqOpts
enableAL
enabledLogs
serverLogLevel
internalErrorsConfig
eventsHttpPoolSize
eventsFetchInterval
asyncActionsFetchInterval
logHeadersFromEnv
enableRemoteSchemaPerms
connectionOptions
webSocketKeepAlive
inferFunctionPerms
maintenanceMode
schemaPollInterval
experimentalFeatures
eventsFetchBatchSize
devMode
gracefulShutdownTime
webSocketConnectionInitTimeout
where
Disable schema sync with an interval of 0 instead of an explicit flag Removing `schemaSyncDisable` flag and interpreting `schemaPollInterval` of `0` as disabling schema sync. This change brings the convention in line with how action and other intervals are used to disable processes. There is an opportunity to abstract the notion of an optional interval similar to how actions uses `AsyncActionsFetchInterval`. This can be used for the following fields of ServeOptions, with RawServeOptions having a milliseconds value where `0` is interpreted as disable. OptionalInterval: ``` -- | Sleep time interval for activities data OptionalInterval = Skip -- ^ No polling | Interval !Milliseconds -- ^ Interval time deriving (Show, Eq) ``` ServeOptions: ``` data ServeOptions impl = ServeOptions { ... , soEventsFetchInterval :: !OptionalInterval , soAsyncActionsFetchInterval :: !OptionalInterval , soSchemaPollInterval :: !OptionalInterval ... } ``` Rather than encoding a `Maybe OptionalInterval` in RawServeOptions, instead a `Maybe Milliseconds` can be used to more directly express the input format, with the ServeOptions constructor interpreting `0` as `Skip`. Current inconsistencies: * `soEventsFetchInterval` has no value interpreted as disabling the fetches * `soAsyncActionsFetchInterval` uses an `OptionalInterval` analog in `RawServeOptions` instead of `Milliseconds` * `soSchemaPollInterval` currently uses `Milliseconds` directly in `ServeOptions` --- ### Kodiak commit message Information used by [Kodiak bot](https://kodiakhq.com/) while merging this PR. #### Commit title Same as the title of this pull request GitOrigin-RevId: 3cda1656ae39ae95ba142512ed4e123d6ffeb7fe
2021-04-07 12:59:48 +03:00
defaultAsyncActionsFetchInterval = Interval 1000 -- 1000 Milliseconds or 1 Second
defaultSchemaPollInterval = Interval 1000 -- 1000 Milliseconds or 1 Second
mkConnParams (RawConnParams s c i cl p pt) = do
stripes <- fromMaybe 1 <$> withEnv s (fst pgStripesEnv)
-- Note: by Little's Law we can expect e.g. (with 50 max connections) a
-- hard throughput cap at 1000RPS when db queries take 50ms on average:
conns <- fromMaybe 50 <$> withEnv c (fst pgConnsEnv)
iTime <- fromMaybe 180 <$> withEnv i (fst pgTimeoutEnv)
connLifetime <- withEnv cl (fst pgConnLifetimeEnv) <&> parseConnLifeTime
allowPrepare <- fromMaybe True <$> withEnv p (fst pgUsePrepareEnv)
poolTimeout <- withEnv pt (fst pgPoolTimeoutEnv)
server: operation timeout with postgres cancelling ### Description This PR implements operation timeouts, as specced in #1232. RFC: [rfcs/operation-timeout-api-limits.md](https://github.com/hasura/graphql-engine-mono/blob/c025a90fe9779436bc0188a2bbf0ad95b5ed1f32/rfcs/operation-timeout-api-limits.md) There's still some things to be done (tests and docs most notably), but apart from that it can be reviewed. I'd still appreciate feedback on the RFC! TODO: - [x] break out the `ApiLimits` refactoring into a separate PR: #2103 - [x] finish the `pg-client-hs` PR: https://github.com/hasura/pg-client-hs/pull/39 - [x] remove configurability, after testing, prior to merging - [ ] tests: #2390 has some tests that I've run locally to confirm things work on a fundamental level - [x] changelog - [x] documentation - [x] fill in the detailed PR checklist ### Changelog - [x] `CHANGELOG.md` is updated with user-facing content relevant to this PR. If no changelog is required, then add the `no-changelog-required` label. ### Affected components - [x] Server - [ ] Console - [ ] CLI - [x] Docs - [ ] Tests ### Related Issues Product spec: #1232. ### Solution and Design Compare `rfcs/operation-timeout-api-limits.md`. ### Steps to test and verify Configure operation timeouts, e.g. by posting ``` { "type": "set_api_limits", "args": { "operation_timeout": { "global": 3 } } } ``` to `v1/metadata` to set an operation timeout of 3s. Then verify that 1. non-admin queries that take longer than 3s time out with a nice error message 2. that those queries return after ~3s (at least for postgres) 3. also that everything else still works as usual ### Limitations, known bugs & workarounds - while this will cause slow queries against any backends to fail, it's only verified to actually interrupt queries against postgres - this will only successfully short-cut (cancel) queries to postgres if the database server is responsive #### Catalog upgrade Does this PR change Hasura Catalog version? - [x] No #### Metadata Does this PR add a new Metadata feature? - [x] Yes - Does `run_sql` auto manages the new metadata through schema diffing? - [x] Not required - Does `run_sql` auto manages the definitions of metadata on renaming? - [x] Not required - Does `export_metadata`/`replace_metadata` supports the new metadata added? - [x] Yes #### GraphQL - [x] No new GraphQL schema is generated #### Breaking changes - [x] No Breaking changes PR-URL: https://github.com/hasura/graphql-engine-mono/pull/1593 GitOrigin-RevId: f0582d0be3ed9fadf89e0c4aaf96344d18331dc4
2021-09-29 19:20:06 +03:00
let allowCancel = True
return $
Q.ConnParams
stripes
conns
iTime
allowPrepare
connLifetime
poolTimeout
server: operation timeout with postgres cancelling ### Description This PR implements operation timeouts, as specced in #1232. RFC: [rfcs/operation-timeout-api-limits.md](https://github.com/hasura/graphql-engine-mono/blob/c025a90fe9779436bc0188a2bbf0ad95b5ed1f32/rfcs/operation-timeout-api-limits.md) There's still some things to be done (tests and docs most notably), but apart from that it can be reviewed. I'd still appreciate feedback on the RFC! TODO: - [x] break out the `ApiLimits` refactoring into a separate PR: #2103 - [x] finish the `pg-client-hs` PR: https://github.com/hasura/pg-client-hs/pull/39 - [x] remove configurability, after testing, prior to merging - [ ] tests: #2390 has some tests that I've run locally to confirm things work on a fundamental level - [x] changelog - [x] documentation - [x] fill in the detailed PR checklist ### Changelog - [x] `CHANGELOG.md` is updated with user-facing content relevant to this PR. If no changelog is required, then add the `no-changelog-required` label. ### Affected components - [x] Server - [ ] Console - [ ] CLI - [x] Docs - [ ] Tests ### Related Issues Product spec: #1232. ### Solution and Design Compare `rfcs/operation-timeout-api-limits.md`. ### Steps to test and verify Configure operation timeouts, e.g. by posting ``` { "type": "set_api_limits", "args": { "operation_timeout": { "global": 3 } } } ``` to `v1/metadata` to set an operation timeout of 3s. Then verify that 1. non-admin queries that take longer than 3s time out with a nice error message 2. that those queries return after ~3s (at least for postgres) 3. also that everything else still works as usual ### Limitations, known bugs & workarounds - while this will cause slow queries against any backends to fail, it's only verified to actually interrupt queries against postgres - this will only successfully short-cut (cancel) queries to postgres if the database server is responsive #### Catalog upgrade Does this PR change Hasura Catalog version? - [x] No #### Metadata Does this PR add a new Metadata feature? - [x] Yes - Does `run_sql` auto manages the new metadata through schema diffing? - [x] Not required - Does `run_sql` auto manages the definitions of metadata on renaming? - [x] Not required - Does `export_metadata`/`replace_metadata` supports the new metadata added? - [x] Yes #### GraphQL - [x] No new GraphQL schema is generated #### Breaking changes - [x] No Breaking changes PR-URL: https://github.com/hasura/graphql-engine-mono/pull/1593 GitOrigin-RevId: f0582d0be3ed9fadf89e0c4aaf96344d18331dc4
2021-09-29 19:20:06 +03:00
allowCancel
mkAuthHook (AuthHookG mUrl mType) = do
mUrlEnv <- withEnv mUrl $ fst authHookEnv
authModeM <- withEnv mType (fst authHookModeEnv)
ty <- onNothing authModeM (authHookTyEnv mType)
return (flip AuthHookG ty <$> mUrlEnv)
-- Also support HASURA_GRAPHQL_AUTH_HOOK_TYPE
Rewrite GraphQL schema generation and query parsing (close #2801) (#4111) Aka “the PDV refactor.” History is preserved on the branch 2801-graphql-schema-parser-refactor. * [skip ci] remove stale benchmark commit from commit_diff * [skip ci] Check for root field name conflicts between remotes * [skip ci] Additionally check for conflicts between remotes and DB * [skip ci] Check for conflicts in schema when tracking a table * [skip ci] Fix equality checking in GraphQL AST * server: fix mishandling of GeoJSON inputs in subscriptions (fix #3239) (#4551) * Add support for multiple top-level fields in a subscription to improve testability of subscriptions * Add an internal flag to enable multiple subscriptions * Add missing call to withConstructorFn in live queries (fix #3239) Co-authored-by: Alexis King <lexi.lambda@gmail.com> * Scheduled triggers (close #1914) (#3553) server: add scheduled triggers Co-authored-by: Alexis King <lexi.lambda@gmail.com> Co-authored-by: Marion Schleifer <marion@hasura.io> Co-authored-by: Karthikeyan Chinnakonda <karthikeyan@hasura.io> Co-authored-by: Aleksandra Sikora <ola.zxcvbnm@gmail.com> * dev.sh: bump version due to addition of croniter python dependency * server: fix an introspection query caching issue (fix #4547) (#4661) Introspection queries accept variables, but we need to make sure to also touch the variables that we ignore, so that an introspection query is marked not reusable if we are not able to build a correct query plan for it. A better solution here would be to deal with such unused variables correctly, so that more introspection queries become reusable. An even better solution would be to type-safely track *how* to reuse which variables, rather than to split the reusage marking from the planning. Co-authored-by: Tirumarai Selvan <tiru@hasura.io> * flush log buffer on exception in mkWaiApp ( fix #4772 ) (#4801) * flush log buffer on exception in mkWaiApp * add comment to explain the introduced change * add changelog * allow logging details of a live query polling thread (#4959) * changes for poller-log add various multiplexed query info in poller-log * minor cleanup, also fixes a bug which will return duplicate data * Live query poller stats can now be logged This also removes in-memory stats that are collected about batched query execution as the log lines when piped into an monitoring tool will give us better insights. * allow poller-log to be configurable * log minimal information in the livequery-poller-log Other information can be retrieved from /dev/subscriptions/extended * fix few review comments * avoid marshalling and unmarshalling from ByteString to EncJSON * separate out SubscriberId and SubscriberMetadata Co-authored-by: Anon Ray <rayanon004@gmail.com> * Don't compile in developer APIs by default * Tighten up handling of admin secret, more docs Store the admin secret only as a hash to prevent leaking the secret inadvertently, and to prevent timing attacks on the secret. NOTE: best practice for stored user passwords is a function with a tunable cost like bcrypt, but our threat model is quite different (even if we thought we could reasonably protect the secret from an attacker who could read arbitrary regions of memory), and bcrypt is far too slow (by design) to perform on each request. We'd have to rely on our (technically savvy) users to choose high entropy passwords in any case. Referencing #4736 * server/docs: add instructions to fix loss of float precision in PostgreSQL <= 11 (#5187) This adds a server flag, --pg-connection-options, that can be used to set a PostgreSQL connection parameter, extra_float_digits, that needs to be used to avoid loss of data on older versions of PostgreSQL, which have odd default behavior when returning float values. (fixes #5092) * [skip ci] Add new commits from master to the commit diff * [skip ci] serve default directives (skip & include) over introspection * [skip ci] Update non-Haskell assets with the version on master * server: refactor GQL execution check and config API (#5094) Co-authored-by: Vamshi Surabhi <vamshi@hasura.io> Co-authored-by: Vamshi Surabhi <0x777@users.noreply.github.com> * [skip ci] fix js issues in tests by pinning dependencies version * [skip ci] bump graphql version * [skip ci] Add note about memory usage * generalize query execution logic on Postgres (#5110) * generalize PGExecCtx to support specialized functions for various operations * fix tests compilation * allow customising PGExecCtx when starting the web server * server: changes catalog initialization and logging for pro customization (#5139) * new typeclass to abstract the logic of QueryLog-ing * abstract the logic of logging websocket-server logs introduce a MonadWSLog typeclass * move catalog initialization to init step expose a helper function to migrate catalog create schema cache in initialiseCtx * expose various modules and functions for pro * [skip ci] cosmetic change * [skip ci] fix test calling a mutation that does not exist * [skip ci] minor text change * [skip ci] refactored input values * [skip ci] remove VString Origin * server: fix updating of headers behaviour in the update cron trigger API and create future events immediately (#5151) * server: fix bug to update headers in an existing cron trigger and create future events Co-authored-by: Tirumarai Selvan <tiru@hasura.io> * Lower stack chunk size in RTS to reduce thread STACK memory (closes #5190) This reduces memory consumption for new idle subscriptions significantly (see linked ticket). The hypothesis is: we fork a lot of threads per websocket, and some of these use slightly more than the initial 1K stack size, so the first overflow balloons to 32K, when significantly less is required. However: running with `+RTS -K1K -xc` did not seem to show evidence of any overflows! So it's a mystery why this improves things. GHC should probably also be doubling the stack buffer at each overflow or doing something even smarter; the knobs we have aren't so helpful. * [skip ci] fix todo and schema generation for aggregate fields * 5087 libpq pool leak (#5089) Shrink libpq buffers to 1MB before returning connection to pool. Closes #5087 See: https://github.com/hasura/pg-client-hs/pull/19 Also related: #3388 #4077 * bump pg-client-hs version (fixes a build issue on some environments) (#5267) * do not use prepared statements for mutations * server: unlock scheduled events on graceful shutdown (#4928) * Fix buggy parsing of new --conn-lifetime flag in 2b0e3774 * [skip ci] remove cherry-picked commit from commit_diff.txt * server: include additional fields in scheduled trigger webhook payload (#5262) * include scheduled triggers metadata in the webhook body Co-authored-by: Tirumarai Selvan <tiru@hasura.io> * server: call the webhook asynchronously in event triggers (#5352) * server: call the webhook asynchronosly in event triggers * Expose all modules in Cabal file (#5371) * [skip ci] update commit_diff.txt * [skip ci] fix cast exp parser & few TODOs * [skip ci] fix remote fields arguments * [skip ci] fix few more TODO, no-op refactor, move resolve/action.hs to execute/action.hs * Pass environment variables around as a data structure, via @sordina (#5374) * Pass environment variables around as a data structure, via @sordina * Resolving build error * Adding Environment passing note to changelog * Removing references to ILTPollerLog as this seems to have been reintroduced from a bad merge * removing commented-out imports * Language pragmas already set by project * Linking async thread * Apply suggestions from code review Use `runQueryTx` instead of `runLazyTx` for queries. * remove the non-user facing entry in the changelog Co-authored-by: Phil Freeman <paf31@cantab.net> Co-authored-by: Phil Freeman <phil@hasura.io> Co-authored-by: Vamshi Surabhi <0x777@users.noreply.github.com> * [skip ci] fix: restrict remote relationship field generation for hasura queries * [skip ci] no-op refactor; move insert execution code from schema parser module * server: call the webhook asynchronously in event triggers (#5352) * server: call the webhook asynchronosly in event triggers * Expose all modules in Cabal file (#5371) * [skip ci] update commit_diff.txt * Pass environment variables around as a data structure, via @sordina (#5374) * Pass environment variables around as a data structure, via @sordina * Resolving build error * Adding Environment passing note to changelog * Removing references to ILTPollerLog as this seems to have been reintroduced from a bad merge * removing commented-out imports * Language pragmas already set by project * Linking async thread * Apply suggestions from code review Use `runQueryTx` instead of `runLazyTx` for queries. * remove the non-user facing entry in the changelog Co-authored-by: Phil Freeman <paf31@cantab.net> Co-authored-by: Phil Freeman <phil@hasura.io> Co-authored-by: Vamshi Surabhi <0x777@users.noreply.github.com> * [skip ci] implement header checking Probably closes #14 and #3659. * server: refactor 'pollQuery' to have a hook to process 'PollDetails' (#5391) Co-authored-by: Vamshi Surabhi <0x777@users.noreply.github.com> * update pg-client (#5421) * [skip ci] update commit_diff * Fix latency buckets for telemetry data These must have gotten messed up during a refactor. As a consequence almost all samples received so far fall into the single erroneous 0 to 1K seconds (originally supposed to be 1ms?) bucket. I also re-thought what the numbers should be, but these are still arbitrary and might want adjusting in the future. * [skip ci] include the latest commit compared against master in commit_diff * [skip ci] include new commits from master in commit_diff * [skip ci] improve description generation * [skip ci] sort all introspect arrays * [skip ci] allow parsers to specify error codes * [skip ci] fix integer and float parsing error code * [skip ci] scalar from json errors are now parse errors * [skip ci] fixed negative integer error message and code * [skip ci] Re-fix nullability in relationships * [skip ci] no-op refactor and removed couple of FIXMEs * [skip ci] uncomment code in 'deleteMetadataObject' * [skip ci] Fix re-fix of nullability for relationships * [skip ci] fix default arguments error code * [skip ci] updated test error message !!! WARNING !!! Since all fields accept `null`, they all are technically optional in the new schema. Meaning there's no such thing as a missing mandatory field anymore: a field that doesn't have a default value, and which therefore isn't labelled as "optional" in the schema, will be assumed to be null if it's missing, meaning it isn't possible anymore to have an error for a missing mandatory field. The only possible error is now when a optional positional argument is omitted but is not the last positional argument. * [skip ci] cleanup of int scalar parser * [skip ci] retro-compatibility of offset as string * [skip ci] Remove commit from commit_diff.txt Although strictly speaking we don't know if this will work correctly in PDV if we would implement query plan caching, the fact is that in the theoretical case that we would have the same issue in PDV, it would probably apply not just to introspection, and the fix would be written completely differently. So this old commit is of no value to us other than the heads-up "make sure query plan caching works correctly even in the presence of unused variables", which is already part of the test suite. * Add MonadTrace and MonadExecuteQuery abstractions (#5383) * [skip ci] Fix accumulation of input object types Just like object types, interface types, and union types, we have to avoid circularities when collecting input types from the GraphQL AST. Additionally, this fixes equality checks for input object types (whose fields are unordered, and hence should be compared as sets) and enum types (ditto). * [skip ci] fix fragment error path * [skip ci] fix node error code * [skip ci] fix paths in insert queries * [skip ci] fix path in objects * [skip ci] manually alter node id path for consistency * [skip ci] more node error fixups * [skip ci] one last relay error message fix * [skip ci] update commit_diff * Propagate the trace context to event triggers (#5409) * Propagate the trace context to event triggers * Handle missing trace and span IDs * Store trace context as one LOCAL * Add migrations * Documentation * changelog * Fix warnings * Respond to code review suggestions * Respond to code review * Undo changelog * Update CHANGELOG.md Co-authored-by: Vamshi Surabhi <0x777@users.noreply.github.com> * server: log request/response sizes for event triggers (#5463) * server: log request/response sizes for event triggers event triggers (and scheduled triggers) now have request/response size in their logs. * add changelog entry * Tracing: Simplify HTTP traced request (#5451) Remove the Inversion of Control (SuspendRequest) and simplify the tracing of HTTP Requests. Co-authored-by: Phil Freeman <phil@hasura.io> * Attach request ID as tracing metadata (#5456) * Propagate the trace context to event triggers * Handle missing trace and span IDs * Store trace context as one LOCAL * Add migrations * Documentation * Include the request ID as trace metadata * changelog * Fix warnings * Respond to code review suggestions * Respond to code review * Undo changelog * Update CHANGELOG.md * Typo Co-authored-by: Vamshi Surabhi <0x777@users.noreply.github.com> * server: add logging for action handlers (#5471) * server: add logging for action handlers * add changelog entry * change action-handler log type from internal to non-internal * fix action-handler-log name * server: pass http and websocket request to logging context (#5470) * pass request body to logging context in all cases * add message size logging on the websocket API this is required by graphql-engine-pro/#416 * message size logging on websocket API As we need to log all messages recieved/sent by the websocket server, it makes sense to log them as part of the websocket server event logs. Previously message recieved were logged inside the onMessage handler, and messages sent were logged only for "data" messages (as a server event log) * fix review comments Co-authored-by: Phil Freeman <phil@hasura.io> * server: stop eventing subsystem threads when shutting down (#5479) * server: stop eventing subsystem threads when shutting down * Apply suggestions from code review Co-authored-by: Karthikeyan Chinnakonda <chkarthikeyan95@gmail.com> Co-authored-by: Phil Freeman <phil@hasura.io> Co-authored-by: Phil Freeman <paf31@cantab.net> Co-authored-by: Karthikeyan Chinnakonda <chkarthikeyan95@gmail.com> * [skip ci] update commit_diff with new commits added in master * Bugfix to support 0-size HASURA_GRAPHQL_QUERY_PLAN_CACHE_SIZE Also some minor refactoring of bounded cache module: - the maxBound check in `trim` was confusing and unnecessary - consequently trim was unnecessary for lookupPure Also add some basic tests * Support only the bounded cache, with default HASURA_GRAPHQL_QUERY_PLAN_CACHE_SIZE of 4000. Closes #5363 * [skip ci] remove merge commit from commit_diff * server: Fix compiler warning caused by GHC upgrade (#5489) Co-authored-by: Vamshi Surabhi <0x777@users.noreply.github.com> * [skip ci] update all non server code from master * [skip ci] aligned object field error message with master * [skip ci] fix remaining undefined? * [skip ci] remove unused import * [skip ci] revert to previous error message, fix tests * Move nullableType/nonNullableType to Schema.hs These are functions on Types, not on Parsers. * [skip ci] fix setup to fix backend only test the order in which permission checks are performed on the branch is slightly different than on master, resulting in a slightly different error if there are no other mutations the user has access to. By adding update permissions, we go back to the expected case. * [skip ci] fix insert geojson tests to reflect new paths * [skip ci] fix enum test for better error message * [skip ci] fix header test for better error message * [skip ci] fix fragment cycle test for better error message * [skip ci] fix error message for type mismatch * [skip ci] fix variable path in test * [skip ci] adjust tests after bug fix * [skip ci] more tests fixing * Add hdb_catalog.current_setting abstraction for reading Hasura settings As the comment in the function’s definition explains, this is needed to work around an awkward Postgres behavior. * [skip ci] Update CONTRIBUTING.md to mention Node setup for Python tests * [skip ci] Add missing Python tests env var to CONTRIBUTING.md * [skip ci] fix order of result when subscription is run with multiple nodes * [skip ci] no-op refactor: fix a warning in Internal/Parser.hs * [skip ci] throw error when a subscription contains remote joins * [skip ci] Enable easier profiling by hiding AssertNF behind a flag In order to compile a profiling build, run: $ cabal new-build -f profiling --enable-profiling * [skip ci] Fix two warnings We used to lookup the objects that implement a given interface by filtering all objects in the schema document. However, one of the tests expects us to generate a warning if the provided `implements` field of an introspection query specifies an object not implementing some interface. So we use that field instead. * [skip ci] Fix warnings by commenting out query plan caching * [skip ci] improve masking/commenting query caching related code & few warning fixes * [skip ci] Fixed compiler warnings in graphql-parser-hs * Sync non-Haskell assets with master * [skip ci] add a test inserting invalid GraphQL but valid JSON value in a jsonb column * [skip ci] Avoid converting to/from Map * [skip ci] Apply some hlint suggestions * [skip ci] remove redundant constraints from buildLiveQueryPlan and explainGQLQuery * [skip ci] add NOTEs about missing Tracing constraints in PDV from master * Remove -fdefer-typed-holes, fix warnings * Update cabal.project.freeze * Limit GHC’s heap size to 8GB in CI to avoid the OOM killer * Commit package-lock.json for Python tests’ remote schema server * restrict env variables start with HASURA_GRAPHQL_ for headers configuration in actions, event triggers & remote schemas (#5519) * restrict env variables start with HASURA_GRAPHQL_ for headers definition in actions & event triggers * update CHANGELOG.md * Apply suggestions from code review Co-authored-by: Vamshi Surabhi <0x777@users.noreply.github.com> * add test for table_by_pk node when roles doesn't have permission to PK * [skip ci] fix introspection query if any enum column present in primary key (fix #5200) (#5522) * [skip ci] test case fix for a6450e126bc2d98bcfd3791501986e4627ce6c6f * [skip ci] add tests to agg queries when role doesn't have access to any cols * fix backend test * Simplify subscription execution * [skip ci] add test to check if required headers are present while querying * Suppose, table B is related to table A and to query B certain headers are necessary, then the test checks that we are throwing error when the header is not set when B is queried through A * fix mutations not checking for view mutability * [skip ci] add variable type checking and corresponding tests * [skip ci] add test to check if update headers are present while doing an upsert * [skip ci] add positive counterparts to some of the negative permission tests * fix args missing their description in introspect * [skip ci] Remove unused function; insert missing markNotReusable call * [skip ci] Add a Note about InputValue * [skip ci] Delete LegacySchema/ 🎉 * [skip ci] Delete GraphQL/{Resolve,Validate}/ 🎉 * [skip ci] Delete top-level Resolve/Validate modules; tidy .cabal file * [skip ci] Delete LegacySchema top-level module Somehow I missed this one. * fix input value to json * [skip ci] elaborate on JSON objects in GraphQL * [skip ci] add missing file * [skip ci] add a test with subscription containing remote joins * add a test with remote joins in mutation output * [skip ci] Add some comments to Schema/Mutation.hs * [skip ci] Remove no longer needed code from RemoteServer.hs * [skip ci] Use a helper function to generate conflict clause parsers * [skip ci] fix type checker error in fields with default value * capitalize the header keys in select_articles_without_required_headers * Somehow, this was the reason the tests were failing. I have no idea, why! * [skip ci] Add a long Note about optional fields and nullability * Improve comments a bit; simplify Schema/Common.hs a bit * [skip ci] full implementation of 5.8.5 type checking. * [skip ci] fix validation test teardown * [skip ci] fix schema stitching test * fix remote schema ignoring enum nullability * [skip ci] fix fieldOptional to not discard nullability * revert nullability of use_spheroid * fix comment * add required remote fields with arguments for tests * [skip ci] add missing docstrings * [skip ci] fixed description of remote fields * [skip ci] change docstring for consistency * fix several schema inconsistencies * revert behaviour change in function arguments parsing * fix remaining nullability issues in new schema * minor no-op refactor; use isListType from graphql-parser-hs * use nullability of remote schema node, while creating a Remote reln * fix 'ID' input coercing & action 'ID' type relationship mapping * include ASTs in MonadExecuteQuery * needed for PRO code-base * Delete code for "interfaces implementing ifaces" (draft GraphQL spec) Previously I started writing some code that adds support for a future GraphQL feature where interfaces may themselves be sub-types of other interfaces. However, this code was incomplete, and partially incorrect. So this commit deletes support for that entirely. * Ignore a remote schema test during the upgrade/downgrade test The PDV refactor does a better job at exposing a minimal set of types through introspection. In particular, not every type that is present in a remote schema is re-exposed by Hasura. The test test_schema_stitching.py::TestRemoteSchemaBasic::test_introspection assumed that all types were re-exposed, which is not required for GraphQL compatibility, in order to test some aspect of our support for remote schemas. So while this particular test has been updated on PDV, the PDV branch now does not pass the old test, which we argue to be incorrect. Hence this test is disabled while we await a release, after which we can re-enable it. This also re-enables a test that was previously disabled for similar, though unrelated, reasons. * add haddock documentation to the action's field parsers * Deslecting some tests in server-upgrade Some tests with current build are failing on server upgrade which it should not. The response is more accurate than what it was. Also the upgrade tests were not throwing errors when the test is expected to return an error, but succeeds. The test framework is patched to catch this case. * [skip ci] Add a long Note about interfaces and object types * send the response headers back to client after running a query * Deselect a few more tests during upgrade/downgrade test * Update commit_diff.txt * change log kind from db_migrate to catalog_migrate (#5531) * Show method and complete URI in traced HTTP calls (#5525) Co-authored-by: Vamshi Surabhi <0x777@users.noreply.github.com> * restrict env variables start with HASURA_GRAPHQL_ for headers configuration in actions, event triggers & remote schemas (#5519) * restrict env variables start with HASURA_GRAPHQL_ for headers definition in actions & event triggers * update CHANGELOG.md * Apply suggestions from code review Co-authored-by: Vamshi Surabhi <0x777@users.noreply.github.com> * fix introspection query if any enum column present in primary key (fix #5200) (#5522) * Fix telemetry reporting of transport (websocket was reported as http) * add log kinds in cli-migrations image (#5529) * add log kinds in cli-migrations image * give hint to resolve timeout error * minor changes and CHANGELOG * server: set hasura.tracecontext in RQL mutations [#5542] (#5555) * server: set hasura.tracecontext in RQL mutations [#5542] * Update test suite Co-authored-by: Tirumarai Selvan <tiru@hasura.io> * Add bulldozer auto-merge and -update configuration We still need to add the github app (as of time of opening this PR) Afterwards devs should be able to allow bulldozer to automatically "update" the branch, merging in parent when it changes, as well as automatically merge when all checks pass. This is opt-in by adding the `auto-update-auto-merge` label to the PR. * Remove 'bulldozer' config, try 'kodiak' for auto-merge see: https://github.com/chdsbd/kodiak The main issue that bit us was not being able to auto update forked branches, also: https://github.com/palantir/bulldozer/issues/66 https://github.com/palantir/bulldozer/issues/145 * Cherry-picked all commits * [skip ci] Slightly improve formatting * Revert "fix introspection query if any enum column present in primary key (fix #5200) (#5522)" This reverts commit 0f9a5afa59a88f6824f4d63d58db246a5ba3fb03. This undoes a cherry-pick of 34288e1eb5f2c5dad9e6d1e05453dd52397dc970 that was already done previously in a6450e126bc2d98bcfd3791501986e4627ce6c6f, and subsequently fixed for PDV in 70e89dc250f8ddc6e2b7930bbe2b3eeaa6dbe1db * Do a small bit of tidying in Hasura.GraphQL.Parser.Collect * Fix cherry-picking work Some previous cherry-picks ended up modifying code that is commented out * [skip ci] clarified comment regarding insert representation * [skip ci] removed obsolete todos * cosmetic change * fix action error message * [skip ci] remove obsolete comment * [skip ci] synchronize stylish haskell extensions list * use previously defined scalar names in parsers rather than ad-hoc literals * Apply most syntax hlint hints. * Clarify comment on update mutation. * [skip ci] Clarify what fields should be specified for objects * Update "_inc" description. * Use record types rather than tuples fo IntrospectionResult and ParsedIntrospection * Get rid of checkFieldNamesUnique (use Data.List.Extended.duplicates) * Throw more errors when collecting query root names * [skip ci] clean column parser comment * Remove dead code inserted in ab65b39 * avoid converting to non-empty list where not needed * add note and TODO about the disabled checks in PDV * minor refactor in remoteField' function * Unify two getObject methods * Nitpicks in Remote.hs * Update CHANGELOG.md * Revert "Unify two getObject methods" This reverts commit bd6bb40355b3d189a46c0312eb52225e18be57b3. We do need two different getObject functions as the corresponding error message is different * Fix error message in Remote.hs * Update CHANGELOG.md Co-authored-by: Auke Booij <auke@tulcod.com> * Apply suggested Changelog fix. Co-authored-by: Auke Booij <auke@tulcod.com> * Fix typo in Changelog. * [skip ci] Update changelog. * reuse type names to avoid duplication * Fix Hashable instance for Definition The presence of `Maybe Unique`, and an optional description, as part of `Definition`s, means that `Definition`s that are considered `Eq`ual may get different hashes. This can happen, for instance, when one object is memoized but another is not. * [skip ci] Update commit_diff.txt * Bump parser version. * Bump freeze file after changes in parser. * [skip ci] Incorporate commits from master * Fix developer flag in server/cabal.project.freeze Co-authored-by: Auke Booij <auke@tulcod.com> * Deselect a changed ENUM test for upgrade/downgrade CI * Deselect test here as well * [skip ci] remove dead code * Disable more tests for upgrade/downgrade * Fix which test gets deselected * Revert "Add hdb_catalog.current_setting abstraction for reading Hasura settings" This reverts commit 66e85ab9fbd56cca2c28a80201f6604fbe811b85. * Remove circular reference in cabal.project.freeze Co-authored-by: Karthikeyan Chinnakonda <karthikeyan@hasura.io> Co-authored-by: Auke Booij <auke@hasura.io> Co-authored-by: Tirumarai Selvan <tiru@hasura.io> Co-authored-by: Marion Schleifer <marion@hasura.io> Co-authored-by: Aleksandra Sikora <ola.zxcvbnm@gmail.com> Co-authored-by: Brandon Simmons <brandon.m.simmons@gmail.com> Co-authored-by: Vamshi Surabhi <0x777@users.noreply.github.com> Co-authored-by: Anon Ray <rayanon004@gmail.com> Co-authored-by: rakeshkky <12475069+rakeshkky@users.noreply.github.com> Co-authored-by: Anon Ray <ecthiender@users.noreply.github.com> Co-authored-by: Vamshi Surabhi <vamshi@hasura.io> Co-authored-by: Antoine Leblanc <antoine@hasura.io> Co-authored-by: Brandon Simmons <brandon@hasura.io> Co-authored-by: Phil Freeman <phil@hasura.io> Co-authored-by: Lyndon Maydwell <lyndon@sordina.net> Co-authored-by: Phil Freeman <paf31@cantab.net> Co-authored-by: Naveen Naidu <naveennaidu479@gmail.com> Co-authored-by: Karthikeyan Chinnakonda <chkarthikeyan95@gmail.com> Co-authored-by: Nizar Malangadan <nizar-m@users.noreply.github.com> Co-authored-by: Antoine Leblanc <crucuny@gmail.com> Co-authored-by: Auke Booij <auke@tulcod.com>
2020-08-21 20:27:01 +03:00
-- TODO (from master):- drop this in next major update
authHookTyEnv mType =
fromMaybe AHTGet
<$> withEnv mType "HASURA_GRAPHQL_AUTH_HOOK_TYPE"
mkCorsConfig mCfg = do
corsDisabled <- withEnvBool False (fst corsDisableEnv)
corsCfg <-
if corsDisabled
then return (CCDisabled True)
else fromMaybe CCAllowAll <$> withEnv mCfg (fst corsDomainEnv)
readCookVal <- withEnvBool (rsoWsReadCookie rso) (fst wsReadCookieEnv)
wsReadCookie <- case (isCorsDisabled corsCfg, readCookVal) of
(True, _) -> return readCookVal
(False, True) ->
throwError $
fst wsReadCookieEnv
<> " can only be used when CORS is disabled"
(False, False) -> return False
return $ case corsCfg of
CCDisabled _ -> CCDisabled wsReadCookie
_ -> corsCfg
2019-04-17 12:48:41 +03:00
mkLQOpts = do
mxRefetchIntM <- withEnv (rsoMxRefetchInt rso) $ fst mxRefetchDelayEnv
mxBatchSizeM <- withEnv (rsoMxBatchSize rso) $ fst mxBatchSizeEnv
return $ LQ.mkLiveQueriesOptions mxBatchSizeM mxRefetchIntM
2019-04-17 12:48:41 +03:00
mkExamplesDoc :: [[String]] -> PP.Doc
mkExamplesDoc exampleLines =
PP.text "Examples: " PP.<$> PP.indent 2 (PP.vsep examples)
where
examples = map PP.text $ intercalate [""] exampleLines
mkEnvVarDoc :: [(String, String)] -> PP.Doc
mkEnvVarDoc envVars =
PP.text "Environment variables: "
PP.<$> PP.indent 2 (PP.vsep $ map mkEnvVarLine envVars)
where
mkEnvVarLine (var, desc) =
2019-01-28 16:55:28 +03:00
(PP.fillBreak 40 (PP.text var) PP.<+> prettifyDesc desc) <> PP.hardline
prettifyDesc = PP.align . PP.fillSep . map PP.text . words
mainCmdFooter :: PP.Doc
mainCmdFooter =
examplesDoc PP.<$> PP.text "" PP.<$> envVarDoc
where
examplesDoc = mkExamplesDoc examples
examples =
[ [ "# Serve GraphQL Engine on default port (8080) with console disabled",
"graphql-engine --database-url <database-url> serve"
],
[ "# For more options, checkout",
"graphql-engine serve --help"
]
]
envVarDoc = mkEnvVarDoc [databaseUrlEnv, retriesNumEnv]
databaseUrlEnv :: (String, String)
databaseUrlEnv =
( "HASURA_GRAPHQL_DATABASE_URL",
"Postgres database URL. Example postgres://foo:bar@example.com:2345/database"
)
metadataDbUrlEnv :: (String, String)
metadataDbUrlEnv =
( "HASURA_GRAPHQL_METADATA_DATABASE_URL",
"Postgres database URL for Metadata storage. Example postgres://foo:bar@example.com:2345/database"
)
serveCmdFooter :: PP.Doc
serveCmdFooter =
examplesDoc PP.<$> PP.text "" PP.<$> envVarDoc
where
examplesDoc = mkExamplesDoc examples
examples =
[ [ "# Start GraphQL Engine on default port (8080) with console enabled",
"graphql-engine --database-url <database-url> serve --enable-console"
],
[ "# Start GraphQL Engine on default port (8080) with console disabled",
"graphql-engine --database-url <database-url> serve"
],
[ "# Start GraphQL Engine on a different port (say 9090) with console disabled",
"graphql-engine --database-url <database-url> serve --server-port 9090"
],
[ "# Start GraphQL Engine with admin secret key",
"graphql-engine --database-url <database-url> serve --admin-secret <adminsecretkey>"
],
[ "# Start GraphQL Engine with restrictive CORS policy (only allow https://example.com:8080)",
"graphql-engine --database-url <database-url> serve --cors-domain https://example.com:8080"
],
[ "# Start GraphQL Engine with multiple domains for CORS (https://example.com, http://localhost:3000 and https://*.foo.bar.com)",
"graphql-engine --database-url <database-url> serve --cors-domain \"https://example.com, https://*.foo.bar.com, http://localhost:3000\""
],
[ "# Start GraphQL Engine with Authentication Webhook (GET)",
"graphql-engine --database-url <database-url> serve --admin-secret <adminsecretkey>"
<> " --auth-hook https://mywebhook.com/get"
],
[ "# Start GraphQL Engine with Authentication Webhook (POST)",
"graphql-engine --database-url <database-url> serve --admin-secret <adminsecretkey>"
<> " --auth-hook https://mywebhook.com/post --auth-hook-mode POST"
],
[ "# Start GraphQL Engine with telemetry enabled/disabled",
"graphql-engine --database-url <database-url> serve --enable-telemetry true|false"
],
[ "# Start GraphQL Engine with HTTP compression enabled for '/v1/query' and '/v1/graphql' endpoints",
"graphql-engine --database-url <database-url> serve --enable-compression"
],
[ "# Start GraphQL Engine with enable/disable including 'internal' information in an error response for the request made by an 'admin'",
"graphql-engine --database-url <database-url> serve --admin-internal-errors true|false"
]
]
envVarDoc = mkEnvVarDoc $ envVars <> eventEnvs
envVars =
[ accessKeyEnv,
adminInternalErrorsEnv,
adminSecretEnv,
asyncActionsFetchIntervalEnv,
authHookEnv,
authHookModeEnv,
corsDisableEnv,
corsDomainEnv,
dangerousBooleanCollapseEnv,
databaseUrlEnv,
devModeEnv,
enableAllowlistEnv,
enableConsoleEnv,
enableTelemetryEnv,
enabledAPIsEnv,
enabledLogsEnv,
jwtSecretEnv,
logLevelEnv,
pgConnsEnv,
pgStripesEnv,
pgTimeoutEnv,
pgUsePrepareEnv,
retriesNumEnv,
serveHostEnv,
servePortEnv,
stringifyNumEnv,
txIsoEnv,
unAuthRoleEnv,
webSocketKeepAliveEnv,
wsReadCookieEnv
]
eventEnvs = [eventsHttpPoolSizeEnv, eventsFetchIntervalEnv]
eventsHttpPoolSizeEnv :: (String, String)
Rewrite GraphQL schema generation and query parsing (close #2801) (#4111) Aka “the PDV refactor.” History is preserved on the branch 2801-graphql-schema-parser-refactor. * [skip ci] remove stale benchmark commit from commit_diff * [skip ci] Check for root field name conflicts between remotes * [skip ci] Additionally check for conflicts between remotes and DB * [skip ci] Check for conflicts in schema when tracking a table * [skip ci] Fix equality checking in GraphQL AST * server: fix mishandling of GeoJSON inputs in subscriptions (fix #3239) (#4551) * Add support for multiple top-level fields in a subscription to improve testability of subscriptions * Add an internal flag to enable multiple subscriptions * Add missing call to withConstructorFn in live queries (fix #3239) Co-authored-by: Alexis King <lexi.lambda@gmail.com> * Scheduled triggers (close #1914) (#3553) server: add scheduled triggers Co-authored-by: Alexis King <lexi.lambda@gmail.com> Co-authored-by: Marion Schleifer <marion@hasura.io> Co-authored-by: Karthikeyan Chinnakonda <karthikeyan@hasura.io> Co-authored-by: Aleksandra Sikora <ola.zxcvbnm@gmail.com> * dev.sh: bump version due to addition of croniter python dependency * server: fix an introspection query caching issue (fix #4547) (#4661) Introspection queries accept variables, but we need to make sure to also touch the variables that we ignore, so that an introspection query is marked not reusable if we are not able to build a correct query plan for it. A better solution here would be to deal with such unused variables correctly, so that more introspection queries become reusable. An even better solution would be to type-safely track *how* to reuse which variables, rather than to split the reusage marking from the planning. Co-authored-by: Tirumarai Selvan <tiru@hasura.io> * flush log buffer on exception in mkWaiApp ( fix #4772 ) (#4801) * flush log buffer on exception in mkWaiApp * add comment to explain the introduced change * add changelog * allow logging details of a live query polling thread (#4959) * changes for poller-log add various multiplexed query info in poller-log * minor cleanup, also fixes a bug which will return duplicate data * Live query poller stats can now be logged This also removes in-memory stats that are collected about batched query execution as the log lines when piped into an monitoring tool will give us better insights. * allow poller-log to be configurable * log minimal information in the livequery-poller-log Other information can be retrieved from /dev/subscriptions/extended * fix few review comments * avoid marshalling and unmarshalling from ByteString to EncJSON * separate out SubscriberId and SubscriberMetadata Co-authored-by: Anon Ray <rayanon004@gmail.com> * Don't compile in developer APIs by default * Tighten up handling of admin secret, more docs Store the admin secret only as a hash to prevent leaking the secret inadvertently, and to prevent timing attacks on the secret. NOTE: best practice for stored user passwords is a function with a tunable cost like bcrypt, but our threat model is quite different (even if we thought we could reasonably protect the secret from an attacker who could read arbitrary regions of memory), and bcrypt is far too slow (by design) to perform on each request. We'd have to rely on our (technically savvy) users to choose high entropy passwords in any case. Referencing #4736 * server/docs: add instructions to fix loss of float precision in PostgreSQL <= 11 (#5187) This adds a server flag, --pg-connection-options, that can be used to set a PostgreSQL connection parameter, extra_float_digits, that needs to be used to avoid loss of data on older versions of PostgreSQL, which have odd default behavior when returning float values. (fixes #5092) * [skip ci] Add new commits from master to the commit diff * [skip ci] serve default directives (skip & include) over introspection * [skip ci] Update non-Haskell assets with the version on master * server: refactor GQL execution check and config API (#5094) Co-authored-by: Vamshi Surabhi <vamshi@hasura.io> Co-authored-by: Vamshi Surabhi <0x777@users.noreply.github.com> * [skip ci] fix js issues in tests by pinning dependencies version * [skip ci] bump graphql version * [skip ci] Add note about memory usage * generalize query execution logic on Postgres (#5110) * generalize PGExecCtx to support specialized functions for various operations * fix tests compilation * allow customising PGExecCtx when starting the web server * server: changes catalog initialization and logging for pro customization (#5139) * new typeclass to abstract the logic of QueryLog-ing * abstract the logic of logging websocket-server logs introduce a MonadWSLog typeclass * move catalog initialization to init step expose a helper function to migrate catalog create schema cache in initialiseCtx * expose various modules and functions for pro * [skip ci] cosmetic change * [skip ci] fix test calling a mutation that does not exist * [skip ci] minor text change * [skip ci] refactored input values * [skip ci] remove VString Origin * server: fix updating of headers behaviour in the update cron trigger API and create future events immediately (#5151) * server: fix bug to update headers in an existing cron trigger and create future events Co-authored-by: Tirumarai Selvan <tiru@hasura.io> * Lower stack chunk size in RTS to reduce thread STACK memory (closes #5190) This reduces memory consumption for new idle subscriptions significantly (see linked ticket). The hypothesis is: we fork a lot of threads per websocket, and some of these use slightly more than the initial 1K stack size, so the first overflow balloons to 32K, when significantly less is required. However: running with `+RTS -K1K -xc` did not seem to show evidence of any overflows! So it's a mystery why this improves things. GHC should probably also be doubling the stack buffer at each overflow or doing something even smarter; the knobs we have aren't so helpful. * [skip ci] fix todo and schema generation for aggregate fields * 5087 libpq pool leak (#5089) Shrink libpq buffers to 1MB before returning connection to pool. Closes #5087 See: https://github.com/hasura/pg-client-hs/pull/19 Also related: #3388 #4077 * bump pg-client-hs version (fixes a build issue on some environments) (#5267) * do not use prepared statements for mutations * server: unlock scheduled events on graceful shutdown (#4928) * Fix buggy parsing of new --conn-lifetime flag in 2b0e3774 * [skip ci] remove cherry-picked commit from commit_diff.txt * server: include additional fields in scheduled trigger webhook payload (#5262) * include scheduled triggers metadata in the webhook body Co-authored-by: Tirumarai Selvan <tiru@hasura.io> * server: call the webhook asynchronously in event triggers (#5352) * server: call the webhook asynchronosly in event triggers * Expose all modules in Cabal file (#5371) * [skip ci] update commit_diff.txt * [skip ci] fix cast exp parser & few TODOs * [skip ci] fix remote fields arguments * [skip ci] fix few more TODO, no-op refactor, move resolve/action.hs to execute/action.hs * Pass environment variables around as a data structure, via @sordina (#5374) * Pass environment variables around as a data structure, via @sordina * Resolving build error * Adding Environment passing note to changelog * Removing references to ILTPollerLog as this seems to have been reintroduced from a bad merge * removing commented-out imports * Language pragmas already set by project * Linking async thread * Apply suggestions from code review Use `runQueryTx` instead of `runLazyTx` for queries. * remove the non-user facing entry in the changelog Co-authored-by: Phil Freeman <paf31@cantab.net> Co-authored-by: Phil Freeman <phil@hasura.io> Co-authored-by: Vamshi Surabhi <0x777@users.noreply.github.com> * [skip ci] fix: restrict remote relationship field generation for hasura queries * [skip ci] no-op refactor; move insert execution code from schema parser module * server: call the webhook asynchronously in event triggers (#5352) * server: call the webhook asynchronosly in event triggers * Expose all modules in Cabal file (#5371) * [skip ci] update commit_diff.txt * Pass environment variables around as a data structure, via @sordina (#5374) * Pass environment variables around as a data structure, via @sordina * Resolving build error * Adding Environment passing note to changelog * Removing references to ILTPollerLog as this seems to have been reintroduced from a bad merge * removing commented-out imports * Language pragmas already set by project * Linking async thread * Apply suggestions from code review Use `runQueryTx` instead of `runLazyTx` for queries. * remove the non-user facing entry in the changelog Co-authored-by: Phil Freeman <paf31@cantab.net> Co-authored-by: Phil Freeman <phil@hasura.io> Co-authored-by: Vamshi Surabhi <0x777@users.noreply.github.com> * [skip ci] implement header checking Probably closes #14 and #3659. * server: refactor 'pollQuery' to have a hook to process 'PollDetails' (#5391) Co-authored-by: Vamshi Surabhi <0x777@users.noreply.github.com> * update pg-client (#5421) * [skip ci] update commit_diff * Fix latency buckets for telemetry data These must have gotten messed up during a refactor. As a consequence almost all samples received so far fall into the single erroneous 0 to 1K seconds (originally supposed to be 1ms?) bucket. I also re-thought what the numbers should be, but these are still arbitrary and might want adjusting in the future. * [skip ci] include the latest commit compared against master in commit_diff * [skip ci] include new commits from master in commit_diff * [skip ci] improve description generation * [skip ci] sort all introspect arrays * [skip ci] allow parsers to specify error codes * [skip ci] fix integer and float parsing error code * [skip ci] scalar from json errors are now parse errors * [skip ci] fixed negative integer error message and code * [skip ci] Re-fix nullability in relationships * [skip ci] no-op refactor and removed couple of FIXMEs * [skip ci] uncomment code in 'deleteMetadataObject' * [skip ci] Fix re-fix of nullability for relationships * [skip ci] fix default arguments error code * [skip ci] updated test error message !!! WARNING !!! Since all fields accept `null`, they all are technically optional in the new schema. Meaning there's no such thing as a missing mandatory field anymore: a field that doesn't have a default value, and which therefore isn't labelled as "optional" in the schema, will be assumed to be null if it's missing, meaning it isn't possible anymore to have an error for a missing mandatory field. The only possible error is now when a optional positional argument is omitted but is not the last positional argument. * [skip ci] cleanup of int scalar parser * [skip ci] retro-compatibility of offset as string * [skip ci] Remove commit from commit_diff.txt Although strictly speaking we don't know if this will work correctly in PDV if we would implement query plan caching, the fact is that in the theoretical case that we would have the same issue in PDV, it would probably apply not just to introspection, and the fix would be written completely differently. So this old commit is of no value to us other than the heads-up "make sure query plan caching works correctly even in the presence of unused variables", which is already part of the test suite. * Add MonadTrace and MonadExecuteQuery abstractions (#5383) * [skip ci] Fix accumulation of input object types Just like object types, interface types, and union types, we have to avoid circularities when collecting input types from the GraphQL AST. Additionally, this fixes equality checks for input object types (whose fields are unordered, and hence should be compared as sets) and enum types (ditto). * [skip ci] fix fragment error path * [skip ci] fix node error code * [skip ci] fix paths in insert queries * [skip ci] fix path in objects * [skip ci] manually alter node id path for consistency * [skip ci] more node error fixups * [skip ci] one last relay error message fix * [skip ci] update commit_diff * Propagate the trace context to event triggers (#5409) * Propagate the trace context to event triggers * Handle missing trace and span IDs * Store trace context as one LOCAL * Add migrations * Documentation * changelog * Fix warnings * Respond to code review suggestions * Respond to code review * Undo changelog * Update CHANGELOG.md Co-authored-by: Vamshi Surabhi <0x777@users.noreply.github.com> * server: log request/response sizes for event triggers (#5463) * server: log request/response sizes for event triggers event triggers (and scheduled triggers) now have request/response size in their logs. * add changelog entry * Tracing: Simplify HTTP traced request (#5451) Remove the Inversion of Control (SuspendRequest) and simplify the tracing of HTTP Requests. Co-authored-by: Phil Freeman <phil@hasura.io> * Attach request ID as tracing metadata (#5456) * Propagate the trace context to event triggers * Handle missing trace and span IDs * Store trace context as one LOCAL * Add migrations * Documentation * Include the request ID as trace metadata * changelog * Fix warnings * Respond to code review suggestions * Respond to code review * Undo changelog * Update CHANGELOG.md * Typo Co-authored-by: Vamshi Surabhi <0x777@users.noreply.github.com> * server: add logging for action handlers (#5471) * server: add logging for action handlers * add changelog entry * change action-handler log type from internal to non-internal * fix action-handler-log name * server: pass http and websocket request to logging context (#5470) * pass request body to logging context in all cases * add message size logging on the websocket API this is required by graphql-engine-pro/#416 * message size logging on websocket API As we need to log all messages recieved/sent by the websocket server, it makes sense to log them as part of the websocket server event logs. Previously message recieved were logged inside the onMessage handler, and messages sent were logged only for "data" messages (as a server event log) * fix review comments Co-authored-by: Phil Freeman <phil@hasura.io> * server: stop eventing subsystem threads when shutting down (#5479) * server: stop eventing subsystem threads when shutting down * Apply suggestions from code review Co-authored-by: Karthikeyan Chinnakonda <chkarthikeyan95@gmail.com> Co-authored-by: Phil Freeman <phil@hasura.io> Co-authored-by: Phil Freeman <paf31@cantab.net> Co-authored-by: Karthikeyan Chinnakonda <chkarthikeyan95@gmail.com> * [skip ci] update commit_diff with new commits added in master * Bugfix to support 0-size HASURA_GRAPHQL_QUERY_PLAN_CACHE_SIZE Also some minor refactoring of bounded cache module: - the maxBound check in `trim` was confusing and unnecessary - consequently trim was unnecessary for lookupPure Also add some basic tests * Support only the bounded cache, with default HASURA_GRAPHQL_QUERY_PLAN_CACHE_SIZE of 4000. Closes #5363 * [skip ci] remove merge commit from commit_diff * server: Fix compiler warning caused by GHC upgrade (#5489) Co-authored-by: Vamshi Surabhi <0x777@users.noreply.github.com> * [skip ci] update all non server code from master * [skip ci] aligned object field error message with master * [skip ci] fix remaining undefined? * [skip ci] remove unused import * [skip ci] revert to previous error message, fix tests * Move nullableType/nonNullableType to Schema.hs These are functions on Types, not on Parsers. * [skip ci] fix setup to fix backend only test the order in which permission checks are performed on the branch is slightly different than on master, resulting in a slightly different error if there are no other mutations the user has access to. By adding update permissions, we go back to the expected case. * [skip ci] fix insert geojson tests to reflect new paths * [skip ci] fix enum test for better error message * [skip ci] fix header test for better error message * [skip ci] fix fragment cycle test for better error message * [skip ci] fix error message for type mismatch * [skip ci] fix variable path in test * [skip ci] adjust tests after bug fix * [skip ci] more tests fixing * Add hdb_catalog.current_setting abstraction for reading Hasura settings As the comment in the function’s definition explains, this is needed to work around an awkward Postgres behavior. * [skip ci] Update CONTRIBUTING.md to mention Node setup for Python tests * [skip ci] Add missing Python tests env var to CONTRIBUTING.md * [skip ci] fix order of result when subscription is run with multiple nodes * [skip ci] no-op refactor: fix a warning in Internal/Parser.hs * [skip ci] throw error when a subscription contains remote joins * [skip ci] Enable easier profiling by hiding AssertNF behind a flag In order to compile a profiling build, run: $ cabal new-build -f profiling --enable-profiling * [skip ci] Fix two warnings We used to lookup the objects that implement a given interface by filtering all objects in the schema document. However, one of the tests expects us to generate a warning if the provided `implements` field of an introspection query specifies an object not implementing some interface. So we use that field instead. * [skip ci] Fix warnings by commenting out query plan caching * [skip ci] improve masking/commenting query caching related code & few warning fixes * [skip ci] Fixed compiler warnings in graphql-parser-hs * Sync non-Haskell assets with master * [skip ci] add a test inserting invalid GraphQL but valid JSON value in a jsonb column * [skip ci] Avoid converting to/from Map * [skip ci] Apply some hlint suggestions * [skip ci] remove redundant constraints from buildLiveQueryPlan and explainGQLQuery * [skip ci] add NOTEs about missing Tracing constraints in PDV from master * Remove -fdefer-typed-holes, fix warnings * Update cabal.project.freeze * Limit GHC’s heap size to 8GB in CI to avoid the OOM killer * Commit package-lock.json for Python tests’ remote schema server * restrict env variables start with HASURA_GRAPHQL_ for headers configuration in actions, event triggers & remote schemas (#5519) * restrict env variables start with HASURA_GRAPHQL_ for headers definition in actions & event triggers * update CHANGELOG.md * Apply suggestions from code review Co-authored-by: Vamshi Surabhi <0x777@users.noreply.github.com> * add test for table_by_pk node when roles doesn't have permission to PK * [skip ci] fix introspection query if any enum column present in primary key (fix #5200) (#5522) * [skip ci] test case fix for a6450e126bc2d98bcfd3791501986e4627ce6c6f * [skip ci] add tests to agg queries when role doesn't have access to any cols * fix backend test * Simplify subscription execution * [skip ci] add test to check if required headers are present while querying * Suppose, table B is related to table A and to query B certain headers are necessary, then the test checks that we are throwing error when the header is not set when B is queried through A * fix mutations not checking for view mutability * [skip ci] add variable type checking and corresponding tests * [skip ci] add test to check if update headers are present while doing an upsert * [skip ci] add positive counterparts to some of the negative permission tests * fix args missing their description in introspect * [skip ci] Remove unused function; insert missing markNotReusable call * [skip ci] Add a Note about InputValue * [skip ci] Delete LegacySchema/ 🎉 * [skip ci] Delete GraphQL/{Resolve,Validate}/ 🎉 * [skip ci] Delete top-level Resolve/Validate modules; tidy .cabal file * [skip ci] Delete LegacySchema top-level module Somehow I missed this one. * fix input value to json * [skip ci] elaborate on JSON objects in GraphQL * [skip ci] add missing file * [skip ci] add a test with subscription containing remote joins * add a test with remote joins in mutation output * [skip ci] Add some comments to Schema/Mutation.hs * [skip ci] Remove no longer needed code from RemoteServer.hs * [skip ci] Use a helper function to generate conflict clause parsers * [skip ci] fix type checker error in fields with default value * capitalize the header keys in select_articles_without_required_headers * Somehow, this was the reason the tests were failing. I have no idea, why! * [skip ci] Add a long Note about optional fields and nullability * Improve comments a bit; simplify Schema/Common.hs a bit * [skip ci] full implementation of 5.8.5 type checking. * [skip ci] fix validation test teardown * [skip ci] fix schema stitching test * fix remote schema ignoring enum nullability * [skip ci] fix fieldOptional to not discard nullability * revert nullability of use_spheroid * fix comment * add required remote fields with arguments for tests * [skip ci] add missing docstrings * [skip ci] fixed description of remote fields * [skip ci] change docstring for consistency * fix several schema inconsistencies * revert behaviour change in function arguments parsing * fix remaining nullability issues in new schema * minor no-op refactor; use isListType from graphql-parser-hs * use nullability of remote schema node, while creating a Remote reln * fix 'ID' input coercing & action 'ID' type relationship mapping * include ASTs in MonadExecuteQuery * needed for PRO code-base * Delete code for "interfaces implementing ifaces" (draft GraphQL spec) Previously I started writing some code that adds support for a future GraphQL feature where interfaces may themselves be sub-types of other interfaces. However, this code was incomplete, and partially incorrect. So this commit deletes support for that entirely. * Ignore a remote schema test during the upgrade/downgrade test The PDV refactor does a better job at exposing a minimal set of types through introspection. In particular, not every type that is present in a remote schema is re-exposed by Hasura. The test test_schema_stitching.py::TestRemoteSchemaBasic::test_introspection assumed that all types were re-exposed, which is not required for GraphQL compatibility, in order to test some aspect of our support for remote schemas. So while this particular test has been updated on PDV, the PDV branch now does not pass the old test, which we argue to be incorrect. Hence this test is disabled while we await a release, after which we can re-enable it. This also re-enables a test that was previously disabled for similar, though unrelated, reasons. * add haddock documentation to the action's field parsers * Deslecting some tests in server-upgrade Some tests with current build are failing on server upgrade which it should not. The response is more accurate than what it was. Also the upgrade tests were not throwing errors when the test is expected to return an error, but succeeds. The test framework is patched to catch this case. * [skip ci] Add a long Note about interfaces and object types * send the response headers back to client after running a query * Deselect a few more tests during upgrade/downgrade test * Update commit_diff.txt * change log kind from db_migrate to catalog_migrate (#5531) * Show method and complete URI in traced HTTP calls (#5525) Co-authored-by: Vamshi Surabhi <0x777@users.noreply.github.com> * restrict env variables start with HASURA_GRAPHQL_ for headers configuration in actions, event triggers & remote schemas (#5519) * restrict env variables start with HASURA_GRAPHQL_ for headers definition in actions & event triggers * update CHANGELOG.md * Apply suggestions from code review Co-authored-by: Vamshi Surabhi <0x777@users.noreply.github.com> * fix introspection query if any enum column present in primary key (fix #5200) (#5522) * Fix telemetry reporting of transport (websocket was reported as http) * add log kinds in cli-migrations image (#5529) * add log kinds in cli-migrations image * give hint to resolve timeout error * minor changes and CHANGELOG * server: set hasura.tracecontext in RQL mutations [#5542] (#5555) * server: set hasura.tracecontext in RQL mutations [#5542] * Update test suite Co-authored-by: Tirumarai Selvan <tiru@hasura.io> * Add bulldozer auto-merge and -update configuration We still need to add the github app (as of time of opening this PR) Afterwards devs should be able to allow bulldozer to automatically "update" the branch, merging in parent when it changes, as well as automatically merge when all checks pass. This is opt-in by adding the `auto-update-auto-merge` label to the PR. * Remove 'bulldozer' config, try 'kodiak' for auto-merge see: https://github.com/chdsbd/kodiak The main issue that bit us was not being able to auto update forked branches, also: https://github.com/palantir/bulldozer/issues/66 https://github.com/palantir/bulldozer/issues/145 * Cherry-picked all commits * [skip ci] Slightly improve formatting * Revert "fix introspection query if any enum column present in primary key (fix #5200) (#5522)" This reverts commit 0f9a5afa59a88f6824f4d63d58db246a5ba3fb03. This undoes a cherry-pick of 34288e1eb5f2c5dad9e6d1e05453dd52397dc970 that was already done previously in a6450e126bc2d98bcfd3791501986e4627ce6c6f, and subsequently fixed for PDV in 70e89dc250f8ddc6e2b7930bbe2b3eeaa6dbe1db * Do a small bit of tidying in Hasura.GraphQL.Parser.Collect * Fix cherry-picking work Some previous cherry-picks ended up modifying code that is commented out * [skip ci] clarified comment regarding insert representation * [skip ci] removed obsolete todos * cosmetic change * fix action error message * [skip ci] remove obsolete comment * [skip ci] synchronize stylish haskell extensions list * use previously defined scalar names in parsers rather than ad-hoc literals * Apply most syntax hlint hints. * Clarify comment on update mutation. * [skip ci] Clarify what fields should be specified for objects * Update "_inc" description. * Use record types rather than tuples fo IntrospectionResult and ParsedIntrospection * Get rid of checkFieldNamesUnique (use Data.List.Extended.duplicates) * Throw more errors when collecting query root names * [skip ci] clean column parser comment * Remove dead code inserted in ab65b39 * avoid converting to non-empty list where not needed * add note and TODO about the disabled checks in PDV * minor refactor in remoteField' function * Unify two getObject methods * Nitpicks in Remote.hs * Update CHANGELOG.md * Revert "Unify two getObject methods" This reverts commit bd6bb40355b3d189a46c0312eb52225e18be57b3. We do need two different getObject functions as the corresponding error message is different * Fix error message in Remote.hs * Update CHANGELOG.md Co-authored-by: Auke Booij <auke@tulcod.com> * Apply suggested Changelog fix. Co-authored-by: Auke Booij <auke@tulcod.com> * Fix typo in Changelog. * [skip ci] Update changelog. * reuse type names to avoid duplication * Fix Hashable instance for Definition The presence of `Maybe Unique`, and an optional description, as part of `Definition`s, means that `Definition`s that are considered `Eq`ual may get different hashes. This can happen, for instance, when one object is memoized but another is not. * [skip ci] Update commit_diff.txt * Bump parser version. * Bump freeze file after changes in parser. * [skip ci] Incorporate commits from master * Fix developer flag in server/cabal.project.freeze Co-authored-by: Auke Booij <auke@tulcod.com> * Deselect a changed ENUM test for upgrade/downgrade CI * Deselect test here as well * [skip ci] remove dead code * Disable more tests for upgrade/downgrade * Fix which test gets deselected * Revert "Add hdb_catalog.current_setting abstraction for reading Hasura settings" This reverts commit 66e85ab9fbd56cca2c28a80201f6604fbe811b85. * Remove circular reference in cabal.project.freeze Co-authored-by: Karthikeyan Chinnakonda <karthikeyan@hasura.io> Co-authored-by: Auke Booij <auke@hasura.io> Co-authored-by: Tirumarai Selvan <tiru@hasura.io> Co-authored-by: Marion Schleifer <marion@hasura.io> Co-authored-by: Aleksandra Sikora <ola.zxcvbnm@gmail.com> Co-authored-by: Brandon Simmons <brandon.m.simmons@gmail.com> Co-authored-by: Vamshi Surabhi <0x777@users.noreply.github.com> Co-authored-by: Anon Ray <rayanon004@gmail.com> Co-authored-by: rakeshkky <12475069+rakeshkky@users.noreply.github.com> Co-authored-by: Anon Ray <ecthiender@users.noreply.github.com> Co-authored-by: Vamshi Surabhi <vamshi@hasura.io> Co-authored-by: Antoine Leblanc <antoine@hasura.io> Co-authored-by: Brandon Simmons <brandon@hasura.io> Co-authored-by: Phil Freeman <phil@hasura.io> Co-authored-by: Lyndon Maydwell <lyndon@sordina.net> Co-authored-by: Phil Freeman <paf31@cantab.net> Co-authored-by: Naveen Naidu <naveennaidu479@gmail.com> Co-authored-by: Karthikeyan Chinnakonda <chkarthikeyan95@gmail.com> Co-authored-by: Nizar Malangadan <nizar-m@users.noreply.github.com> Co-authored-by: Antoine Leblanc <crucuny@gmail.com> Co-authored-by: Auke Booij <auke@tulcod.com>
2020-08-21 20:27:01 +03:00
eventsHttpPoolSizeEnv =
( "HASURA_GRAPHQL_EVENTS_HTTP_POOL_SIZE",
"Max event processing threads (default: 100)"
)
eventsFetchIntervalEnv :: (String, String)
eventsFetchIntervalEnv =
( "HASURA_GRAPHQL_EVENTS_FETCH_INTERVAL",
"Interval in milliseconds to sleep before trying to fetch events again after a fetch returned no events from postgres."
)
eventsFetchBatchSizeEnv :: (String, String)
eventsFetchBatchSizeEnv =
( "HASURA_GRAPHQL_EVENTS_FETCH_BATCH_SIZE",
"The maximum number of events to be fetched from the events table in a single batch. Default 100"
)
asyncActionsFetchIntervalEnv :: (String, String)
asyncActionsFetchIntervalEnv =
( "HASURA_GRAPHQL_ASYNC_ACTIONS_FETCH_INTERVAL",
"Interval in milliseconds to sleep before trying to fetch new async actions. "
++ "Value \"0\" implies completely disable fetching async actions from storage. "
++ "Default 1000 milliseconds"
)
logHeadersFromEnvEnv :: (String, String)
logHeadersFromEnvEnv =
( "HASURA_GRAPHQL_LOG_HEADERS_FROM_ENV",
"Log headers sent instead of logging referenced environment variables."
)
retriesNumEnv :: (String, String)
retriesNumEnv =
( "HASURA_GRAPHQL_NO_OF_RETRIES",
"No.of retries if Postgres connection error occurs (default: 1)"
)
servePortEnv :: (String, String)
servePortEnv =
( "HASURA_GRAPHQL_SERVER_PORT",
"Port on which graphql-engine should be served (default: 8080)"
)
serveHostEnv :: (String, String)
serveHostEnv =
( "HASURA_GRAPHQL_SERVER_HOST",
"Host on which graphql-engine will listen (default: *)"
)
pgConnsEnv :: (String, String)
pgConnsEnv =
( "HASURA_GRAPHQL_PG_CONNECTIONS",
"Maximum number of Postgres connections that can be opened per stripe (default: 50). "
<> "When the maximum is reached we will block until a new connection becomes available, "
<> "even if there is capacity in other stripes."
)
pgStripesEnv :: (String, String)
pgStripesEnv =
( "HASURA_GRAPHQL_PG_STRIPES",
"Number of stripes (distinct sub-pools) to maintain with Postgres (default: 1). "
<> "New connections will be taken from a particular stripe pseudo-randomly."
)
pgTimeoutEnv :: (String, String)
pgTimeoutEnv =
( "HASURA_GRAPHQL_PG_TIMEOUT",
"Each connection's idle time before it is closed (default: 180 sec)"
)
pgConnLifetimeEnv :: (String, String)
pgConnLifetimeEnv =
( "HASURA_GRAPHQL_PG_CONN_LIFETIME",
"Time from connection creation after which the connection should be destroyed and a new one "
<> "created. A value of 0 indicates we should never destroy an active connection. If 0 is "
<> "passed, memory from large query results may not be reclaimed. (default: 600 sec)"
)
pgPoolTimeoutEnv :: (String, String)
pgPoolTimeoutEnv =
( "HASURA_GRAPHQL_PG_POOL_TIMEOUT",
"How long to wait when acquiring a Postgres connection, in seconds (default: forever)."
)
pgUsePrepareEnv :: (String, String)
pgUsePrepareEnv =
( "HASURA_GRAPHQL_USE_PREPARED_STATEMENTS",
"Use prepared statements for queries (default: true)"
)
txIsoEnv :: (String, String)
txIsoEnv =
( "HASURA_GRAPHQL_TX_ISOLATION",
"transaction isolation. read-committed / repeatable-read / serializable (default: read-commited)"
)
accessKeyEnv :: (String, String)
accessKeyEnv =
( "HASURA_GRAPHQL_ACCESS_KEY",
"Admin secret key, required to access this instance (deprecated: use HASURA_GRAPHQL_ADMIN_SECRET instead)"
)
adminSecretEnv :: (String, String)
adminSecretEnv =
( "HASURA_GRAPHQL_ADMIN_SECRET",
"Admin Secret key, required to access this instance"
)
authHookEnv :: (String, String)
authHookEnv =
( "HASURA_GRAPHQL_AUTH_HOOK",
"URL of the authorization webhook required to authorize requests"
)
authHookModeEnv :: (String, String)
authHookModeEnv =
( "HASURA_GRAPHQL_AUTH_HOOK_MODE",
"HTTP method to use for authorization webhook (default: GET)"
)
jwtSecretEnv :: (String, String)
jwtSecretEnv =
( "HASURA_GRAPHQL_JWT_SECRET",
jwtSecretHelp
)
unAuthRoleEnv :: (String, String)
unAuthRoleEnv =
( "HASURA_GRAPHQL_UNAUTHORIZED_ROLE",
"Unauthorized role, used when admin-secret is not sent in admin-secret only mode "
++ "or \"Authorization\" header is absent in JWT mode"
)
corsDisableEnv :: (String, String)
corsDisableEnv =
( "HASURA_GRAPHQL_DISABLE_CORS",
"Disable CORS. Do not send any CORS headers on any request"
)
corsDomainEnv :: (String, String)
corsDomainEnv =
( "HASURA_GRAPHQL_CORS_DOMAIN",
"CSV of list of domains, excluding scheme (http/https) and including port, "
++ "to allow CORS for. Wildcard domains are allowed. See docs for details."
)
enableConsoleEnv :: (String, String)
enableConsoleEnv =
( "HASURA_GRAPHQL_ENABLE_CONSOLE",
"Enable API Console (default: false)"
)
2019-01-28 16:55:28 +03:00
enableTelemetryEnv :: (String, String)
enableTelemetryEnv =
( "HASURA_GRAPHQL_ENABLE_TELEMETRY",
-- TODO (from master): better description
"Enable anonymous telemetry (default: true)"
2019-01-28 16:55:28 +03:00
)
wsReadCookieEnv :: (String, String)
wsReadCookieEnv =
( "HASURA_GRAPHQL_WS_READ_COOKIE",
"Read cookie on WebSocket initial handshake, even when CORS is disabled."
++ " This can be a potential security flaw! Please make sure you know "
++ "what you're doing."
++ "This configuration is only applicable when CORS is disabled."
)
stringifyNumEnv :: (String, String)
stringifyNumEnv =
( "HASURA_GRAPHQL_STRINGIFY_NUMERIC_TYPES",
"Stringify numeric types (default: false)"
)
dangerousBooleanCollapseEnv :: (String, String)
dangerousBooleanCollapseEnv =
( "HASURA_GRAPHQL_V1_BOOLEAN_NULL_COLLAPSE",
"Emulate V1's behaviour re. boolean expression, where an explicit 'null'"
<> " value will be interpreted to mean that the field should be ignored"
<> " [DEPRECATED, WILL BE REMOVED SOON] (default: false)"
)
defaultEnabledAPIs :: [API]
#ifdef DeveloperAPIs
defaultEnabledAPIs = [METADATA,GRAPHQL,PGDUMP,CONFIG,DEVELOPER]
#else
defaultEnabledAPIs = [METADATA,GRAPHQL,PGDUMP,CONFIG]
#endif
enabledAPIsEnv :: (String, String)
enabledAPIsEnv =
( "HASURA_GRAPHQL_ENABLED_APIS",
"Comma separated list of enabled APIs. (default: metadata,graphql,pgdump,config)"
)
[Preview] Inherited roles for postgres read queries fixes #3868 docker image - `hasura/graphql-engine:inherited-roles-preview-48b73a2de` Note: To be able to use the inherited roles feature, the graphql-engine should be started with the env variable `HASURA_GRAPHQL_EXPERIMENTAL_FEATURES` set to `inherited_roles`. Introduction ------------ This PR implements the idea of multiple roles as presented in this [paper](https://www.microsoft.com/en-us/research/wp-content/uploads/2016/02/FGALanguageICDE07.pdf). The multiple roles feature in this PR can be used via inherited roles. An inherited role is a role which can be created by combining multiple singular roles. For example, if there are two roles `author` and `editor` configured in the graphql-engine, then we can create a inherited role with the name of `combined_author_editor` role which will combine the select permissions of the `author` and `editor` roles and then make GraphQL queries using the `combined_author_editor`. How are select permissions of different roles are combined? ------------------------------------------------------------ A select permission includes 5 things: 1. Columns accessible to the role 2. Row selection filter 3. Limit 4. Allow aggregation 5. Scalar computed fields accessible to the role Suppose there are two roles, `role1` gives access to the `address` column with row filter `P1` and `role2` gives access to both the `address` and the `phone` column with row filter `P2` and we create a new role `combined_roles` which combines `role1` and `role2`. Let's say the following GraphQL query is queried with the `combined_roles` role. ```graphql query { employees { address phone } } ``` This will translate to the following SQL query: ```sql select (case when (P1 or P2) then address else null end) as address, (case when P2 then phone else null end) as phone from employee where (P1 or P2) ``` The other parameters of the select permission will be combined in the following manner: 1. Limit - Minimum of the limits will be the limit of the inherited role 2. Allow aggregations - If any of the role allows aggregation, then the inherited role will allow aggregation 3. Scalar computed fields - same as table column fields, as in the above example APIs for inherited roles: ---------------------- 1. `add_inherited_role` `add_inherited_role` is the [metadata API](https://hasura.io/docs/1.0/graphql/core/api-reference/index.html#schema-metadata-api) to create a new inherited role. It accepts two arguments `role_name`: the name of the inherited role to be added (String) `role_set`: list of roles that need to be combined (Array of Strings) Example: ```json { "type": "add_inherited_role", "args": { "role_name":"combined_user", "role_set":[ "user", "user1" ] } } ``` After adding the inherited role, the inherited role can be used like single roles like earlier Note: An inherited role can only be created with non-inherited/singular roles. 2. `drop_inherited_role` The `drop_inherited_role` API accepts the name of the inherited role and drops it from the metadata. It accepts a single argument: `role_name`: name of the inherited role to be dropped Example: ```json { "type": "drop_inherited_role", "args": { "role_name":"combined_user" } } ``` Metadata --------- The derived roles metadata will be included under the `experimental_features` key while exporting the metadata. ```json { "experimental_features": { "derived_roles": [ { "role_name": "manager_is_employee_too", "role_set": [ "employee", "manager" ] } ] } } ``` Scope ------ Only postgres queries and subscriptions are supported in this PR. Important points: ----------------- 1. All columns exposed to an inherited role will be marked as `nullable`, this is done so that cell value nullification can be done. TODOs ------- - [ ] Tests - [ ] Test a GraphQL query running with a inherited role without enabling inherited roles in experimental features - [] Tests for aggregate queries, limit, computed fields, functions, subscriptions (?) - [ ] Introspection test with a inherited role (nullability changes in a inherited role) - [ ] Docs - [ ] Changelog Co-authored-by: Vamshi Surabhi <6562944+0x777@users.noreply.github.com> GitOrigin-RevId: 3b8ee1e11f5ceca80fe294f8c074d42fbccfec63
2021-03-08 14:14:13 +03:00
experimentalFeaturesEnv :: (String, String)
experimentalFeaturesEnv =
( "HASURA_GRAPHQL_EXPERIMENTAL_FEATURES",
"Comma separated list of experimental features. (all: inherited_roles)"
[Preview] Inherited roles for postgres read queries fixes #3868 docker image - `hasura/graphql-engine:inherited-roles-preview-48b73a2de` Note: To be able to use the inherited roles feature, the graphql-engine should be started with the env variable `HASURA_GRAPHQL_EXPERIMENTAL_FEATURES` set to `inherited_roles`. Introduction ------------ This PR implements the idea of multiple roles as presented in this [paper](https://www.microsoft.com/en-us/research/wp-content/uploads/2016/02/FGALanguageICDE07.pdf). The multiple roles feature in this PR can be used via inherited roles. An inherited role is a role which can be created by combining multiple singular roles. For example, if there are two roles `author` and `editor` configured in the graphql-engine, then we can create a inherited role with the name of `combined_author_editor` role which will combine the select permissions of the `author` and `editor` roles and then make GraphQL queries using the `combined_author_editor`. How are select permissions of different roles are combined? ------------------------------------------------------------ A select permission includes 5 things: 1. Columns accessible to the role 2. Row selection filter 3. Limit 4. Allow aggregation 5. Scalar computed fields accessible to the role Suppose there are two roles, `role1` gives access to the `address` column with row filter `P1` and `role2` gives access to both the `address` and the `phone` column with row filter `P2` and we create a new role `combined_roles` which combines `role1` and `role2`. Let's say the following GraphQL query is queried with the `combined_roles` role. ```graphql query { employees { address phone } } ``` This will translate to the following SQL query: ```sql select (case when (P1 or P2) then address else null end) as address, (case when P2 then phone else null end) as phone from employee where (P1 or P2) ``` The other parameters of the select permission will be combined in the following manner: 1. Limit - Minimum of the limits will be the limit of the inherited role 2. Allow aggregations - If any of the role allows aggregation, then the inherited role will allow aggregation 3. Scalar computed fields - same as table column fields, as in the above example APIs for inherited roles: ---------------------- 1. `add_inherited_role` `add_inherited_role` is the [metadata API](https://hasura.io/docs/1.0/graphql/core/api-reference/index.html#schema-metadata-api) to create a new inherited role. It accepts two arguments `role_name`: the name of the inherited role to be added (String) `role_set`: list of roles that need to be combined (Array of Strings) Example: ```json { "type": "add_inherited_role", "args": { "role_name":"combined_user", "role_set":[ "user", "user1" ] } } ``` After adding the inherited role, the inherited role can be used like single roles like earlier Note: An inherited role can only be created with non-inherited/singular roles. 2. `drop_inherited_role` The `drop_inherited_role` API accepts the name of the inherited role and drops it from the metadata. It accepts a single argument: `role_name`: name of the inherited role to be dropped Example: ```json { "type": "drop_inherited_role", "args": { "role_name":"combined_user" } } ``` Metadata --------- The derived roles metadata will be included under the `experimental_features` key while exporting the metadata. ```json { "experimental_features": { "derived_roles": [ { "role_name": "manager_is_employee_too", "role_set": [ "employee", "manager" ] } ] } } ``` Scope ------ Only postgres queries and subscriptions are supported in this PR. Important points: ----------------- 1. All columns exposed to an inherited role will be marked as `nullable`, this is done so that cell value nullification can be done. TODOs ------- - [ ] Tests - [ ] Test a GraphQL query running with a inherited role without enabling inherited roles in experimental features - [] Tests for aggregate queries, limit, computed fields, functions, subscriptions (?) - [ ] Introspection test with a inherited role (nullability changes in a inherited role) - [ ] Docs - [ ] Changelog Co-authored-by: Vamshi Surabhi <6562944+0x777@users.noreply.github.com> GitOrigin-RevId: 3b8ee1e11f5ceca80fe294f8c074d42fbccfec63
2021-03-08 14:14:13 +03:00
)
gracefulShutdownEnv :: (String, String)
gracefulShutdownEnv =
( "HASURA_GRAPHQL_GRACEFUL_SHUTDOWN_TIMEOUT",
"Timeout for graceful shutdown before which in-flight scheduled events, "
<> " cron events and async actions to complete (default: 60 seconds)"
)
consoleAssetsDirEnv :: (String, String)
consoleAssetsDirEnv =
( "HASURA_GRAPHQL_CONSOLE_ASSETS_DIR",
"A directory from which static assets required for console is served at"
++ "'/console/assets' path. Can be set to '/srv/console-assets' on the"
++ " default docker image to disable loading assets from CDN."
)
enabledLogsEnv :: (String, String)
enabledLogsEnv =
( "HASURA_GRAPHQL_ENABLED_LOG_TYPES",
"Comma separated list of enabled log types "
<> "(default: startup,http-log,webhook-log,websocket-log)"
<> "(all: startup,http-log,webhook-log,websocket-log,query-log)"
)
logLevelEnv :: (String, String)
logLevelEnv =
( "HASURA_GRAPHQL_LOG_LEVEL",
"Server log level (default: info) (all: error, warn, info, debug)"
)
devModeEnv :: (String, String)
devModeEnv =
( "HASURA_GRAPHQL_DEV_MODE",
"Set dev mode for GraphQL requests; include 'internal' key in the errors extensions (if required) of the response"
)
enableRemoteSchemaPermsEnv :: (String, String)
enableRemoteSchemaPermsEnv =
( "HASURA_GRAPHQL_ENABLE_REMOTE_SCHEMA_PERMISSIONS",
"Enables remote schema permissions (default: false)"
)
inferFunctionPermsEnv :: (String, String)
inferFunctionPermsEnv =
( "HASURA_GRAPHQL_INFER_FUNCTION_PERMISSIONS",
"Infers function permissions (default: true)"
)
maintenanceModeEnv :: (String, String)
maintenanceModeEnv =
( "HASURA_GRAPHQL_ENABLE_MAINTENANCE_MODE",
"Flag to enable maintenance mode in the graphql-engine"
)
schemaPollIntervalEnv :: (String, String)
schemaPollIntervalEnv =
( "HASURA_GRAPHQL_SCHEMA_SYNC_POLL_INTERVAL",
"Interval to poll metadata storage for updates in milliseconds - Default 1000 (1s) - Set to 0 to disable"
)
adminInternalErrorsEnv :: (String, String)
adminInternalErrorsEnv =
( "HASURA_GRAPHQL_ADMIN_INTERNAL_ERRORS",
"Enables including 'internal' information in an error response for requests made by an 'admin' (default: true)"
)
parsePostgresConnInfo :: Parser (PostgresConnInfo (Maybe PostgresRawConnInfo))
parsePostgresConnInfo = do
retries' <- retries
maybeRawConnInfo <-
(fmap PGConnDatabaseUrl <$> parseDatabaseUrl)
<|> (fmap PGConnDetails <$> parseRawConnDetails)
pure $ PostgresConnInfo maybeRawConnInfo retries'
where
retries =
optional $
option
auto
( long "retries"
<> metavar "NO OF RETRIES"
<> help (snd retriesNumEnv)
)
parseDatabaseUrl :: Parser (Maybe URLTemplate)
parseDatabaseUrl =
optional $
option
(eitherReader (parseURLTemplate . T.pack))
( long "database-url"
<> metavar "<DATABASE-URL>"
<> help (snd databaseUrlEnv)
)
parseRawConnDetails :: Parser (Maybe PostgresRawConnDetails)
parseRawConnDetails = do
host' <- host
port' <- port
user' <- user
password' <- password
dbName' <- dbName
options' <- options
pure $
PostgresRawConnDetails
<$> host'
<*> port'
<*> user'
<*> pure password'
<*> dbName'
<*> pure options'
where
host =
optional $
strOption
( long "host"
<> metavar "<HOST>"
<> help "Postgres server host"
)
port =
optional $
option
auto
( long "port"
<> short 'p'
<> metavar "<PORT>"
<> help "Postgres server port"
)
user =
optional $
strOption
( long "user"
<> short 'u'
<> metavar "<USER>"
<> help "Database user name"
)
password =
strOption
( long "password"
<> metavar "<PASSWORD>"
<> value ""
<> help "Password of the user"
)
dbName =
optional $
strOption
( long "dbname"
<> short 'd'
<> metavar "<DBNAME>"
<> help "Database name to connect to"
)
options =
optional $
strOption
( long "pg-connection-options"
<> short 'o'
<> metavar "<DATABASE-OPTIONS>"
<> help "PostgreSQL options"
)
parseMetadataDbUrl :: Parser (Maybe String)
parseMetadataDbUrl =
optional $
strOption
( long "metadata-database-url"
<> metavar "<METADATA-DATABASE-URL>"
<> help (snd metadataDbUrlEnv)
)
2018-06-27 16:11:32 +03:00
parseTxIsolation :: Parser (Maybe Q.TxIsolation)
parseTxIsolation =
optional $
option
(eitherReader readIsoLevel)
( long "tx-iso"
<> short 'i'
<> metavar "<TXISO>"
<> help (snd txIsoEnv)
)
parseConnParams :: Parser RawConnParams
parseConnParams =
RawConnParams <$> stripes <*> conns <*> idleTimeout <*> connLifetime <*> allowPrepare <*> poolTimeout
where
stripes =
optional $
option
auto
( long "stripes"
<> short 's'
<> metavar "<NO OF STRIPES>"
<> help (snd pgStripesEnv)
)
conns =
optional $
option
auto
( long "connections"
<> short 'c'
<> metavar "<NO OF CONNS>"
<> help (snd pgConnsEnv)
)
idleTimeout =
optional $
option
auto
( long "timeout"
<> metavar "<SECONDS>"
<> help (snd pgTimeoutEnv)
)
connLifetime =
fmap (fmap (realToFrac :: Int -> NominalDiffTime)) $
optional $
option
auto
( long "conn-lifetime"
<> metavar "<SECONDS>"
<> help (snd pgConnLifetimeEnv)
)
allowPrepare =
optional $
option
(eitherReader parseStringAsBool)
( long "use-prepared-statements"
<> metavar "<true|false>"
<> help (snd pgUsePrepareEnv)
)
poolTimeout =
fmap (fmap (realToFrac :: Int -> NominalDiffTime)) $
optional $
option
auto
( long "pool-timeout"
<> metavar "<SECONDS>"
<> help (snd pgPoolTimeoutEnv)
)
parseServerPort :: Parser (Maybe Int)
parseServerPort =
optional $
option
auto
( long "server-port"
<> metavar "<PORT>"
<> help (snd servePortEnv)
)
parseServerHost :: Parser (Maybe HostPreference)
parseServerHost =
optional $
strOption
( long "server-host"
<> metavar "<HOST>"
<> help "Host on which graphql-engine will listen (default: *)"
)
parseAccessKey :: Parser (Maybe AdminSecretHash)
parseAccessKey =
optional $
hashAdminSecret
<$> strOption
( long "access-key"
<> metavar "ADMIN SECRET KEY (DEPRECATED: USE --admin-secret)"
<> help (snd adminSecretEnv)
)
parseAdminSecret :: Parser (Maybe AdminSecretHash)
parseAdminSecret =
optional $
hashAdminSecret
<$> strOption
( long "admin-secret"
<> metavar "ADMIN SECRET KEY"
<> help (snd adminSecretEnv)
)
add support for jwt authorization (close #186) (#255) The API: 1. HGE has `--jwt-secret` flag or `HASURA_GRAPHQL_JWT_SECRET` env var. The value of which is a JSON. 2. The structure of this JSON is: `{"type": "<standard-JWT-algorithms>", "key": "<the-key>"}` `type` : Standard JWT algos : `HS256`, `RS256`, `RS512` etc. (see jwt.io). `key`: i. Incase of symmetric key, the key as it is. ii. Incase of asymmetric keys, only the public key, in a PEM encoded string or as a X509 certificate. 3. The claims in the JWT token must contain the following: i. `x-hasura-default-role` field: default role of that user ii. `x-hasura-allowed-roles` : A list of allowed roles for the user. The default role is overriden by `x-hasura-role` header. 4. The claims in the JWT token, can have other `x-hasura-*` fields where their values can only be strings. 5. The JWT tokens are sent as `Authorization: Bearer <token>` headers. --- To test: 1. Generate a shared secret (for HMAC-SHA256) or RSA key pair. 2. Goto https://jwt.io/ , add the keys 3. Edit the claims to have `x-hasura-role` (mandatory) and other `x-hasura-*` fields. Add permissions related to the claims to test permissions. 4. Start HGE with `--jwt-secret` flag or `HASURA_GRAPHQL_JWT_SECRET` env var, which takes a JSON string: `{"type": "HS256", "key": "mylongsharedsecret"}` or `{"type":"RS256", "key": "<PEM-encoded-public-key>"}` 5. Copy the JWT token from jwt.io and use it in the `Authorization: Bearer <token>` header. --- TODO: Support EC public keys. It is blocked on frasertweedale/hs-jose#61
2018-08-30 13:32:09 +03:00
parseWebHook :: Parser RawAuthHook
parseWebHook =
AuthHookG <$> url <*> urlType
where
url =
optional $
strOption
( long "auth-hook"
<> metavar "<WEB HOOK URL>"
<> help (snd authHookEnv)
)
urlType =
optional $
option
(eitherReader readHookType)
( long "auth-hook-mode"
<> metavar "<GET|POST>"
<> help (snd authHookModeEnv)
)
parseJwtSecret :: Parser (Maybe JWTConfig)
parseJwtSecret =
optional $
option
(eitherReader readJson)
( long "jwt-secret"
<> metavar "<JSON CONFIG>"
<> help (snd jwtSecretEnv)
)
add support for jwt authorization (close #186) (#255) The API: 1. HGE has `--jwt-secret` flag or `HASURA_GRAPHQL_JWT_SECRET` env var. The value of which is a JSON. 2. The structure of this JSON is: `{"type": "<standard-JWT-algorithms>", "key": "<the-key>"}` `type` : Standard JWT algos : `HS256`, `RS256`, `RS512` etc. (see jwt.io). `key`: i. Incase of symmetric key, the key as it is. ii. Incase of asymmetric keys, only the public key, in a PEM encoded string or as a X509 certificate. 3. The claims in the JWT token must contain the following: i. `x-hasura-default-role` field: default role of that user ii. `x-hasura-allowed-roles` : A list of allowed roles for the user. The default role is overriden by `x-hasura-role` header. 4. The claims in the JWT token, can have other `x-hasura-*` fields where their values can only be strings. 5. The JWT tokens are sent as `Authorization: Bearer <token>` headers. --- To test: 1. Generate a shared secret (for HMAC-SHA256) or RSA key pair. 2. Goto https://jwt.io/ , add the keys 3. Edit the claims to have `x-hasura-role` (mandatory) and other `x-hasura-*` fields. Add permissions related to the claims to test permissions. 4. Start HGE with `--jwt-secret` flag or `HASURA_GRAPHQL_JWT_SECRET` env var, which takes a JSON string: `{"type": "HS256", "key": "mylongsharedsecret"}` or `{"type":"RS256", "key": "<PEM-encoded-public-key>"}` 5. Copy the JWT token from jwt.io and use it in the `Authorization: Bearer <token>` header. --- TODO: Support EC public keys. It is blocked on frasertweedale/hs-jose#61
2018-08-30 13:32:09 +03:00
jwtSecretHelp :: String
jwtSecretHelp =
"The JSON containing type and the JWK used for verifying. e.g: "
<> "`{\"type\": \"HS256\", \"key\": \"<your-hmac-shared-secret>\", \"claims_namespace\": \"<optional-custom-claims-key-name>\"}`,"
<> "`{\"type\": \"RS256\", \"key\": \"<your-PEM-RSA-public-key>\", \"claims_namespace\": \"<optional-custom-claims-key-name>\"}`"
2018-06-27 16:11:32 +03:00
parseUnAuthRole :: Parser (Maybe RoleName)
parseUnAuthRole =
fmap mkRoleName' $
optional $
strOption
( long "unauthorized-role"
<> metavar "<ROLE>"
<> help (snd unAuthRoleEnv)
)
where
backend only insert permissions (rfc #4120) (#4224) * move user info related code to Hasura.User module * the RFC #4120 implementation; insert permissions with admin secret * revert back to old RoleName based schema maps An attempt made to avoid duplication of schema contexts in types if any role doesn't possess any admin secret specific schema * fix compile errors in haskell test * keep 'user_vars' for session variables in http-logs * no-op refacto * tests for admin only inserts * update docs for admin only inserts * updated CHANGELOG.md * default behaviour when admin secret is not set * fix x-hasura-role to X-Hasura-Role in pytests * introduce effective timeout in actions async tests * update docs for admin-secret not configured case * Update docs/graphql/manual/api-reference/schema-metadata-api/permission.rst Co-Authored-By: Marion Schleifer <marion@hasura.io> * Apply suggestions from code review Co-Authored-By: Marion Schleifer <marion@hasura.io> * a complete iteration backend insert permissions accessable via 'x-hasura-backend-privilege' session variable * console changes for backend-only permissions * provide tooltip id; update labels and tooltips; * requested changes * requested changes - remove className from Toggle component - use appropriate function name (capitalizeFirstChar -> capitalize) * use toggle props from definitelyTyped * fix accidental commit * Revert "introduce effective timeout in actions async tests" This reverts commit b7a59c19d643520cfde6af579889e1038038438a. * generate complete schema for both 'default' and 'backend' sessions * Apply suggestions from code review Co-Authored-By: Marion Schleifer <marion@hasura.io> * remove unnecessary import, export Toggle as is * update session variable in tooltip * 'x-hasura-use-backend-only-permissions' variable to switch * update help texts * update docs * update docs * update console help text * regenerate package-lock * serve no backend schema when backend_only: false and header set to true - Few type name refactor as suggested by @0x777 * update CHANGELOG.md * Update CHANGELOG.md * Update CHANGELOG.md * fix a merge bug where a certain entity didn't get removed Co-authored-by: Marion Schleifer <marion@hasura.io> Co-authored-by: Rishichandra Wawhal <rishi@hasura.io> Co-authored-by: rikinsk <rikin.kachhia@gmail.com> Co-authored-by: Tirumarai Selvan <tiru@hasura.io>
2020-04-24 12:10:53 +03:00
mkRoleName' mText = mText >>= mkRoleName
parseCorsConfig :: Parser (Maybe CorsConfig)
parseCorsConfig = mapCC <$> disableCors <*> corsDomain
where
corsDomain =
optional $
option
(eitherReader readCorsDomains)
( long "cors-domain"
<> metavar "<DOMAINS>"
<> help (snd corsDomainEnv)
)
disableCors =
switch
( long "disable-cors"
<> help (snd corsDisableEnv)
)
2018-06-27 16:11:32 +03:00
mapCC isDisabled domains =
bool domains (Just $ CCDisabled False) isDisabled
parseEnableConsole :: Parser Bool
parseEnableConsole =
switch
( long "enable-console"
<> help (snd enableConsoleEnv)
)
parseConsoleAssetsDir :: Parser (Maybe Text)
parseConsoleAssetsDir =
optional $
option
(eitherReader fromEnv)
( long "console-assets-dir"
<> help (snd consoleAssetsDirEnv)
)
2019-01-28 16:55:28 +03:00
parseEnableTelemetry :: Parser (Maybe Bool)
parseEnableTelemetry =
optional $
option
(eitherReader parseStringAsBool)
( long "enable-telemetry"
<> help (snd enableTelemetryEnv)
)
2019-01-28 16:55:28 +03:00
parseWsReadCookie :: Parser Bool
parseWsReadCookie =
switch
( long "ws-read-cookie"
<> help (snd wsReadCookieEnv)
)
parseStringifyNum :: Parser Bool
parseStringifyNum =
switch
( long "stringify-numeric-types"
<> help (snd stringifyNumEnv)
)
parseDangerousBooleanCollapse :: Parser (Maybe Bool)
parseDangerousBooleanCollapse =
optional $
option
(eitherReader parseStrAsBool)
( long "v1-boolean-null-collapse"
<> help (snd dangerousBooleanCollapseEnv)
)
parseEnabledAPIs :: Parser (Maybe [API])
parseEnabledAPIs =
optional $
option
(eitherReader readAPIs)
( long "enabled-apis"
<> help (snd enabledAPIsEnv)
)
[Preview] Inherited roles for postgres read queries fixes #3868 docker image - `hasura/graphql-engine:inherited-roles-preview-48b73a2de` Note: To be able to use the inherited roles feature, the graphql-engine should be started with the env variable `HASURA_GRAPHQL_EXPERIMENTAL_FEATURES` set to `inherited_roles`. Introduction ------------ This PR implements the idea of multiple roles as presented in this [paper](https://www.microsoft.com/en-us/research/wp-content/uploads/2016/02/FGALanguageICDE07.pdf). The multiple roles feature in this PR can be used via inherited roles. An inherited role is a role which can be created by combining multiple singular roles. For example, if there are two roles `author` and `editor` configured in the graphql-engine, then we can create a inherited role with the name of `combined_author_editor` role which will combine the select permissions of the `author` and `editor` roles and then make GraphQL queries using the `combined_author_editor`. How are select permissions of different roles are combined? ------------------------------------------------------------ A select permission includes 5 things: 1. Columns accessible to the role 2. Row selection filter 3. Limit 4. Allow aggregation 5. Scalar computed fields accessible to the role Suppose there are two roles, `role1` gives access to the `address` column with row filter `P1` and `role2` gives access to both the `address` and the `phone` column with row filter `P2` and we create a new role `combined_roles` which combines `role1` and `role2`. Let's say the following GraphQL query is queried with the `combined_roles` role. ```graphql query { employees { address phone } } ``` This will translate to the following SQL query: ```sql select (case when (P1 or P2) then address else null end) as address, (case when P2 then phone else null end) as phone from employee where (P1 or P2) ``` The other parameters of the select permission will be combined in the following manner: 1. Limit - Minimum of the limits will be the limit of the inherited role 2. Allow aggregations - If any of the role allows aggregation, then the inherited role will allow aggregation 3. Scalar computed fields - same as table column fields, as in the above example APIs for inherited roles: ---------------------- 1. `add_inherited_role` `add_inherited_role` is the [metadata API](https://hasura.io/docs/1.0/graphql/core/api-reference/index.html#schema-metadata-api) to create a new inherited role. It accepts two arguments `role_name`: the name of the inherited role to be added (String) `role_set`: list of roles that need to be combined (Array of Strings) Example: ```json { "type": "add_inherited_role", "args": { "role_name":"combined_user", "role_set":[ "user", "user1" ] } } ``` After adding the inherited role, the inherited role can be used like single roles like earlier Note: An inherited role can only be created with non-inherited/singular roles. 2. `drop_inherited_role` The `drop_inherited_role` API accepts the name of the inherited role and drops it from the metadata. It accepts a single argument: `role_name`: name of the inherited role to be dropped Example: ```json { "type": "drop_inherited_role", "args": { "role_name":"combined_user" } } ``` Metadata --------- The derived roles metadata will be included under the `experimental_features` key while exporting the metadata. ```json { "experimental_features": { "derived_roles": [ { "role_name": "manager_is_employee_too", "role_set": [ "employee", "manager" ] } ] } } ``` Scope ------ Only postgres queries and subscriptions are supported in this PR. Important points: ----------------- 1. All columns exposed to an inherited role will be marked as `nullable`, this is done so that cell value nullification can be done. TODOs ------- - [ ] Tests - [ ] Test a GraphQL query running with a inherited role without enabling inherited roles in experimental features - [] Tests for aggregate queries, limit, computed fields, functions, subscriptions (?) - [ ] Introspection test with a inherited role (nullability changes in a inherited role) - [ ] Docs - [ ] Changelog Co-authored-by: Vamshi Surabhi <6562944+0x777@users.noreply.github.com> GitOrigin-RevId: 3b8ee1e11f5ceca80fe294f8c074d42fbccfec63
2021-03-08 14:14:13 +03:00
parseExperimentalFeatures :: Parser (Maybe [ExperimentalFeature])
parseExperimentalFeatures =
optional $
option
(eitherReader readExperimentalFeatures)
( long "experimental-features"
<> help (snd experimentalFeaturesEnv)
)
[Preview] Inherited roles for postgres read queries fixes #3868 docker image - `hasura/graphql-engine:inherited-roles-preview-48b73a2de` Note: To be able to use the inherited roles feature, the graphql-engine should be started with the env variable `HASURA_GRAPHQL_EXPERIMENTAL_FEATURES` set to `inherited_roles`. Introduction ------------ This PR implements the idea of multiple roles as presented in this [paper](https://www.microsoft.com/en-us/research/wp-content/uploads/2016/02/FGALanguageICDE07.pdf). The multiple roles feature in this PR can be used via inherited roles. An inherited role is a role which can be created by combining multiple singular roles. For example, if there are two roles `author` and `editor` configured in the graphql-engine, then we can create a inherited role with the name of `combined_author_editor` role which will combine the select permissions of the `author` and `editor` roles and then make GraphQL queries using the `combined_author_editor`. How are select permissions of different roles are combined? ------------------------------------------------------------ A select permission includes 5 things: 1. Columns accessible to the role 2. Row selection filter 3. Limit 4. Allow aggregation 5. Scalar computed fields accessible to the role Suppose there are two roles, `role1` gives access to the `address` column with row filter `P1` and `role2` gives access to both the `address` and the `phone` column with row filter `P2` and we create a new role `combined_roles` which combines `role1` and `role2`. Let's say the following GraphQL query is queried with the `combined_roles` role. ```graphql query { employees { address phone } } ``` This will translate to the following SQL query: ```sql select (case when (P1 or P2) then address else null end) as address, (case when P2 then phone else null end) as phone from employee where (P1 or P2) ``` The other parameters of the select permission will be combined in the following manner: 1. Limit - Minimum of the limits will be the limit of the inherited role 2. Allow aggregations - If any of the role allows aggregation, then the inherited role will allow aggregation 3. Scalar computed fields - same as table column fields, as in the above example APIs for inherited roles: ---------------------- 1. `add_inherited_role` `add_inherited_role` is the [metadata API](https://hasura.io/docs/1.0/graphql/core/api-reference/index.html#schema-metadata-api) to create a new inherited role. It accepts two arguments `role_name`: the name of the inherited role to be added (String) `role_set`: list of roles that need to be combined (Array of Strings) Example: ```json { "type": "add_inherited_role", "args": { "role_name":"combined_user", "role_set":[ "user", "user1" ] } } ``` After adding the inherited role, the inherited role can be used like single roles like earlier Note: An inherited role can only be created with non-inherited/singular roles. 2. `drop_inherited_role` The `drop_inherited_role` API accepts the name of the inherited role and drops it from the metadata. It accepts a single argument: `role_name`: name of the inherited role to be dropped Example: ```json { "type": "drop_inherited_role", "args": { "role_name":"combined_user" } } ``` Metadata --------- The derived roles metadata will be included under the `experimental_features` key while exporting the metadata. ```json { "experimental_features": { "derived_roles": [ { "role_name": "manager_is_employee_too", "role_set": [ "employee", "manager" ] } ] } } ``` Scope ------ Only postgres queries and subscriptions are supported in this PR. Important points: ----------------- 1. All columns exposed to an inherited role will be marked as `nullable`, this is done so that cell value nullification can be done. TODOs ------- - [ ] Tests - [ ] Test a GraphQL query running with a inherited role without enabling inherited roles in experimental features - [] Tests for aggregate queries, limit, computed fields, functions, subscriptions (?) - [ ] Introspection test with a inherited role (nullability changes in a inherited role) - [ ] Docs - [ ] Changelog Co-authored-by: Vamshi Surabhi <6562944+0x777@users.noreply.github.com> GitOrigin-RevId: 3b8ee1e11f5ceca80fe294f8c074d42fbccfec63
2021-03-08 14:14:13 +03:00
parseGracefulShutdownTimeout :: Parser (Maybe Seconds)
parseGracefulShutdownTimeout =
optional $
option
(eitherReader readEither)
( long "graceful-shutdown-timeout"
<> metavar "<INTERVAL (seconds)>"
<> help (snd gracefulShutdownEnv)
)
2019-04-17 12:48:41 +03:00
parseMxRefetchInt :: Parser (Maybe LQ.RefetchInterval)
parseMxRefetchInt =
optional $
option
(eitherReader fromEnv)
( long "live-queries-multiplexed-refetch-interval"
<> metavar "<INTERVAL(ms)>"
<> help (snd mxRefetchDelayEnv)
)
2019-04-17 12:48:41 +03:00
parseMxBatchSize :: Parser (Maybe LQ.BatchSize)
parseMxBatchSize =
optional $
option
(eitherReader fromEnv)
( long "live-queries-multiplexed-batch-size"
<> metavar "BATCH_SIZE"
<> help (snd mxBatchSizeEnv)
)
2019-04-17 12:48:41 +03:00
parseEnableAllowlist :: Parser Bool
parseEnableAllowlist =
switch
( long "enable-allowlist"
<> help (snd enableAllowlistEnv)
)
parseGraphqlDevMode :: Parser Bool
parseGraphqlDevMode =
switch
( long "dev-mode"
<> help (snd devModeEnv)
)
parseGraphqlAdminInternalErrors :: Parser (Maybe Bool)
parseGraphqlAdminInternalErrors =
optional $
option
(eitherReader parseStrAsBool)
( long "admin-internal-errors"
<> help (snd adminInternalErrorsEnv)
)
parseGraphqlEventsHttpPoolSize :: Parser (Maybe Int)
parseGraphqlEventsHttpPoolSize =
optional $
option
(eitherReader fromEnv)
( long "events-http-pool-size"
<> metavar (fst eventsHttpPoolSizeEnv)
<> help (snd eventsHttpPoolSizeEnv)
)
parseGraphqlEventsFetchInterval :: Parser (Maybe Milliseconds)
parseGraphqlEventsFetchInterval =
optional $
option
(eitherReader readEither)
( long "events-fetch-interval"
<> metavar (fst eventsFetchIntervalEnv)
<> help (snd eventsFetchIntervalEnv)
)
parseEventsFetchBatchSize :: Parser (Maybe NonNegativeInt)
parseEventsFetchBatchSize =
optional $
option
(eitherReader readNonNegativeInt)
( long "events-fetch-batch-size"
<> metavar (fst eventsFetchBatchSizeEnv)
<> help (snd eventsFetchBatchSizeEnv)
)
Disable schema sync with an interval of 0 instead of an explicit flag Removing `schemaSyncDisable` flag and interpreting `schemaPollInterval` of `0` as disabling schema sync. This change brings the convention in line with how action and other intervals are used to disable processes. There is an opportunity to abstract the notion of an optional interval similar to how actions uses `AsyncActionsFetchInterval`. This can be used for the following fields of ServeOptions, with RawServeOptions having a milliseconds value where `0` is interpreted as disable. OptionalInterval: ``` -- | Sleep time interval for activities data OptionalInterval = Skip -- ^ No polling | Interval !Milliseconds -- ^ Interval time deriving (Show, Eq) ``` ServeOptions: ``` data ServeOptions impl = ServeOptions { ... , soEventsFetchInterval :: !OptionalInterval , soAsyncActionsFetchInterval :: !OptionalInterval , soSchemaPollInterval :: !OptionalInterval ... } ``` Rather than encoding a `Maybe OptionalInterval` in RawServeOptions, instead a `Maybe Milliseconds` can be used to more directly express the input format, with the ServeOptions constructor interpreting `0` as `Skip`. Current inconsistencies: * `soEventsFetchInterval` has no value interpreted as disabling the fetches * `soAsyncActionsFetchInterval` uses an `OptionalInterval` analog in `RawServeOptions` instead of `Milliseconds` * `soSchemaPollInterval` currently uses `Milliseconds` directly in `ServeOptions` --- ### Kodiak commit message Information used by [Kodiak bot](https://kodiakhq.com/) while merging this PR. #### Commit title Same as the title of this pull request GitOrigin-RevId: 3cda1656ae39ae95ba142512ed4e123d6ffeb7fe
2021-04-07 12:59:48 +03:00
parseGraphqlAsyncActionsFetchInterval :: Parser (Maybe Milliseconds)
parseGraphqlAsyncActionsFetchInterval =
optional $
option
(eitherReader readEither)
( long "async-actions-fetch-interval"
<> metavar (fst asyncActionsFetchIntervalEnv)
<> help (snd eventsFetchIntervalEnv)
)
parseLogHeadersFromEnv :: Parser Bool
parseLogHeadersFromEnv =
switch
( long "log-headers-from-env"
<> help (snd devModeEnv)
)
parseEnableRemoteSchemaPerms :: Parser Bool
parseEnableRemoteSchemaPerms =
switch
( long "enable-remote-schema-permissions"
<> help (snd enableRemoteSchemaPermsEnv)
)
parseInferFunctionPerms :: Parser (Maybe Bool)
parseInferFunctionPerms =
optional $
option
(eitherReader parseStrAsBool)
( long "infer-function-permissions"
<> help (snd inferFunctionPermsEnv)
)
parseEnableMaintenanceMode :: Parser Bool
parseEnableMaintenanceMode =
switch
( long "enable-maintenance-mode"
<> help (snd maintenanceModeEnv)
)
parseSchemaPollInterval :: Parser (Maybe Milliseconds)
parseSchemaPollInterval =
optional $
option
(eitherReader readEither)
( long "schema-sync-poll-interval"
<> metavar (fst schemaPollIntervalEnv)
<> help (snd schemaPollIntervalEnv)
)
2019-04-17 12:48:41 +03:00
mxRefetchDelayEnv :: (String, String)
mxRefetchDelayEnv =
( "HASURA_GRAPHQL_LIVE_QUERIES_MULTIPLEXED_REFETCH_INTERVAL",
"results will only be sent once in this interval (in milliseconds) for "
<> "live queries which can be multiplexed. Default: 1000 (1sec)"
2019-04-17 12:48:41 +03:00
)
mxBatchSizeEnv :: (String, String)
mxBatchSizeEnv =
( "HASURA_GRAPHQL_LIVE_QUERIES_MULTIPLEXED_BATCH_SIZE",
"multiplexed live queries are split into batches of the specified "
<> "size. Default 100. "
2019-04-17 12:48:41 +03:00
)
enableAllowlistEnv :: (String, String)
enableAllowlistEnv =
( "HASURA_GRAPHQL_ENABLE_ALLOWLIST",
"Only accept allowed GraphQL queries"
)
parsePlanCacheSize :: Parser (Maybe Cache.CacheSize)
parsePlanCacheSize =
optional $
option
(eitherReader Cache.parseCacheSize)
( long "query-plan-cache-size"
<> help
( "[DEPRECATED: value ignored.] The maximum number of query plans "
<> "that can be cached, allowed values: 0-65535, "
<> "0 disables the cache. Default 4000"
)
)
parseEnabledLogs :: L.EnabledLogTypes impl => Parser (Maybe [L.EngineLogType impl])
parseEnabledLogs =
optional $
option
(eitherReader L.parseEnabledLogTypes)
( long "enabled-log-types"
<> help (snd enabledLogsEnv)
)
parseLogLevel :: Parser (Maybe L.LogLevel)
parseLogLevel =
optional $
option
(eitherReader readLogLevel)
( long "log-level"
<> help (snd logLevelEnv)
)
censorQueryItem :: Text -> QueryItem -> QueryItem
censorQueryItem sensitive (key, Just _) | key == encodeUtf8 sensitive = (key, Just "...")
censorQueryItem _ qi = qi
censorQuery :: Text -> Query -> Query
censorQuery sensitive = fmap (censorQueryItem sensitive)
updateQuery :: (Query -> Query) -> URI -> URI
updateQuery f uri =
let queries = parseQuery $ pack $ uriQuery uri
in uri {uriQuery = unpack (renderQuery True $ f queries)}
censorURI :: Text -> URI -> URI
censorURI sensitive uri = updateQuery (censorQuery sensitive) uri
-- Init logging related
connInfoToLog :: Q.ConnInfo -> StartupLog
connInfoToLog connInfo =
StartupLog L.LevelInfo "postgres_connection" infoVal
where
Q.ConnInfo retries details = connInfo
infoVal = case details of
Q.CDDatabaseURI uri -> mkDBUriLog $ T.unpack $ bsToTxt uri
Q.CDOptions co ->
J.object
[ "host" J..= Q.connHost co,
"port" J..= Q.connPort co,
"user" J..= Q.connUser co,
"database" J..= Q.connDatabase co,
"retries" J..= retries
]
mkDBUriLog uri =
case show . censorURI "sslpassword" <$> parseURI uri of
Nothing ->
J.object
["error" J..= ("parsing database url failed" :: String)]
Just s ->
J.object
[ "retries" J..= retries,
"database_url" J..= s
]
serveOptsToLog :: J.ToJSON (L.EngineLogType impl) => ServeOptions impl -> StartupLog
serveOptsToLog so =
StartupLog L.LevelInfo "server_configuration" infoVal
where
infoVal =
J.object
[ "port" J..= soPort so,
"server_host" J..= show (soHost so),
"transaction_isolation" J..= show (soTxIso so),
"admin_secret_set" J..= isJust (soAdminSecret so),
"auth_hook" J..= (ahUrl <$> soAuthHook so),
"auth_hook_mode" J..= (show . ahType <$> soAuthHook so),
"jwt_secret" J..= (J.toJSON <$> soJwtSecret so),
"unauth_role" J..= soUnAuthRole so,
"cors_config" J..= soCorsConfig so,
"enable_console" J..= soEnableConsole so,
"console_assets_dir" J..= soConsoleAssetsDir so,
"enable_telemetry" J..= soEnableTelemetry so,
"use_prepared_statements" J..= (Q.cpAllowPrepare . soConnParams) so,
"stringify_numeric_types" J..= soStringifyNum so,
"v1-boolean-null-collapse" J..= soDangerousBooleanCollapse so,
"enabled_apis" J..= soEnabledAPIs so,
"live_query_options" J..= soLiveQueryOpts so,
"enable_allowlist" J..= soEnableAllowlist so,
"enabled_log_types" J..= soEnabledLogTypes so,
"log_level" J..= soLogLevel so,
"remote_schema_permissions" J..= soEnableRemoteSchemaPermissions so,
"websocket_compression_options" J..= show (WS.connectionCompressionOptions . soConnectionOptions $ so),
"websocket_keep_alive" J..= show (soWebsocketKeepAlive so),
"infer_function_permissions" J..= soInferFunctionPermissions so,
"enable_maintenance_mode" J..= soEnableMaintenanceMode so,
"experimental_features" J..= soExperimentalFeatures so,
"events_fetch_batch_size" J..= soEventsFetchBatchSize so,
"graceful_shutdown_timeout" J..= soGracefulShutdownTimeout so,
"websocket_connection_init_timeout" J..= show (soWebsocketConnectionInitTimeout so)
]
mkGenericStrLog :: L.LogLevel -> Text -> String -> StartupLog
mkGenericStrLog logLevel k msg =
StartupLog logLevel k $ J.toJSON msg
mkGenericLog :: (J.ToJSON a) => L.LogLevel -> Text -> a -> StartupLog
mkGenericLog logLevel k msg =
StartupLog logLevel k $ J.toJSON msg
inconsistentMetadataLog :: SchemaCache -> StartupLog
inconsistentMetadataLog sc =
StartupLog L.LevelWarn "inconsistent_metadata" infoVal
where
infoVal = J.object ["objects" J..= scInconsistentObjs sc]
serveOptionsParser :: L.EnabledLogTypes impl => Parser (RawServeOptions impl)
serveOptionsParser =
RawServeOptions
<$> parseServerPort
<*> parseServerHost
<*> parseConnParams
<*> parseTxIsolation
<*> (parseAdminSecret <|> parseAccessKey)
<*> parseWebHook
<*> parseJwtSecret
<*> parseUnAuthRole
<*> parseCorsConfig
<*> parseEnableConsole
<*> parseConsoleAssetsDir
<*> parseEnableTelemetry
<*> parseWsReadCookie
<*> parseStringifyNum
<*> parseDangerousBooleanCollapse
<*> parseEnabledAPIs
<*> parseMxRefetchInt
<*> parseMxBatchSize
<*> parseEnableAllowlist
<*> parseEnabledLogs
<*> parseLogLevel
<* parsePlanCacheSize -- parsed (for backwards compatibility reasons) but ignored
<*> parseGraphqlDevMode
<*> parseGraphqlAdminInternalErrors
<*> parseGraphqlEventsHttpPoolSize
<*> parseGraphqlEventsFetchInterval
<*> parseGraphqlAsyncActionsFetchInterval
<*> parseLogHeadersFromEnv
<*> parseEnableRemoteSchemaPerms
<*> parseWebSocketCompression
<*> parseWebSocketKeepAlive
<*> parseInferFunctionPerms
<*> parseEnableMaintenanceMode
<*> parseSchemaPollInterval
<*> parseExperimentalFeatures
<*> parseEventsFetchBatchSize
<*> parseGracefulShutdownTimeout
<*> parseWebSocketConnectionInitTimeout
-- | This implements the mapping between application versions
-- and catalog schema versions.
downgradeShortcuts :: [(String, String)]
downgradeShortcuts =
$( do
let s = $(makeRelativeToProject "src-rsr/catalog_versions.txt" >>= embedStringFile)
parseVersions = map (parseVersion . words) . lines
parseVersion [tag, version] = (tag, version)
parseVersion other = error ("unrecognized tag/catalog mapping " ++ show other)
TH.lift (parseVersions s)
)
downgradeOptionsParser :: Parser DowngradeOptions
downgradeOptionsParser =
DowngradeOptions
<$> choice
( strOption
( long "to-catalog-version"
<> metavar "<VERSION>"
<> help "The target catalog schema version (e.g. 31)"
) :
map (uncurry shortcut) downgradeShortcuts
)
<*> switch
( long "dryRun"
<> help "Don't run any migrations, just print out the SQL."
)
where
shortcut v catalogVersion =
flag'
(DataString.fromString catalogVersion)
( long ("to-" <> v)
<> help ("Downgrade to graphql-engine version " <> v <> " (equivalent to --to-catalog-version " <> catalogVersion <> ")")
)
webSocketCompressionEnv :: (String, String)
webSocketCompressionEnv =
( "HASURA_GRAPHQL_CONNECTION_COMPRESSION",
"Enable WebSocket permessage-deflate compression (default: false)"
)
parseWebSocketCompression :: Parser Bool
parseWebSocketCompression =
switch
( long "websocket-compression"
<> help (snd webSocketCompressionEnv)
)
-- NOTE: this is purely used by Apollo-Subscription-Transport-WS
webSocketKeepAliveEnv :: (String, String)
webSocketKeepAliveEnv =
( "HASURA_GRAPHQL_WEBSOCKET_KEEPALIVE",
"Control websocket keep-alive timeout (default 5 seconds)"
)
parseWebSocketKeepAlive :: Parser (Maybe Int)
parseWebSocketKeepAlive =
optional $
option
(eitherReader readEither)
( long "websocket-keepalive"
<> help (snd webSocketKeepAliveEnv)
)
-- NOTE: this is purely used by GraphQL-WS
webSocketConnectionInitTimeoutEnv :: (String, String)
webSocketConnectionInitTimeoutEnv =
( "HASURA_GRAPHQL_WEBSOCKET_CONNECTION_INIT_TIMEOUT", -- FIXME?: maybe a better name
"Control websocket connection_init timeout (default 3 seconds)"
)
parseWebSocketConnectionInitTimeout :: Parser (Maybe Int)
parseWebSocketConnectionInitTimeout =
optional $
option
(eitherReader readEither)
( long "websocket-connection-init-timeout"
<> help (snd webSocketConnectionInitTimeoutEnv)
)