Skip to content

Commit fdde986

Browse files
authored
agent: add reopenStore function for postgres; run notification tests with postgres (#1435)
1 parent 9404a3a commit fdde986

File tree

9 files changed

+58
-32
lines changed

9 files changed

+58
-32
lines changed

simplexmq.cabal

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -414,6 +414,7 @@ test-suite simplexmq-test
414414
AgentTests.EqInstances
415415
AgentTests.FunctionalAPITests
416416
AgentTests.MigrationTests
417+
AgentTests.NotificationTests
417418
AgentTests.ServerChoice
418419
CLITests
419420
CoreTests.BatchingTests
@@ -446,7 +447,6 @@ test-suite simplexmq-test
446447
Paths_simplexmq
447448
if !flag(client_postgres)
448449
other-modules:
449-
AgentTests.NotificationTests
450450
AgentTests.SchemaDump
451451
AgentTests.SQLiteTests
452452
hs-source-dirs:

src/Simplex/Messaging/Agent/Store.hs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -73,6 +73,9 @@ createStore dbFilePath dbKey keepKey = Store.createDBStore dbFilePath dbKey keep
7373
closeStore :: DBStore -> IO ()
7474
closeStore = Store.closeDBStore
7575

76+
reopenStore :: DBStore -> IO ()
77+
reopenStore = Store.reopenDBStore
78+
7679
execSQL :: DB.Connection -> Text -> IO [Text]
7780
execSQL = Store.execSQL
7881

src/Simplex/Messaging/Agent/Store/Postgres.hs

Lines changed: 24 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE LambdaCase #-}
12
{-# LANGUAGE NamedFieldPuns #-}
23
{-# LANGUAGE OverloadedStrings #-}
34
{-# LANGUAGE QuasiQuotes #-}
@@ -6,7 +7,8 @@
67
module Simplex.Messaging.Agent.Store.Postgres
78
( createDBStore,
89
closeDBStore,
9-
execSQL
10+
reopenDBStore,
11+
execSQL,
1012
)
1113
where
1214

@@ -15,7 +17,7 @@ import Control.Monad (unless, void)
1517
import Data.Functor (($>))
1618
import Data.String (fromString)
1719
import Data.Text (Text)
18-
import Database.PostgreSQL.Simple (ConnectInfo (..), Only (..), defaultConnectInfo)
20+
import Database.PostgreSQL.Simple (ConnectInfo (..), Only (..))
1921
import qualified Database.PostgreSQL.Simple as PSQL
2022
import Database.PostgreSQL.Simple.SqlQQ (sql)
2123
import Simplex.Messaging.Agent.Store.Migrations (migrateSchema)
@@ -24,7 +26,7 @@ import qualified Simplex.Messaging.Agent.Store.Postgres.DB as DB
2426
import Simplex.Messaging.Agent.Store.Postgres.Util (createDBAndUserIfNotExists)
2527
import Simplex.Messaging.Agent.Store.Shared (Migration (..), MigrationConfirmation (..), MigrationError (..))
2628
import Simplex.Messaging.Util (ifM)
27-
import UnliftIO.Exception (onException)
29+
import UnliftIO.Exception (bracketOnError, onException)
2830
import UnliftIO.MVar
2931
import UnliftIO.STM
3032

@@ -44,11 +46,11 @@ createDBStore connectInfo schema migrations confirmMigrations = do
4446
Left e -> closeDBStore st $> Left e
4547

4648
connectPostgresStore :: 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

5355
connectDB :: ConnectInfo -> String -> IO (DB.Connection, Bool)
5456
connectDB 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)
85103
execSQL :: PSQL.Connection -> Text -> IO [Text]
86104
execSQL _db _query = throwIO (userError "not implemented")

src/Simplex/Messaging/Agent/Store/Postgres/Common.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -17,6 +17,7 @@ import UnliftIO.STM
1717
-- TODO [postgres] use log_min_duration_statement instead of custom slow queries (SQLite's Connection type)
1818
data DBStore = DBStore
1919
{ dbConnectInfo :: PSQL.ConnectInfo,
20+
dbSchema :: String,
2021
dbConnection :: MVar PSQL.Connection,
2122
dbClosed :: TVar Bool,
2223
dbNew :: Bool

src/Simplex/Messaging/Agent/Store/Postgres/Migrations/M20241210_initial.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -208,7 +208,7 @@ CREATE TABLE ntf_tokens(
208208
tkn_action BYTEA,
209209
created_at TIMESTAMPTZ NOT NULL DEFAULT (now()),
210210
updated_at TIMESTAMPTZ NOT NULL DEFAULT (now()),
211-
ntf_mode TEXT NULL,
211+
ntf_mode BYTEA NULL,
212212
PRIMARY KEY(provider, device_token, ntf_host, ntf_port),
213213
FOREIGN KEY(ntf_host, ntf_port) REFERENCES ntf_servers
214214
ON DELETE RESTRICT ON UPDATE CASCADE
@@ -222,8 +222,8 @@ CREATE TABLE ntf_subscriptions(
222222
ntf_port TEXT NOT NULL,
223223
ntf_sub_id BYTEA,
224224
ntf_sub_status TEXT NOT NULL,
225-
ntf_sub_action TEXT,
226-
ntf_sub_smp_action TEXT,
225+
ntf_sub_action BYTEA,
226+
ntf_sub_smp_action BYTEA,
227227
ntf_sub_action_ts TIMESTAMPTZ,
228228
updated_by_supervisor SMALLINT NOT NULL DEFAULT 0,
229229
created_at TIMESTAMPTZ NOT NULL DEFAULT (now()),

src/Simplex/Messaging/Agent/Store/SQLite.hs

Lines changed: 5 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -27,13 +27,12 @@
2727
module Simplex.Messaging.Agent.Store.SQLite
2828
( createDBStore,
2929
closeDBStore,
30+
reopenDBStore,
3031
execSQL,
3132
-- used in Simplex.Chat.Archive
3233
sqlString,
3334
keyString,
3435
storeKey,
35-
-- used in Simplex.Chat.Mobile and tests
36-
reopenSQLiteStore,
3736
-- used in tests
3837
connectSQLiteStore,
3938
openSQLiteStore,
@@ -127,14 +126,14 @@ openSQLiteStore_ DBStore {dbConnection, dbFilePath, dbKey, dbClosed} key keepKey
127126
writeTVar dbKey $! storeKey key keepKey
128127
putMVar dbConnection DB.Connection {conn, slow}
129128

130-
reopenSQLiteStore :: DBStore -> IO ()
131-
reopenSQLiteStore st@DBStore {dbKey, dbClosed} =
132-
ifM (readTVarIO dbClosed) open (putStrLn "reopenSQLiteStore: already opened")
129+
reopenDBStore :: DBStore -> IO ()
130+
reopenDBStore st@DBStore {dbKey, dbClosed} =
131+
ifM (readTVarIO dbClosed) open (putStrLn "reopenDBStore: already opened")
133132
where
134133
open =
135134
readTVarIO dbKey >>= \case
136135
Just key -> openSQLiteStore_ st key True
137-
Nothing -> fail "reopenSQLiteStore: no key"
136+
Nothing -> fail "reopenDBStore: no key"
138137

139138
keyString :: ScrubbedBytes -> Text
140139
keyString = sqlString . safeDecodeUtf8 . BA.convert

tests/AgentTests.hs

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -12,14 +12,14 @@ import AgentTests.ConnectionRequestTests
1212
import AgentTests.DoubleRatchetTests (doubleRatchetTests)
1313
import AgentTests.FunctionalAPITests (functionalAPITests)
1414
import AgentTests.MigrationTests (migrationTests)
15+
import AgentTests.NotificationTests (notificationTests)
1516
import AgentTests.ServerChoice (serverChoiceTests)
1617
import Simplex.Messaging.Transport (ATransport (..))
1718
import Test.Hspec
1819
#if defined(dbPostgres)
1920
import Fixtures
2021
import Simplex.Messaging.Agent.Store.Postgres.Util (dropAllSchemasExceptSystem)
2122
#else
22-
import AgentTests.NotificationTests (notificationTests)
2323
import AgentTests.SQLiteTests (storeTests)
2424
#endif
2525

@@ -30,12 +30,12 @@ agentTests (ATransport t) = do
3030
describe "Double ratchet tests" doubleRatchetTests
3131
#if defined(dbPostgres)
3232
after_ (dropAllSchemasExceptSystem testDBConnectInfo) $ do
33+
#else
34+
do
35+
#endif
3336
describe "Functional API" $ functionalAPITests (ATransport t)
3437
describe "Chosen servers" serverChoiceTests
35-
#else
36-
describe "Functional API" $ functionalAPITests (ATransport t)
37-
describe "Chosen servers" serverChoiceTests
38-
-- notifications aren't tested with postgres, as we don't plan to use iOS client with it
39-
describe "Notification tests" $ notificationTests (ATransport t)
38+
describe "Notification tests" $ notificationTests (ATransport t)
39+
#if !defined(dbPostgres)
4040
describe "SQLite store" storeTests
4141
#endif

tests/AgentTests/NotificationTests.hs

Lines changed: 11 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE CPP #-}
12
{-# LANGUAGE DuplicateRecordFields #-}
23
{-# LANGUAGE FlexibleContexts #-}
34
{-# LANGUAGE GADTs #-}
@@ -53,7 +54,6 @@ import qualified Data.ByteString.Char8 as B
5354
import Data.List.NonEmpty (NonEmpty (..))
5455
import qualified Data.List.NonEmpty as L
5556
import Data.Text.Encoding (encodeUtf8)
56-
import Database.SQLite.Simple.QQ (sql)
5757
import NtfClient
5858
import SMPAgentClient (agentCfg, initAgentServers, initAgentServers2, testDB, testDB2, testNtfServer, testNtfServer2)
5959
import SMPClient (cfg, cfgVPrev, testPort, testPort2, testStoreLogFile2, testStoreMsgsDir2, withSmpServer, withSmpServerConfigOn, withSmpServerStoreLogOn, withSmpServerStoreMsgLogOn)
@@ -62,9 +62,9 @@ import Simplex.Messaging.Agent.Client (ProtocolTestFailure (..), ProtocolTestSte
6262
import Simplex.Messaging.Agent.Env.SQLite (AgentConfig, Env (..), InitialAgentServers)
6363
import Simplex.Messaging.Agent.Protocol hiding (CON, CONF, INFO, SENT)
6464
import Simplex.Messaging.Agent.Store.AgentStore (getSavedNtfToken)
65-
import Simplex.Messaging.Agent.Store.SQLite (closeDBStore, reopenSQLiteStore)
66-
import Simplex.Messaging.Agent.Store.SQLite.Common (withTransaction)
67-
import qualified Simplex.Messaging.Agent.Store.SQLite.DB as DB
65+
import Simplex.Messaging.Agent.Store (closeStore, reopenStore)
66+
import Simplex.Messaging.Agent.Store.Common (withTransaction)
67+
import qualified Simplex.Messaging.Agent.Store.DB as DB
6868
import qualified Simplex.Messaging.Crypto as C
6969
import Simplex.Messaging.Encoding.String
7070
import Simplex.Messaging.Notifications.Protocol
@@ -78,6 +78,11 @@ import Simplex.Messaging.Server.Env.STM (ServerConfig (..))
7878
import Simplex.Messaging.Transport (ATransport)
7979
import Test.Hspec
8080
import UnliftIO
81+
#if defined(dbPostgres)
82+
import Database.PostgreSQL.Simple.SqlQQ (sql)
83+
#else
84+
import Database.SQLite.Simple.QQ (sql)
85+
#endif
8186

8287
notificationTests :: ATransport -> Spec
8388
notificationTests t = do
@@ -496,7 +501,7 @@ testNotificationSubscriptionExistingConnection apns baseId alice@AgentClient {ag
496501

497502
threadDelay 500000
498503
suspendAgent alice 0
499-
closeDBStore store
504+
closeStore store
500505
threadDelay 1000000
501506
putStrLn "before opening the database from another agent"
502507

@@ -507,7 +512,7 @@ testNotificationSubscriptionExistingConnection apns baseId alice@AgentClient {ag
507512

508513
threadDelay 1000000
509514
putStrLn "after closing the database in another agent"
510-
reopenSQLiteStore store
515+
reopenStore store
511516
foregroundAgent alice
512517
threadDelay 500000
513518

tests/AgentTests/SQLiteTests.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -604,7 +604,7 @@ testCloseReopenStore = do
604604
hasMigrations st
605605
closeDBStore st
606606
errorGettingMigrations st
607-
reopenSQLiteStore st
607+
reopenDBStore st
608608
hasMigrations st
609609

610610
testCloseReopenEncryptedStore :: IO ()
@@ -615,13 +615,13 @@ testCloseReopenEncryptedStore = do
615615
closeDBStore st
616616
closeDBStore st
617617
errorGettingMigrations st
618-
reopenSQLiteStore st `shouldThrow` \(e :: SomeException) -> "reopenSQLiteStore: no key" `isInfixOf` show e
618+
reopenDBStore st `shouldThrow` \(e :: SomeException) -> "reopenDBStore: no key" `isInfixOf` show e
619619
openSQLiteStore st key True
620620
openSQLiteStore st key True
621621
hasMigrations st
622622
closeDBStore st
623623
errorGettingMigrations st
624-
reopenSQLiteStore st
624+
reopenDBStore st
625625
hasMigrations st
626626

627627
testReopenEncryptedStoreKeepKey :: IO ()
@@ -631,7 +631,7 @@ testReopenEncryptedStoreKeepKey = do
631631
hasMigrations st
632632
closeDBStore st
633633
errorGettingMigrations st
634-
reopenSQLiteStore st
634+
reopenDBStore st
635635
hasMigrations st
636636

637637
getMigrations :: DBStore -> IO Bool

0 commit comments

Comments
 (0)