1+ {-# LANGUAGE LambdaCase #-}
12{-# LANGUAGE NamedFieldPuns #-}
23{-# LANGUAGE OverloadedStrings #-}
34{-# LANGUAGE QuasiQuotes #-}
67module Simplex.Messaging.Agent.Store.Postgres
78 ( createDBStore ,
89 closeDBStore ,
9- execSQL
10+ reopenDBStore ,
11+ execSQL ,
1012 )
1113where
1214
@@ -15,7 +17,7 @@ import Control.Monad (unless, void)
1517import Data.Functor (($>) )
1618import Data.String (fromString )
1719import Data.Text (Text )
18- import Database.PostgreSQL.Simple (ConnectInfo (.. ), Only (.. ), defaultConnectInfo )
20+ import Database.PostgreSQL.Simple (ConnectInfo (.. ), Only (.. ))
1921import qualified Database.PostgreSQL.Simple as PSQL
2022import Database.PostgreSQL.Simple.SqlQQ (sql )
2123import Simplex.Messaging.Agent.Store.Migrations (migrateSchema )
@@ -24,7 +26,7 @@ import qualified Simplex.Messaging.Agent.Store.Postgres.DB as DB
2426import Simplex.Messaging.Agent.Store.Postgres.Util (createDBAndUserIfNotExists )
2527import Simplex.Messaging.Agent.Store.Shared (Migration (.. ), MigrationConfirmation (.. ), MigrationError (.. ))
2628import Simplex.Messaging.Util (ifM )
27- import UnliftIO.Exception (onException )
29+ import UnliftIO.Exception (bracketOnError , onException )
2830import UnliftIO.MVar
2931import UnliftIO.STM
3032
@@ -44,11 +46,11 @@ createDBStore connectInfo schema migrations confirmMigrations = do
4446 Left e -> closeDBStore st $> Left e
4547
4648connectPostgresStore :: ConnectInfo -> String -> IO DBStore
47- connectPostgresStore dbConnectInfo schema = do
48- (dbConn, dbNew) <- connectDB dbConnectInfo schema -- TODO [postgres] analogue for dbBusyLoop?
49+ connectPostgresStore dbConnectInfo dbSchema = do
50+ (dbConn, dbNew) <- connectDB dbConnectInfo dbSchema -- TODO [postgres] analogue for dbBusyLoop?
4951 dbConnection <- newMVar dbConn
5052 dbClosed <- newTVarIO False
51- pure DBStore {dbConnectInfo, dbConnection, dbNew, dbClosed}
53+ pure DBStore {dbConnectInfo, dbSchema, dbConnection, dbNew, dbClosed}
5254
5355connectDB :: ConnectInfo -> String -> IO (DB. Connection , Bool )
5456connectDB dbConnectInfo schema = do
@@ -81,6 +83,22 @@ closeDBStore st@DBStore {dbClosed} =
8183 DB. close conn
8284 atomically $ writeTVar dbClosed True
8385
86+ openPostgresStore_ :: DBStore -> IO ()
87+ openPostgresStore_ DBStore {dbConnectInfo, dbSchema, dbConnection, dbClosed} =
88+ bracketOnError
89+ (takeMVar dbConnection)
90+ (tryPutMVar dbConnection)
91+ $ \ _dbConn -> do
92+ (dbConn, _dbNew) <- connectDB dbConnectInfo dbSchema
93+ atomically $ writeTVar dbClosed False
94+ putMVar dbConnection dbConn
95+
96+ reopenDBStore :: DBStore -> IO ()
97+ reopenDBStore st@ DBStore {dbClosed} =
98+ ifM (readTVarIO dbClosed) open (putStrLn " reopenDBStore: already opened" )
99+ where
100+ open = openPostgresStore_ st
101+
84102-- TODO [postgres] not necessary for postgres (used for ExecAgentStoreSQL, ExecChatStoreSQL)
85103execSQL :: PSQL. Connection -> Text -> IO [Text ]
86104execSQL _db _query = throwIO (userError " not implemented" )
0 commit comments