2020-05-27 18:02:58 +03:00
|
|
|
|
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
2019-11-20 21:21:30 +03:00
|
|
|
|
{-# LANGUAGE UndecidableInstances #-}
|
|
|
|
|
|
2019-04-17 12:48:41 +03:00
|
|
|
|
-- A module for postgres execution related types and operations
|
|
|
|
|
|
2020-10-27 16:53:49 +03:00
|
|
|
|
module Hasura.Backends.Postgres.Connection
|
2019-04-17 12:48:41 +03:00
|
|
|
|
( MonadTx(..)
|
2021-08-02 22:13:06 +03:00
|
|
|
|
, LazyTxT(..)
|
2019-04-17 12:48:41 +03:00
|
|
|
|
|
|
|
|
|
, runLazyTx
|
2020-06-16 20:44:59 +03:00
|
|
|
|
, runQueryTx
|
2021-09-01 20:56:46 +03:00
|
|
|
|
, runQueryTxWithCtx
|
2019-04-17 12:48:41 +03:00
|
|
|
|
, withUserInfo
|
2020-07-23 23:39:26 +03:00
|
|
|
|
, withTraceContext
|
2021-07-27 11:05:33 +03:00
|
|
|
|
, setHeadersTx
|
|
|
|
|
, setTraceContextInTx
|
2019-11-20 09:47:06 +03:00
|
|
|
|
, sessionInfoJsonExp
|
2019-04-17 12:48:41 +03:00
|
|
|
|
|
2020-10-30 14:00:39 +03:00
|
|
|
|
, doesSchemaExist
|
|
|
|
|
, doesTableExist
|
2020-12-28 15:56:00 +03:00
|
|
|
|
, enablePgcryptoExtension
|
2021-01-07 12:04:22 +03:00
|
|
|
|
, dropHdbCatalogSchema
|
2020-12-28 15:56:00 +03:00
|
|
|
|
|
2021-02-14 09:07:52 +03:00
|
|
|
|
, PostgresPoolSettings(..)
|
|
|
|
|
, PostgresSourceConnInfo(..)
|
|
|
|
|
, PostgresConnConfiguration(..)
|
2021-05-21 04:49:50 +03:00
|
|
|
|
, PGClientCerts(..)
|
|
|
|
|
, CertVar(..)
|
|
|
|
|
, CertData(..)
|
|
|
|
|
, SSLMode(..)
|
2021-03-16 18:27:51 +03:00
|
|
|
|
, DefaultPostgresPoolSettings(..)
|
|
|
|
|
, getDefaultPGPoolSettingIfNotExists
|
|
|
|
|
, defaultPostgresPoolSettings
|
|
|
|
|
, setPostgresPoolSettings
|
2021-04-13 03:15:37 +03:00
|
|
|
|
, pccConnectionInfo
|
|
|
|
|
, pccReadReplicas
|
|
|
|
|
, psciDatabaseUrl
|
|
|
|
|
, psciPoolSettings
|
2021-04-14 20:51:02 +03:00
|
|
|
|
, psciUsePreparedStatements
|
2021-04-28 19:49:23 +03:00
|
|
|
|
, psciIsolationLevel
|
2021-05-21 04:49:50 +03:00
|
|
|
|
, psciSslConfiguration
|
2020-12-28 15:56:00 +03:00
|
|
|
|
, module ET
|
2019-04-17 12:48:41 +03:00
|
|
|
|
) where
|
|
|
|
|
|
2020-10-27 16:53:49 +03:00
|
|
|
|
import Hasura.Prelude
|
|
|
|
|
|
2021-04-28 19:49:23 +03:00
|
|
|
|
import qualified Data.Text as T
|
2020-12-28 15:56:00 +03:00
|
|
|
|
import qualified Database.PG.Query as Q
|
|
|
|
|
import qualified Database.PG.Query.Connection as Q
|
2020-10-27 16:53:49 +03:00
|
|
|
|
|
2021-04-13 03:15:37 +03:00
|
|
|
|
import Control.Lens (makeLenses)
|
2020-12-28 15:56:00 +03:00
|
|
|
|
import Control.Monad.Morph (hoist)
|
|
|
|
|
import Control.Monad.Trans.Control (MonadBaseControl (..))
|
2019-11-20 21:21:30 +03:00
|
|
|
|
import Control.Monad.Unique
|
2019-07-22 15:47:13 +03:00
|
|
|
|
import Control.Monad.Validate
|
2021-02-14 09:07:52 +03:00
|
|
|
|
import Data.Aeson
|
2021-05-21 04:49:50 +03:00
|
|
|
|
import Data.Aeson.Casing (aesonDrop)
|
2021-02-14 09:07:52 +03:00
|
|
|
|
import Data.Aeson.Extended
|
|
|
|
|
import Data.Aeson.TH
|
2021-05-21 04:49:50 +03:00
|
|
|
|
import Data.Bifoldable
|
|
|
|
|
import Data.Bifunctor
|
|
|
|
|
import Data.Bitraversable
|
|
|
|
|
import Data.Char (toLower)
|
2021-06-15 18:05:41 +03:00
|
|
|
|
import Data.Hashable.Time ()
|
2021-05-21 04:49:50 +03:00
|
|
|
|
import Data.Semigroup (Max (..))
|
|
|
|
|
import Data.Text (unpack)
|
2021-04-28 19:49:23 +03:00
|
|
|
|
import Data.Time
|
2021-05-21 05:46:58 +03:00
|
|
|
|
import Test.QuickCheck.Instances.Semigroup ()
|
2021-04-28 19:49:23 +03:00
|
|
|
|
import Test.QuickCheck.Instances.Time ()
|
2019-07-22 15:47:13 +03:00
|
|
|
|
|
2020-12-28 15:56:00 +03:00
|
|
|
|
import qualified Hasura.Backends.Postgres.SQL.DML as S
|
|
|
|
|
import qualified Hasura.Tracing as Tracing
|
2019-04-17 12:48:41 +03:00
|
|
|
|
|
2020-12-28 15:56:00 +03:00
|
|
|
|
import Hasura.Backends.Postgres.Execute.Types as ET
|
2020-10-30 14:00:39 +03:00
|
|
|
|
import Hasura.Backends.Postgres.SQL.Types
|
2021-05-11 18:18:31 +03:00
|
|
|
|
import Hasura.Base.Error
|
2021-06-15 18:05:41 +03:00
|
|
|
|
import Hasura.Base.Instances ()
|
2021-02-14 09:07:52 +03:00
|
|
|
|
import Hasura.Incremental (Cacheable (..))
|
2021-05-21 04:49:50 +03:00
|
|
|
|
import Hasura.RQL.Types.Common (UrlConf (..))
|
2020-12-14 07:30:19 +03:00
|
|
|
|
import Hasura.SQL.Types
|
2021-04-28 19:49:23 +03:00
|
|
|
|
import Hasura.Server.Utils (parseConnLifeTime, readIsoLevel)
|
2021-01-09 02:09:15 +03:00
|
|
|
|
import Hasura.Session
|
2019-04-17 12:48:41 +03:00
|
|
|
|
|
2021-06-15 18:05:41 +03:00
|
|
|
|
|
2019-04-17 12:48:41 +03:00
|
|
|
|
class (MonadError QErr m) => MonadTx m where
|
|
|
|
|
liftTx :: Q.TxE QErr a -> m a
|
|
|
|
|
|
|
|
|
|
instance (MonadTx m) => MonadTx (StateT s m) where
|
|
|
|
|
liftTx = lift . liftTx
|
|
|
|
|
instance (MonadTx m) => MonadTx (ReaderT s m) where
|
|
|
|
|
liftTx = lift . liftTx
|
2019-11-20 21:21:30 +03:00
|
|
|
|
instance (Monoid w, MonadTx m) => MonadTx (WriterT w m) where
|
|
|
|
|
liftTx = lift . liftTx
|
2019-07-22 15:47:13 +03:00
|
|
|
|
instance (MonadTx m) => MonadTx (ValidateT e m) where
|
|
|
|
|
liftTx = lift . liftTx
|
2020-07-15 13:40:48 +03:00
|
|
|
|
instance (MonadTx m) => MonadTx (Tracing.TraceT m) where
|
|
|
|
|
liftTx = lift . liftTx
|
2021-08-02 22:13:06 +03:00
|
|
|
|
instance (MonadIO m) => MonadTx (Q.TxET QErr m) where
|
|
|
|
|
liftTx = hoist liftIO
|
2019-04-17 12:48:41 +03:00
|
|
|
|
|
2021-08-02 22:13:06 +03:00
|
|
|
|
-- | This type *used to be* like 'Q.TxE', but deferred acquiring a Postgres
|
|
|
|
|
-- connection until the first execution of 'liftTx'. If no call to 'liftTx' is
|
|
|
|
|
-- ever reached (i.e. a successful result is returned or an error is raised
|
|
|
|
|
-- before ever executing a query), no connection was ever acquired.
|
2019-08-28 15:19:21 +03:00
|
|
|
|
--
|
2021-08-02 22:13:06 +03:00
|
|
|
|
-- This was useful for certain code paths that only conditionally need database
|
2020-06-16 20:44:59 +03:00
|
|
|
|
-- access. For example, although most queries will eventually hit Postgres,
|
|
|
|
|
-- introspection queries or queries that exclusively use remote schemas never
|
2021-08-02 22:13:06 +03:00
|
|
|
|
-- will; using 'LazyTxT e m' keeps those branches from unnecessarily allocating
|
|
|
|
|
-- a connection.
|
|
|
|
|
--
|
|
|
|
|
-- However introspection queries and remote queries now never end up producing a
|
|
|
|
|
-- 'LazyTxT' action, and hence the laziness adds no benefit, so that we could
|
|
|
|
|
-- simplify this type, its name being a mere reminder of a past design of
|
|
|
|
|
-- graphql-engine.
|
|
|
|
|
--
|
|
|
|
|
-- It may be worthwhile in the future to simply replace this type with Q.TxET
|
|
|
|
|
-- entirely.
|
|
|
|
|
newtype LazyTxT e m a = LazyTxT {unLazyTxT :: Q.TxET e m a}
|
|
|
|
|
deriving (Functor, Applicative, Monad, MonadError e, MonadIO, MonadTrans)
|
2019-04-17 12:48:41 +03:00
|
|
|
|
|
|
|
|
|
runLazyTx
|
2020-10-30 14:00:39 +03:00
|
|
|
|
:: ( MonadIO m
|
|
|
|
|
, MonadBaseControl IO m
|
|
|
|
|
)
|
2019-11-26 15:14:21 +03:00
|
|
|
|
=> PGExecCtx
|
2019-11-15 03:20:18 +03:00
|
|
|
|
-> Q.TxAccess
|
2020-10-30 14:00:39 +03:00
|
|
|
|
-> LazyTxT QErr m a -> ExceptT QErr m a
|
2021-08-02 22:13:06 +03:00
|
|
|
|
runLazyTx pgExecCtx = \case
|
|
|
|
|
Q.ReadOnly -> _pecRunReadOnly pgExecCtx . unLazyTxT
|
|
|
|
|
Q.ReadWrite -> _pecRunReadWrite pgExecCtx . unLazyTxT
|
2020-06-16 20:44:59 +03:00
|
|
|
|
|
|
|
|
|
-- | This runs the given set of statements (Tx) without wrapping them in BEGIN
|
|
|
|
|
-- and COMMIT. This should only be used for running a single statement query!
|
|
|
|
|
runQueryTx
|
2021-08-02 22:13:06 +03:00
|
|
|
|
:: (MonadIO m, MonadError QErr m) => PGExecCtx -> LazyTxT QErr IO a -> m a
|
|
|
|
|
runQueryTx pgExecCtx ltx =
|
|
|
|
|
liftEither =<< liftIO (runExceptT $ _pecRunReadNoTx pgExecCtx (unLazyTxT ltx))
|
2019-04-17 12:48:41 +03:00
|
|
|
|
|
2021-09-01 20:56:46 +03:00
|
|
|
|
-- NOTE: Same warning as 'runQueryTx' applies here.
|
|
|
|
|
-- This variant of 'runQueryTx' allows passing the `userInfo` context and `tracecontext`.
|
|
|
|
|
runQueryTxWithCtx
|
|
|
|
|
:: (MonadIO m, MonadError QErr m)
|
|
|
|
|
=> UserInfo
|
|
|
|
|
-> Tracing.TraceContext
|
|
|
|
|
-> PGExecCtx
|
|
|
|
|
-> LazyTxT QErr IO a
|
|
|
|
|
-> m a
|
|
|
|
|
runQueryTxWithCtx userInfo traceCtx pgExecCtx =
|
|
|
|
|
runQueryTx pgExecCtx . withUserInfo userInfo . withTraceContext traceCtx
|
|
|
|
|
|
2020-10-30 14:00:39 +03:00
|
|
|
|
setHeadersTx :: (MonadIO m) => SessionVariables -> Q.TxET QErr m ()
|
2020-07-14 22:00:58 +03:00
|
|
|
|
setHeadersTx session = do
|
2019-04-17 12:48:41 +03:00
|
|
|
|
Q.unitQE defaultTxErrorHandler setSess () False
|
|
|
|
|
where
|
|
|
|
|
setSess = Q.fromText $
|
2020-04-24 12:10:53 +03:00
|
|
|
|
"SET LOCAL \"hasura.user\" = " <> toSQLTxt (sessionInfoJsonExp session)
|
2019-11-20 09:47:06 +03:00
|
|
|
|
|
2020-04-24 12:10:53 +03:00
|
|
|
|
sessionInfoJsonExp :: SessionVariables -> S.SQLExp
|
2021-02-14 09:07:52 +03:00
|
|
|
|
sessionInfoJsonExp = S.SELit . encodeToStrictText
|
2019-04-17 12:48:41 +03:00
|
|
|
|
|
2020-10-30 14:00:39 +03:00
|
|
|
|
withUserInfo :: (MonadIO m) => UserInfo -> LazyTxT QErr m a -> LazyTxT QErr m a
|
2021-08-17 13:21:56 +03:00
|
|
|
|
withUserInfo uInfo ltx = LazyTxT (setHeadersTx $ _uiSession uInfo) >> ltx
|
2019-04-17 12:48:41 +03:00
|
|
|
|
|
2021-07-27 11:05:33 +03:00
|
|
|
|
setTraceContextInTx :: (MonadIO m) => Tracing.TraceContext -> Q.TxET QErr m ()
|
2021-08-17 13:21:56 +03:00
|
|
|
|
setTraceContextInTx traceCtx = Q.unitQE defaultTxErrorHandler sql () False
|
|
|
|
|
where
|
|
|
|
|
sql = Q.fromText $ "SET LOCAL \"hasura.tracecontext\" = " <>
|
2021-07-27 11:05:33 +03:00
|
|
|
|
toSQLTxt (S.SELit . encodeToStrictText . Tracing.injectEventContext $ traceCtx)
|
|
|
|
|
|
2020-07-23 23:39:26 +03:00
|
|
|
|
-- | Inject the trace context as a transaction-local variable,
|
|
|
|
|
-- so that it can be picked up by any triggers (including event triggers).
|
|
|
|
|
withTraceContext
|
2020-10-30 14:00:39 +03:00
|
|
|
|
:: (MonadIO m)
|
|
|
|
|
=> Tracing.TraceContext
|
|
|
|
|
-> LazyTxT QErr m a
|
|
|
|
|
-> LazyTxT QErr m a
|
2021-08-17 13:21:56 +03:00
|
|
|
|
withTraceContext ctx ltx = LazyTxT (setTraceContextInTx ctx) >> ltx
|
2019-04-17 12:48:41 +03:00
|
|
|
|
|
2021-08-02 22:13:06 +03:00
|
|
|
|
deriving instance Tracing.MonadTrace m => Tracing.MonadTrace (Q.TxET e m)
|
|
|
|
|
deriving instance Tracing.MonadTrace m => Tracing.MonadTrace (LazyTxT e m)
|
2020-10-30 14:00:39 +03:00
|
|
|
|
|
2021-08-02 22:13:06 +03:00
|
|
|
|
deriving instance (MonadIO m) => MonadTx (LazyTxT QErr m)
|
2019-11-20 21:21:30 +03:00
|
|
|
|
|
2021-08-02 22:13:06 +03:00
|
|
|
|
deriving instance (MonadBase IO m) => MonadBase IO (LazyTxT e m)
|
2019-11-20 21:21:30 +03:00
|
|
|
|
|
2021-08-02 22:13:06 +03:00
|
|
|
|
deriving instance (MonadBaseControl IO m) => MonadBaseControl IO (LazyTxT e m)
|
2019-11-20 21:21:30 +03:00
|
|
|
|
|
2020-10-30 14:00:39 +03:00
|
|
|
|
instance (MonadIO m) => MonadUnique (LazyTxT e m) where
|
2019-11-20 21:21:30 +03:00
|
|
|
|
newUnique = liftIO newUnique
|
2020-10-30 14:00:39 +03:00
|
|
|
|
|
|
|
|
|
doesSchemaExist :: MonadTx m => SchemaName -> m Bool
|
|
|
|
|
doesSchemaExist schemaName =
|
|
|
|
|
liftTx $ (runIdentity . Q.getRow) <$> Q.withQE defaultTxErrorHandler [Q.sql|
|
|
|
|
|
SELECT EXISTS
|
|
|
|
|
( SELECT 1 FROM information_schema.schemata
|
|
|
|
|
WHERE schema_name = $1
|
|
|
|
|
) |] (Identity schemaName) False
|
|
|
|
|
|
|
|
|
|
doesTableExist :: MonadTx m => SchemaName -> TableName -> m Bool
|
|
|
|
|
doesTableExist schemaName tableName =
|
|
|
|
|
liftTx $ (runIdentity . Q.getRow) <$> Q.withQE defaultTxErrorHandler [Q.sql|
|
|
|
|
|
SELECT EXISTS
|
|
|
|
|
( SELECT 1 FROM pg_tables
|
|
|
|
|
WHERE schemaname = $1 AND tablename = $2
|
|
|
|
|
) |] (schemaName, tableName) False
|
|
|
|
|
|
|
|
|
|
isExtensionAvailable :: MonadTx m => Text -> m Bool
|
|
|
|
|
isExtensionAvailable extensionName =
|
|
|
|
|
liftTx $ (runIdentity . Q.getRow) <$> Q.withQE defaultTxErrorHandler [Q.sql|
|
|
|
|
|
SELECT EXISTS
|
|
|
|
|
( SELECT 1 FROM pg_catalog.pg_available_extensions
|
|
|
|
|
WHERE name = $1
|
|
|
|
|
) |] (Identity extensionName) False
|
2020-12-28 15:56:00 +03:00
|
|
|
|
|
|
|
|
|
enablePgcryptoExtension :: forall m. MonadTx m => m ()
|
|
|
|
|
enablePgcryptoExtension = do
|
|
|
|
|
pgcryptoAvailable <- isExtensionAvailable "pgcrypto"
|
|
|
|
|
if pgcryptoAvailable then createPgcryptoExtension
|
|
|
|
|
else throw400 Unexpected $
|
|
|
|
|
"pgcrypto extension is required, but could not find the extension in the "
|
|
|
|
|
<> "PostgreSQL server. Please make sure this extension is available."
|
|
|
|
|
where
|
|
|
|
|
createPgcryptoExtension :: m ()
|
|
|
|
|
createPgcryptoExtension =
|
|
|
|
|
liftTx $ Q.unitQE needsPGCryptoError
|
|
|
|
|
"CREATE EXTENSION IF NOT EXISTS pgcrypto SCHEMA public" () False
|
|
|
|
|
where
|
|
|
|
|
needsPGCryptoError e@(Q.PGTxErr _ _ _ err) =
|
|
|
|
|
case err of
|
|
|
|
|
Q.PGIUnexpected _ -> requiredError
|
|
|
|
|
Q.PGIStatement pgErr -> case Q.edStatusCode pgErr of
|
|
|
|
|
Just "42501" -> err500 PostgresError permissionsMessage
|
|
|
|
|
_ -> requiredError
|
|
|
|
|
where
|
|
|
|
|
requiredError =
|
2021-02-14 09:07:52 +03:00
|
|
|
|
(err500 PostgresError requiredMessage) { qeInternal = Just $ toJSON e }
|
2020-12-28 15:56:00 +03:00
|
|
|
|
requiredMessage =
|
|
|
|
|
"pgcrypto extension is required, but it could not be created;"
|
|
|
|
|
<> " encountered unknown postgres error"
|
|
|
|
|
permissionsMessage =
|
|
|
|
|
"pgcrypto extension is required, but the current user doesn’t have permission to"
|
|
|
|
|
<> " create it. Please grant superuser permission, or setup the initial schema via"
|
2021-03-01 21:50:24 +03:00
|
|
|
|
<> " https://hasura.io/docs/latest/graphql/core/deployment/postgres-permissions.html"
|
2021-01-07 12:04:22 +03:00
|
|
|
|
|
|
|
|
|
dropHdbCatalogSchema :: (MonadTx m) => m ()
|
|
|
|
|
dropHdbCatalogSchema = liftTx $ Q.catchE defaultTxErrorHandler $
|
|
|
|
|
-- This is where
|
|
|
|
|
-- 1. Metadata storage:- Metadata and its stateful information stored
|
|
|
|
|
-- 2. Postgres source:- Table event trigger related stuff & insert permission check function stored
|
|
|
|
|
Q.unitQ "DROP SCHEMA IF EXISTS hdb_catalog CASCADE" () False
|
2021-02-14 09:07:52 +03:00
|
|
|
|
|
|
|
|
|
data PostgresPoolSettings
|
|
|
|
|
= PostgresPoolSettings
|
2021-04-28 19:49:23 +03:00
|
|
|
|
{ _ppsMaxConnections :: !(Maybe Int)
|
|
|
|
|
, _ppsIdleTimeout :: !(Maybe Int)
|
|
|
|
|
, _ppsRetries :: !(Maybe Int)
|
|
|
|
|
, _ppsPoolTimeout :: !(Maybe NominalDiffTime)
|
|
|
|
|
, _ppsConnectionLifetime :: !(Maybe NominalDiffTime)
|
2021-02-14 09:07:52 +03:00
|
|
|
|
} deriving (Show, Eq, Generic)
|
|
|
|
|
instance Cacheable PostgresPoolSettings
|
|
|
|
|
instance Hashable PostgresPoolSettings
|
|
|
|
|
instance NFData PostgresPoolSettings
|
2021-03-16 18:27:51 +03:00
|
|
|
|
$(deriveToJSON hasuraJSON{omitNothingFields = True} ''PostgresPoolSettings)
|
2021-02-14 09:07:52 +03:00
|
|
|
|
|
|
|
|
|
instance FromJSON PostgresPoolSettings where
|
2021-04-28 19:49:23 +03:00
|
|
|
|
parseJSON = withObject "PostgresPoolSettings" $ \o ->
|
2021-02-14 09:07:52 +03:00
|
|
|
|
PostgresPoolSettings
|
2021-03-16 18:27:51 +03:00
|
|
|
|
<$> o .:? "max_connections"
|
|
|
|
|
<*> o .:? "idle_timeout"
|
|
|
|
|
<*> o .:? "retries"
|
2021-04-28 19:49:23 +03:00
|
|
|
|
<*> o .:? "pool_timeout"
|
|
|
|
|
<*> ((o .:? "connection_lifetime") <&> parseConnLifeTime)
|
2021-02-14 09:07:52 +03:00
|
|
|
|
|
2021-03-16 18:27:51 +03:00
|
|
|
|
data DefaultPostgresPoolSettings =
|
|
|
|
|
DefaultPostgresPoolSettings
|
2021-04-28 19:49:23 +03:00
|
|
|
|
{ _dppsMaxConnections :: !Int
|
|
|
|
|
, _dppsIdleTimeout :: !Int
|
|
|
|
|
, _dppsRetries :: !Int
|
|
|
|
|
, _dppsConnectionLifetime :: !(Maybe NominalDiffTime)
|
2021-03-16 18:27:51 +03:00
|
|
|
|
} deriving (Show, Eq)
|
|
|
|
|
|
|
|
|
|
defaultPostgresPoolSettings :: DefaultPostgresPoolSettings
|
2021-04-28 19:49:23 +03:00
|
|
|
|
defaultPostgresPoolSettings = DefaultPostgresPoolSettings 50 180 1 (Just 600)
|
2021-03-16 18:27:51 +03:00
|
|
|
|
|
|
|
|
|
-- Use this when you want to set only few of the PG Pool settings.
|
|
|
|
|
-- The values which are not set will use the default values.
|
|
|
|
|
setPostgresPoolSettings :: PostgresPoolSettings
|
|
|
|
|
setPostgresPoolSettings =
|
2021-02-14 09:07:52 +03:00
|
|
|
|
PostgresPoolSettings
|
2021-04-28 19:49:23 +03:00
|
|
|
|
{ _ppsMaxConnections = (Just $ _dppsMaxConnections defaultPostgresPoolSettings)
|
|
|
|
|
, _ppsIdleTimeout = (Just $ _dppsIdleTimeout defaultPostgresPoolSettings)
|
|
|
|
|
, _ppsRetries = (Just $ _dppsRetries defaultPostgresPoolSettings)
|
|
|
|
|
, _ppsPoolTimeout = Nothing -- @Nothing@ is the default value of the pool timeout
|
|
|
|
|
, _ppsConnectionLifetime = _dppsConnectionLifetime defaultPostgresPoolSettings
|
2021-02-14 09:07:52 +03:00
|
|
|
|
}
|
|
|
|
|
|
2021-03-16 18:27:51 +03:00
|
|
|
|
-- PG Pool Settings are not given by the user, set defaults
|
|
|
|
|
getDefaultPGPoolSettingIfNotExists :: Maybe PostgresPoolSettings -> DefaultPostgresPoolSettings -> (Int, Int, Int)
|
|
|
|
|
getDefaultPGPoolSettingIfNotExists connSettings defaultPgPoolSettings =
|
|
|
|
|
case connSettings of
|
|
|
|
|
-- Atleast one of the postgres pool settings is set, then set default values to other settings
|
2021-04-28 19:49:23 +03:00
|
|
|
|
Just connSettings' ->
|
|
|
|
|
(maxConnections connSettings', idleTimeout connSettings', retries connSettings')
|
2021-03-16 18:27:51 +03:00
|
|
|
|
-- No PG Pool settings provided by user, set default values for all
|
|
|
|
|
Nothing -> (defMaxConnections, defIdleTimeout, defRetries)
|
|
|
|
|
|
|
|
|
|
where
|
|
|
|
|
defMaxConnections = _dppsMaxConnections defaultPgPoolSettings
|
|
|
|
|
defIdleTimeout = _dppsIdleTimeout defaultPgPoolSettings
|
|
|
|
|
defRetries = _dppsRetries defaultPgPoolSettings
|
|
|
|
|
|
|
|
|
|
maxConnections = fromMaybe defMaxConnections . _ppsMaxConnections
|
|
|
|
|
idleTimeout = fromMaybe defIdleTimeout . _ppsIdleTimeout
|
|
|
|
|
retries = fromMaybe defRetries . _ppsRetries
|
|
|
|
|
|
2021-05-21 04:49:50 +03:00
|
|
|
|
data SSLMode =
|
|
|
|
|
Disable
|
|
|
|
|
| Allow
|
|
|
|
|
| Prefer
|
|
|
|
|
| Require
|
|
|
|
|
| VerifyCA
|
|
|
|
|
| VerifyFull
|
|
|
|
|
deriving (Eq, Ord, Generic, Enum, Bounded)
|
|
|
|
|
instance Cacheable SSLMode
|
|
|
|
|
instance Hashable SSLMode
|
|
|
|
|
instance NFData SSLMode
|
|
|
|
|
|
|
|
|
|
instance Show SSLMode where
|
|
|
|
|
show = \case
|
|
|
|
|
Disable -> "disable"
|
|
|
|
|
Allow -> "allow"
|
|
|
|
|
Prefer -> "prefer"
|
|
|
|
|
Require -> "require"
|
|
|
|
|
VerifyCA -> "verify-ca"
|
|
|
|
|
VerifyFull -> "verify-full"
|
|
|
|
|
|
|
|
|
|
deriving via (Max SSLMode) instance Semigroup SSLMode
|
|
|
|
|
|
|
|
|
|
instance FromJSON SSLMode where
|
|
|
|
|
parseJSON = withText "SSLMode" $ \case
|
|
|
|
|
"disable" -> pure Disable
|
|
|
|
|
"allow" -> pure Allow
|
|
|
|
|
"prefer" -> pure Prefer
|
|
|
|
|
"require" -> pure Require
|
|
|
|
|
"verify-ca" -> pure VerifyCA
|
|
|
|
|
"verify-full" -> pure VerifyFull
|
|
|
|
|
err -> fail $ "Invalid SSL Mode " <> unpack err
|
|
|
|
|
|
|
|
|
|
data CertVar
|
|
|
|
|
= CertVar String
|
|
|
|
|
| CertLiteral String
|
|
|
|
|
deriving (Show, Eq, Generic)
|
|
|
|
|
|
|
|
|
|
instance Cacheable CertVar
|
|
|
|
|
instance Hashable CertVar
|
|
|
|
|
instance NFData CertVar
|
|
|
|
|
|
|
|
|
|
instance ToJSON CertVar where
|
|
|
|
|
toJSON (CertVar var) = (object ["from_env" .= var])
|
|
|
|
|
toJSON (CertLiteral var) = String (T.pack var)
|
|
|
|
|
|
|
|
|
|
instance FromJSON CertVar where
|
|
|
|
|
parseJSON (String s) = pure (CertLiteral (T.unpack s))
|
|
|
|
|
parseJSON x = withObject "CertVar" (\o -> CertVar <$> o .: "from_env") x
|
|
|
|
|
|
|
|
|
|
newtype CertData = CertData { unCert :: Text }
|
|
|
|
|
deriving (Show, Eq, Generic)
|
|
|
|
|
|
|
|
|
|
instance ToJSON CertData where
|
|
|
|
|
toJSON = String . unCert
|
|
|
|
|
|
|
|
|
|
data PGClientCerts p a = PGClientCerts
|
|
|
|
|
{ pgcSslCert :: a
|
|
|
|
|
, pgcSslKey :: a
|
|
|
|
|
, pgcSslRootCert :: a
|
|
|
|
|
, pgcSslMode :: SSLMode
|
|
|
|
|
, pgcSslPassword :: Maybe p
|
|
|
|
|
} deriving (Show, Eq, Generic, Functor, Foldable, Traversable)
|
|
|
|
|
$(deriveFromJSON (aesonDrop 3 (fmap toLower)) ''PGClientCerts)
|
|
|
|
|
$(deriveToJSON (aesonDrop 3 (fmap toLower)) ''PGClientCerts)
|
|
|
|
|
|
|
|
|
|
instance Bifunctor PGClientCerts where
|
|
|
|
|
bimap f g pgCerts = g <$> pgCerts { pgcSslPassword = f <$> (pgcSslPassword pgCerts)}
|
|
|
|
|
|
|
|
|
|
instance Bifoldable PGClientCerts where
|
|
|
|
|
bifoldMap f g PGClientCerts{..} =
|
|
|
|
|
fold $ fmap g [pgcSslCert, pgcSslKey, pgcSslRootCert] <> maybe [] (pure . f) pgcSslPassword
|
|
|
|
|
|
|
|
|
|
instance Bitraversable PGClientCerts where
|
|
|
|
|
bitraverse f g PGClientCerts{..} =
|
|
|
|
|
PGClientCerts <$> g pgcSslCert <*> g pgcSslKey <*> g pgcSslRootCert <*> pure pgcSslMode <*> traverse f pgcSslPassword
|
|
|
|
|
|
|
|
|
|
instance (Cacheable p, Cacheable a) => Cacheable (PGClientCerts p a)
|
|
|
|
|
instance (Hashable p, Hashable a) => Hashable (PGClientCerts p a)
|
|
|
|
|
instance (NFData p, NFData a) => NFData (PGClientCerts p a)
|
|
|
|
|
|
|
|
|
|
instance ToJSON SSLMode where
|
|
|
|
|
toJSON = String . tshow
|
|
|
|
|
|
2021-04-28 19:49:23 +03:00
|
|
|
|
deriving instance Generic Q.TxIsolation
|
|
|
|
|
instance Cacheable Q.TxIsolation
|
|
|
|
|
instance NFData Q.TxIsolation
|
|
|
|
|
instance Hashable Q.TxIsolation
|
|
|
|
|
|
|
|
|
|
instance FromJSON Q.TxIsolation where
|
|
|
|
|
parseJSON = withText "Q.TxIsolation" $ \t ->
|
|
|
|
|
onLeft (readIsoLevel $ T.unpack t) fail
|
|
|
|
|
|
|
|
|
|
instance ToJSON Q.TxIsolation where
|
|
|
|
|
toJSON Q.ReadCommitted = "read-committed"
|
|
|
|
|
toJSON Q.RepeatableRead = "repeatable-read"
|
|
|
|
|
toJSON Q.Serializable = "serializable"
|
|
|
|
|
|
2021-02-14 09:07:52 +03:00
|
|
|
|
data PostgresSourceConnInfo
|
|
|
|
|
= PostgresSourceConnInfo
|
2021-04-14 20:51:02 +03:00
|
|
|
|
{ _psciDatabaseUrl :: !UrlConf
|
|
|
|
|
, _psciPoolSettings :: !(Maybe PostgresPoolSettings)
|
|
|
|
|
, _psciUsePreparedStatements :: !Bool
|
2021-04-28 19:49:23 +03:00
|
|
|
|
, _psciIsolationLevel :: !Q.TxIsolation
|
2021-05-21 04:49:50 +03:00
|
|
|
|
, _psciSslConfiguration :: !(Maybe (PGClientCerts CertVar CertVar))
|
2021-02-14 09:07:52 +03:00
|
|
|
|
} deriving (Show, Eq, Generic)
|
|
|
|
|
instance Cacheable PostgresSourceConnInfo
|
|
|
|
|
instance Hashable PostgresSourceConnInfo
|
|
|
|
|
instance NFData PostgresSourceConnInfo
|
2021-03-16 18:27:51 +03:00
|
|
|
|
$(deriveToJSON hasuraJSON{omitNothingFields = True} ''PostgresSourceConnInfo)
|
2021-04-13 03:15:37 +03:00
|
|
|
|
$(makeLenses ''PostgresSourceConnInfo)
|
|
|
|
|
|
2021-02-14 09:07:52 +03:00
|
|
|
|
instance FromJSON PostgresSourceConnInfo where
|
2021-04-28 19:49:23 +03:00
|
|
|
|
parseJSON = withObject "PostgresSourceConnInfo" $ \o ->
|
2021-02-14 09:07:52 +03:00
|
|
|
|
PostgresSourceConnInfo
|
|
|
|
|
<$> o .: "database_url"
|
2021-03-16 18:27:51 +03:00
|
|
|
|
<*> o .:? "pool_settings"
|
2021-04-14 20:51:02 +03:00
|
|
|
|
<*> o .:? "use_prepared_statements" .!= False -- By default preparing statements is OFF for postgres source
|
2021-04-28 19:49:23 +03:00
|
|
|
|
<*> o .:? "isolation_level" .!= Q.ReadCommitted
|
2021-05-21 04:49:50 +03:00
|
|
|
|
<*> o .:? "ssl_configuration"
|
2021-02-14 09:07:52 +03:00
|
|
|
|
|
|
|
|
|
data PostgresConnConfiguration
|
|
|
|
|
= PostgresConnConfiguration
|
|
|
|
|
{ _pccConnectionInfo :: !PostgresSourceConnInfo
|
|
|
|
|
, _pccReadReplicas :: !(Maybe (NonEmpty PostgresSourceConnInfo))
|
|
|
|
|
} deriving (Show, Eq, Generic)
|
|
|
|
|
instance Cacheable PostgresConnConfiguration
|
|
|
|
|
instance Hashable PostgresConnConfiguration
|
|
|
|
|
instance NFData PostgresConnConfiguration
|
|
|
|
|
$(deriveJSON hasuraJSON{omitNothingFields = True} ''PostgresConnConfiguration)
|
2021-04-13 03:15:37 +03:00
|
|
|
|
$(makeLenses ''PostgresConnConfiguration)
|