Skip to content
Draft
Changes from 1 commit
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
Prev Previous commit
use new pool when configuration is reloaded
laurenceisla committed Dec 30, 2023
commit 0f782a258285bf6acbed235322bd81154695044c
21 changes: 15 additions & 6 deletions src/PostgREST/AppState.hs
Original file line number Diff line number Diff line change
@@ -83,7 +83,7 @@ data AuthResult = AuthResult

data AppState = AppState
-- | Database connection pool
{ statePool :: SQL.Pool
{ statePool :: IORef SQL.Pool
-- | Database server version, will be updated by the connectionWorker
, statePgVersion :: IORef PgVersion
-- | No schema cache at the start. Will be filled in by the connectionWorker
@@ -125,8 +125,9 @@ init conf = do

initWithPool :: AppSockets -> SQL.Pool -> AppConfig -> IO AppState
initWithPool (sock, adminSock) pool conf = do
appState <- AppState pool
<$> newIORef minimumPgVersion -- assume we're in a supported version when starting, this will be corrected on a later step
appState <- AppState
<$> newIORef pool
<*> newIORef minimumPgVersion -- assume we're in a supported version when starting, this will be corrected on a later step
<*> newIORef Nothing
<*> pure (pure ())
<*> newEmptyMVar
@@ -208,7 +209,8 @@ initPool AppConfig{..} =
-- | Run an action with a database connection.
usePool :: AppState -> AppConfig -> SQL.Session a -> IO (Either SQL.UsageError a)
usePool appState@AppState{..} AppConfig{configLogLevel} x = do
res <- SQL.use statePool x
pool <- getPool appState
res <- SQL.use pool x

when (configLogLevel > LogCrit) $ do
whenLeft res (\case
@@ -223,11 +225,17 @@ usePool appState@AppState{..} AppConfig{configLogLevel} x = do
-- | Flush the connection pool so that any future use of the pool will
-- use connections freshly established after this call.
flushPool :: AppState -> IO ()
flushPool AppState{..} = SQL.release statePool
flushPool appState = SQL.release =<< getPool appState

-- | Destroy the pool on shutdown.
destroyPool :: AppState -> IO ()
destroyPool AppState{..} = SQL.release statePool
destroyPool appState = SQL.release =<< getPool appState

getPool :: AppState -> IO SQL.Pool
getPool = readIORef . statePool

putPool :: AppState -> SQL.Pool -> IO ()
putPool = atomicWriteIORef . statePool

getPgVersion :: AppState -> IO PgVersion
getPgVersion = readIORef . statePgVersion
@@ -478,6 +486,7 @@ reReadConfig startingUp appState = do
logWithZTime appState $ "Failed reloading config: " <> err
Right newConf -> do
putConfig appState newConf
putPool appState =<< initPool newConf
if startingUp then
pass
else
8 changes: 8 additions & 0 deletions test/io/fixtures.sql
Original file line number Diff line number Diff line change
@@ -198,3 +198,11 @@ $$ language sql set statement_timeout = '4s';
create function get_postgres_version() returns int as $$
select current_setting('server_version_num')::int;
$$ language sql;

create function change_db_pool_config(size int) returns void as $_$
begin
execute format($$
alter role postgrest_test_authenticator set pgrst.db_pool = %L;
$$, size);
perform pg_notify('pgrst', 'reload config');
end $_$ volatile security definer language plpgsql;
36 changes: 36 additions & 0 deletions test/io/test_io.py
Original file line number Diff line number Diff line change
@@ -582,6 +582,42 @@ def test_pool_acquisition_timeout(level, defaultenv, metapostgrest):
assert "Timed out acquiring connection from connection pool." in output[1]


def test_db_pool_configuration_reload(defaultenv):
"Verify that PGRST_DB_POOL setting is reloaded correctly"

env = {
**defaultenv,
"PGRST_DB_POOL": "1",
"PGRST_DB_POOL_ACQUISITION_TIMEOUT": "1", # 1 second
}

with run(env=env) as postgrest:
response = postgrest.session.post(
"/rpc/change_db_pool_config", data={"size": 2}
)
assert response.status_code == 204

sleep_until_postgrest_config_reload()

def sleep():
res = postgrest.session.get("/rpc/sleep?seconds=1")
assert res.status_code == 204

def get_projects():
res = postgrest.session.get("/projects")
assert res.status_code == 200

thread_1 = Thread(target=sleep)
thread_1.start()

# This would return an error if the DB_POOL is only 1
thread_2 = Thread(target=get_projects)
thread_2.start()

thread_1.join()
thread_2.join()


def test_change_statement_timeout_held_connection(defaultenv, metapostgrest):
"Statement timeout changes take effect immediately, even with a request outliving the reconfiguration"