Skip to content

Commit 1658048

Browse files
authored
Revert "smp server: use separate database pool for reading queues and creating service records (#1561)" (#1564)
This reverts commit 3df2425.
1 parent 27d3851 commit 1658048

File tree

1 file changed

+4
-13
lines changed

1 file changed

+4
-13
lines changed

src/Simplex/Messaging/Server/QueueStore/Postgres.hs

Lines changed: 4 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -210,7 +210,7 @@ instance StoreQueueClass q => QueueStoreClass q (PostgresQueueStore q) where
210210
mask = E.uninterruptibleMask_ . runExceptT
211211
cacheSender rId = TM.insert qId rId senders
212212
loadQueue condition =
213-
withFastDB "getQueue_" st $ \db -> firstRow rowToQueueRec AUTH $
213+
withDB "getQueue_" st $ \db -> firstRow rowToQueueRec AUTH $
214214
DB.query db (queueRecQuery <> condition <> " AND deleted_at IS NULL") (Only qId)
215215
cacheQueue rId qRec insertRef = do
216216
sq <- mkQ True rId qRec -- loaded queue
@@ -391,7 +391,7 @@ instance StoreQueueClass q => QueueStoreClass q (PostgresQueueStore q) where
391391
getCreateService st sr@ServiceRec {serviceId = newSrvId, serviceRole, serviceCertHash = XV.Fingerprint fp} =
392392
withLockMap (serviceLocks st) fp "getCreateService" $ E.uninterruptibleMask_ $ runExceptT $ do
393393
(serviceId, new) <-
394-
withFastDB "getCreateService" st $ \db ->
394+
withDB "getCreateService" st $ \db ->
395395
maybeFirstRow id (DB.query db "SELECT service_id, service_role FROM services WHERE service_cert_hash = ?" (Only (Binary fp))) >>= \case
396396
Just (serviceId, role)
397397
| role == serviceRole -> pure $ Right (serviceId, False)
@@ -640,19 +640,10 @@ assertUpdated = (>>= \n -> when (n == 0) (throwE AUTH))
640640

641641
withDB' :: Text -> PostgresQueueStore q -> (DB.Connection -> IO a) -> ExceptT ErrorType IO a
642642
withDB' op st action = withDB op st $ fmap Right . action
643-
{-# INLINE withDB' #-}
644-
645-
withFastDB :: forall a q. Text -> PostgresQueueStore q -> (DB.Connection -> IO (Either ErrorType a)) -> ExceptT ErrorType IO a
646-
withFastDB op st = withDB_ op st True
647-
{-# INLINE withFastDB #-}
648643

649644
withDB :: forall a q. Text -> PostgresQueueStore q -> (DB.Connection -> IO (Either ErrorType a)) -> ExceptT ErrorType IO a
650-
withDB op st = withDB_ op st False
651-
{-# INLINE withDB #-}
652-
653-
withDB_ :: forall a q. Text -> PostgresQueueStore q -> Bool -> (DB.Connection -> IO (Either ErrorType a)) -> ExceptT ErrorType IO a
654-
withDB_ op st priority action =
655-
ExceptT $ E.try (withTransactionPriority (dbStore st) priority action) >>= either logErr pure
645+
withDB op st action =
646+
ExceptT $ E.try (withConnection (dbStore st) action) >>= either logErr pure
656647
where
657648
logErr :: E.SomeException -> IO (Either ErrorType a)
658649
logErr e = logError ("STORE: " <> err) $> Left (STORE err)

0 commit comments

Comments
 (0)