1
+ {-# LANGUAGE TypeApplications #-}
2
+
1
3
module Database.PostgreSQL.PQTypes.Internal.Connection
2
4
( -- * Connection
3
5
Connection (.. )
6
+ , getBackendPidIO
4
7
, ConnectionData (.. )
5
8
, withConnectionData
6
9
, ConnectionStats (.. )
@@ -26,10 +29,11 @@ import Control.Exception qualified as E
26
29
import Control.Monad
27
30
import Control.Monad.Base
28
31
import Control.Monad.Catch
29
- import Data.Bifunctor
30
32
import Data.ByteString.Char8 qualified as BS
31
33
import Data.Foldable qualified as F
34
+ import Data.Functor.Identity
32
35
import Data.IORef
36
+ import Data.Int
33
37
import Data.Kind
34
38
import Data.Pool
35
39
import Data.Set qualified as S
@@ -48,6 +52,7 @@ import Database.PostgreSQL.PQTypes.Internal.Composite
48
52
import Database.PostgreSQL.PQTypes.Internal.Error
49
53
import Database.PostgreSQL.PQTypes.Internal.Error.Code
50
54
import Database.PostgreSQL.PQTypes.Internal.Exception
55
+ import Database.PostgreSQL.PQTypes.Internal.QueryResult
51
56
import Database.PostgreSQL.PQTypes.Internal.Utils
52
57
import Database.PostgreSQL.PQTypes.SQL.Class
53
58
import Database.PostgreSQL.PQTypes.SQL.Raw
@@ -114,6 +119,8 @@ initialStats =
114
119
data ConnectionData = ConnectionData
115
120
{ cdPtr :: ! (Ptr PGconn )
116
121
-- ^ Pointer to connection object.
122
+ , cdBackendPid :: ! Int
123
+ -- ^ Process ID of the server process attached to the current session.
117
124
, cdStats :: ! ConnectionStats
118
125
-- ^ Statistics associated with the connection.
119
126
, cdPreparedQueries :: ! (IORef (S. Set T. Text ))
@@ -125,6 +132,11 @@ newtype Connection = Connection
125
132
{ unConnection :: MVar (Maybe ConnectionData )
126
133
}
127
134
135
+ getBackendPidIO :: Connection -> IO Int
136
+ getBackendPidIO conn = do
137
+ withConnectionData conn " getBackendPidIO" $ \ cd -> do
138
+ pure (cd, cdBackendPid cd)
139
+
128
140
withConnectionData
129
141
:: Connection
130
142
-> String
@@ -133,7 +145,9 @@ withConnectionData
133
145
withConnectionData (Connection mvc) fname f =
134
146
modifyMVar mvc $ \ mc -> case mc of
135
147
Nothing -> hpqTypesError $ fname ++ " : no connection"
136
- Just cd -> first Just <$> f cd
148
+ Just cd -> do
149
+ (cd', r) <- f cd
150
+ cd' `seq` pure (Just cd', r)
137
151
138
152
-- | Database connection supplier.
139
153
newtype ConnectionSourceM m = ConnectionSourceM
@@ -215,10 +229,21 @@ connect ConnectionSettings {..} = mask $ \unmask -> do
215
229
Just
216
230
ConnectionData
217
231
{ cdPtr = connPtr
232
+ , cdBackendPid = 0
218
233
, cdStats = initialStats
219
234
, cdPreparedQueries = preparedQueries
220
235
}
221
236
F. forM_ csRole $ \ role -> runQueryIO conn $ " SET ROLE " <> role
237
+
238
+ let selectPid = " SELECT pg_backend_pid()" :: RawSQL ()
239
+ (_, res) <- runQueryIO conn selectPid
240
+ case F. toList $ mkQueryResult @ (Identity Int32 ) selectPid 0 res of
241
+ [pid] -> withConnectionData conn fname $ \ cd -> do
242
+ pure (cd {cdBackendPid = fromIntegral pid}, () )
243
+ pids -> do
244
+ let err = HPQTypesError $ " unexpected backend pid: " ++ show pids
245
+ rethrowWithContext selectPid 0 $ toException err
246
+
222
247
pure conn
223
248
where
224
249
fname = " connect"
@@ -317,6 +342,7 @@ runPreparedQueryIO conn (QueryName queryName) sql = do
317
342
E. throwIO
318
343
DBException
319
344
{ dbeQueryContext = sql
345
+ , dbeBackendPid = cdBackendPid
320
346
, dbeError = HPQTypesError " runPreparedQueryIO: unnamed prepared query is not supported"
321
347
, dbeCallStack = callStack
322
348
}
@@ -329,7 +355,7 @@ runPreparedQueryIO conn (QueryName queryName) sql = do
329
355
-- succeeds, we need to reflect that fact in cdPreparedQueries since
330
356
-- you can't prepare a query with the same name more than once.
331
357
res <- c_PQparamPrepare cdPtr nullPtr param cname query
332
- void . withForeignPtr res $ verifyResult sql cdPtr
358
+ void . withForeignPtr res $ verifyResult sql cdBackendPid cdPtr
333
359
modifyIORef' cdPreparedQueries $ S. insert queryName
334
360
(,)
335
361
<$> (fromIntegral <$> c_PQparamCount param)
@@ -353,7 +379,7 @@ runQueryImpl fname conn sql execSql = do
353
379
-- runtime system is used) and react appropriately.
354
380
queryRunner <- async . restore $ do
355
381
(paramCount, res) <- execSql cd
356
- affected <- withForeignPtr res $ verifyResult sql cdPtr
382
+ affected <- withForeignPtr res $ verifyResult sql cdBackendPid cdPtr
357
383
stats' <- case affected of
358
384
Left _ ->
359
385
return
@@ -370,8 +396,7 @@ runQueryImpl fname conn sql execSql = do
370
396
, statsValues = statsValues cdStats + (rows * columns)
371
397
, statsParams = statsParams cdStats + paramCount
372
398
}
373
- -- Force evaluation of modified stats to squash a space leak.
374
- stats' `seq` return (cd {cdStats = stats'}, (either id id affected, res))
399
+ return (cd {cdStats = stats'}, (either id id affected, res))
375
400
-- If we receive an exception while waiting for the execution to complete,
376
401
-- we need to send a request to PostgreSQL for query cancellation and wait
377
402
-- for the query runner thread to terminate. It is paramount we make the
@@ -399,10 +424,11 @@ runQueryImpl fname conn sql execSql = do
399
424
verifyResult
400
425
:: (HasCallStack , IsSQL sql )
401
426
=> sql
427
+ -> Int
402
428
-> Ptr PGconn
403
429
-> Ptr PGresult
404
430
-> IO (Either Int Int )
405
- verifyResult sql conn res = do
431
+ verifyResult sql pid conn res = do
406
432
-- works even if res is NULL
407
433
rst <- c_PQresultStatus res
408
434
case rst of
@@ -421,7 +447,7 @@ verifyResult sql conn res = do
421
447
_ | otherwise -> return . Left $ 0
422
448
where
423
449
throwSQLError =
424
- rethrowWithContext sql
450
+ rethrowWithContext sql pid
425
451
=<< if res == nullPtr
426
452
then
427
453
return . E. toException . QueryError
@@ -451,6 +477,7 @@ verifyResult sql conn res = do
451
477
E. throwIO
452
478
DBException
453
479
{ dbeQueryContext = sql
480
+ , dbeBackendPid = pid
454
481
, dbeError = HPQTypesError (" verifyResult: string returned by PQcmdTuples is not a valid number: " ++ show sn)
455
482
, dbeCallStack = callStack
456
483
}
0 commit comments