Skip to content

Commit aca4567

Browse files
committed
ntf server: remove support for store log
1 parent a1277bf commit aca4567

File tree

5 files changed

+58
-593
lines changed

5 files changed

+58
-593
lines changed

simplexmq.cabal

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -275,7 +275,6 @@ library
275275
Simplex.Messaging.Notifications.Server.Store.Migrations
276276
Simplex.Messaging.Notifications.Server.Store.Postgres
277277
Simplex.Messaging.Notifications.Server.Store.Types
278-
Simplex.Messaging.Notifications.Server.StoreLog
279278
Simplex.Messaging.Server.MsgStore.Postgres
280279
Simplex.Messaging.Server.QueueStore.Postgres
281280
Simplex.Messaging.Server.QueueStore.Postgres.Migrations

src/Simplex/Messaging/Notifications/Server/Env.hs

Lines changed: 1 addition & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -9,8 +9,6 @@
99
module Simplex.Messaging.Notifications.Server.Env where
1010

1111
import Control.Concurrent (ThreadId)
12-
import Control.Logger.Simple
13-
import Control.Monad
1412
import Crypto.Random
1513
import Data.Int (Int64)
1614
import Data.List.NonEmpty (NonEmpty)
@@ -27,16 +25,13 @@ import qualified Simplex.Messaging.Crypto as C
2725
import Simplex.Messaging.Notifications.Protocol
2826
import Simplex.Messaging.Notifications.Server.Push.APNS
2927
import Simplex.Messaging.Notifications.Server.Stats
30-
import Simplex.Messaging.Notifications.Server.Store (newNtfSTMStore)
3128
import Simplex.Messaging.Notifications.Server.Store.Postgres
3229
import Simplex.Messaging.Notifications.Server.Store.Types
33-
import Simplex.Messaging.Notifications.Server.StoreLog (readWriteNtfSTMStore)
3430
import Simplex.Messaging.Notifications.Transport (NTFVersion, VersionRangeNTF)
3531
import Simplex.Messaging.Protocol (BasicAuth, CorrId, Party (..), SMPServer, SParty (..), Transmission)
3632
import Simplex.Messaging.Server.Env.STM (StartOptions (..))
3733
import Simplex.Messaging.Server.Expiration
3834
import Simplex.Messaging.Server.QueueStore.Postgres.Config (PostgresStoreCfg (..))
39-
import Simplex.Messaging.Server.StoreLog (closeStoreLog)
4035
import Simplex.Messaging.Session
4136
import Simplex.Messaging.TMap (TMap)
4237
import qualified Simplex.Messaging.TMap as TM
@@ -96,8 +91,7 @@ data NtfEnv = NtfEnv
9691
}
9792

9893
newNtfServerEnv :: NtfServerConfig -> IO NtfEnv
99-
newNtfServerEnv config@NtfServerConfig {pushQSize, smpAgentCfg, apnsConfig, dbStoreConfig, ntfCredentials, useServiceCreds, startOptions} = do
100-
when (compactLog startOptions) $ compactDbStoreLog $ dbStoreLogPath dbStoreConfig
94+
newNtfServerEnv config@NtfServerConfig {pushQSize, smpAgentCfg, apnsConfig, dbStoreConfig, ntfCredentials, useServiceCreds} = do
10195
random <- C.newRandom
10296
store <- newNtfDbStore dbStoreConfig
10397
tlsServerCreds <- loadServerCredential ntfCredentials
@@ -115,14 +109,6 @@ newNtfServerEnv config@NtfServerConfig {pushQSize, smpAgentCfg, apnsConfig, dbSt
115109
pushServer <- newNtfPushServer pushQSize apnsConfig
116110
serverStats <- newNtfServerStats =<< getCurrentTime
117111
pure NtfEnv {config, subscriber, pushServer, store, random, tlsServerCreds, serverIdentity = C.KeyHash fp, serverStats}
118-
where
119-
compactDbStoreLog = \case
120-
Just f -> do
121-
logNote $ "compacting store log " <> T.pack f
122-
newNtfSTMStore >>= readWriteNtfSTMStore False f >>= closeStoreLog
123-
Nothing -> do
124-
logError "Error: `--compact-log` used without `enable: on` option in STORE_LOG section of INI file"
125-
exitFailure
126112

127113
data NtfSubscriber = NtfSubscriber
128114
{ smpSubscribers :: TMap SMPServer SMPSubscriberVar,

src/Simplex/Messaging/Notifications/Server/Main.hs

Lines changed: 3 additions & 93 deletions
Original file line numberDiff line numberDiff line change
@@ -17,42 +17,32 @@ import Data.Functor (($>))
1717
import Data.Ini (lookupValue, readIniFile)
1818
import Data.Int (Int64)
1919
import Data.Maybe (fromMaybe)
20-
import Data.Set (Set)
21-
import qualified Data.Set as S
2220
import qualified Data.Text as T
2321
import Data.Text.Encoding (encodeUtf8)
2422
import qualified Data.Text.IO as T
2523
import Network.Socket (HostName, ServiceName)
2624
import Options.Applicative
27-
import Simplex.Messaging.Agent.Store.Postgres (checkSchemaExists)
2825
import Simplex.Messaging.Agent.Store.Postgres.Options (DBOpts (..))
2926
import Simplex.Messaging.Agent.Store.Shared (MigrationConfirmation (..))
3027
import Simplex.Messaging.Client (HostMode (..), NetworkConfig (..), ProtocolClientConfig (..), SMPWebPortServers (..), SocksMode (..), defaultNetworkConfig, textToHostMode)
3128
import Simplex.Messaging.Client.Agent (SMPClientAgentConfig (..), defaultSMPClientAgentConfig)
3229
import qualified Simplex.Messaging.Crypto as C
33-
import Simplex.Messaging.Notifications.Protocol (NtfTokenId)
34-
import Simplex.Messaging.Notifications.Server (runNtfServer, restoreServerLastNtfs)
30+
import Simplex.Messaging.Notifications.Server (runNtfServer)
3531
import Simplex.Messaging.Notifications.Server.Env (NtfServerConfig (..), defaultInactiveClientExpiration)
3632
import Simplex.Messaging.Notifications.Server.Push.APNS (defaultAPNSPushClientConfig)
37-
import Simplex.Messaging.Notifications.Server.Store (newNtfSTMStore)
38-
import Simplex.Messaging.Notifications.Server.Store.Postgres (exportNtfDbStore, importNtfSTMStore, newNtfDbStore)
39-
import Simplex.Messaging.Notifications.Server.StoreLog (readWriteNtfSTMStore)
4033
import Simplex.Messaging.Notifications.Transport (alpnSupportedNTFHandshakes, supportedServerNTFVRange)
4134
import Simplex.Messaging.Protocol (ProtoServerWithAuth (..), pattern NtfServer)
4235
import Simplex.Messaging.Server.CLI
4336
import Simplex.Messaging.Server.Env.STM (StartOptions (..))
4437
import Simplex.Messaging.Server.Expiration
45-
import Simplex.Messaging.Server.Main (strParse)
4638
import Simplex.Messaging.Server.Main.Init (iniDbOpts)
4739
import Simplex.Messaging.Server.QueueStore.Postgres.Config (PostgresStoreCfg (..))
48-
import Simplex.Messaging.Server.StoreLog (closeStoreLog)
4940
import Simplex.Messaging.Transport (ASrvTransport)
5041
import Simplex.Messaging.Transport.Client (TransportHost (..))
5142
import Simplex.Messaging.Transport.HTTP2 (httpALPN)
5243
import Simplex.Messaging.Transport.Server (AddHTTP, ServerCredentials (..), mkTransportServerConfig)
53-
import Simplex.Messaging.Util (eitherToMaybe, ifM, tshow)
54-
import System.Directory (createDirectoryIfMissing, doesFileExist, renameFile)
55-
import System.Exit (exitFailure)
44+
import Simplex.Messaging.Util (eitherToMaybe, tshow)
45+
import System.Directory (createDirectoryIfMissing, doesFileExist)
5646
import System.FilePath (combine)
5747
import System.IO (BufferMode (..), hSetBuffering, stderr, stdout)
5848
import Text.Read (readMaybe)
@@ -73,69 +63,11 @@ ntfServerCLI cfgPath logPath =
7363
deleteDirIfExists cfgPath
7464
deleteDirIfExists logPath
7565
putStrLn "Deleted configuration and log files"
76-
Database cmd dbOpts@DBOpts {connstr, schema} -> withIniFile $ \ini -> do
77-
schemaExists <- checkSchemaExists connstr schema
78-
storeLogExists <- doesFileExist storeLogFilePath
79-
lastNtfsExists <- doesFileExist defaultLastNtfsFile
80-
case cmd of
81-
SCImport skipTokens
82-
| schemaExists && (storeLogExists || lastNtfsExists) -> exitConfigureNtfStore connstr schema
83-
| schemaExists -> do
84-
putStrLn $ "Schema " <> B.unpack schema <> " already exists in PostrgreSQL database: " <> B.unpack connstr
85-
exitFailure
86-
| not storeLogExists -> do
87-
putStrLn $ storeLogFilePath <> " file does not exist."
88-
exitFailure
89-
| not lastNtfsExists -> do
90-
putStrLn $ defaultLastNtfsFile <> " file does not exist."
91-
exitFailure
92-
| otherwise -> do
93-
storeLogFile <- getRequiredStoreLogFile ini
94-
confirmOrExit
95-
("WARNING: store log file " <> storeLogFile <> " will be compacted and imported to PostrgreSQL database: " <> B.unpack connstr <> ", schema: " <> B.unpack schema)
96-
"Notification server store not imported"
97-
stmStore <- newNtfSTMStore
98-
sl <- readWriteNtfSTMStore True storeLogFile stmStore
99-
closeStoreLog sl
100-
restoreServerLastNtfs stmStore defaultLastNtfsFile
101-
let storeCfg = PostgresStoreCfg {dbOpts = dbOpts {createSchema = True}, dbStoreLogPath = Nothing, confirmMigrations = MCConsole, deletedTTL = iniDeletedTTL ini}
102-
ps <- newNtfDbStore storeCfg
103-
(tCnt, sCnt, nCnt, serviceCnt) <- importNtfSTMStore ps stmStore skipTokens
104-
renameFile storeLogFile $ storeLogFile <> ".bak"
105-
putStrLn $ "Import completed: " <> show tCnt <> " tokens, " <> show sCnt <> " subscriptions, " <> show serviceCnt <> " service associations, " <> show nCnt <> " last token notifications."
106-
putStrLn "Configure database options in INI file."
107-
SCExport
108-
| schemaExists && storeLogExists -> exitConfigureNtfStore connstr schema
109-
| not schemaExists -> do
110-
putStrLn $ "Schema " <> B.unpack schema <> " does not exist in PostrgreSQL database: " <> B.unpack connstr
111-
exitFailure
112-
| storeLogExists -> do
113-
putStrLn $ storeLogFilePath <> " file already exists."
114-
exitFailure
115-
| lastNtfsExists -> do
116-
putStrLn $ defaultLastNtfsFile <> " file already exists."
117-
exitFailure
118-
| otherwise -> do
119-
confirmOrExit
120-
("WARNING: PostrgreSQL database schema " <> B.unpack schema <> " (database: " <> B.unpack connstr <> ") will be exported to store log file " <> storeLogFilePath)
121-
"Notification server store not imported"
122-
let storeCfg = PostgresStoreCfg {dbOpts, dbStoreLogPath = Just storeLogFilePath, confirmMigrations = MCConsole, deletedTTL = iniDeletedTTL ini}
123-
st <- newNtfDbStore storeCfg
124-
(tCnt, sCnt, nCnt) <- exportNtfDbStore st defaultLastNtfsFile
125-
putStrLn $ "Export completed: " <> show tCnt <> " tokens, " <> show sCnt <> " subscriptions, " <> show nCnt <> " last token notifications."
12666
where
12767
withIniFile a =
12868
doesFileExist iniFile >>= \case
12969
True -> readIniFile iniFile >>= either exitError a
13070
_ -> exitError $ "Error: server is not initialized (" <> iniFile <> " does not exist).\nRun `" <> executableName <> " init`."
131-
getRequiredStoreLogFile ini = do
132-
case enableStoreLog' ini $> storeLogFilePath of
133-
Just storeLogFile -> do
134-
ifM
135-
(doesFileExist storeLogFile)
136-
(pure storeLogFile)
137-
(putStrLn ("Store log file " <> storeLogFile <> " not found") >> exitFailure)
138-
Nothing -> putStrLn "Store log disabled, see `[STORE_LOG] enable`" >> exitFailure
13971
iniFile = combine cfgPath "ntf-server.ini"
14072
serverVersion = "SMP notifications server v" <> simplexmqVersionCommit
14173
defaultServerPort = "443"
@@ -289,11 +221,6 @@ ntfServerCLI cfgPath logPath =
289221
startOptions
290222
}
291223
iniDeletedTTL ini = readIniDefault (86400 * defaultDeletedTTL) "STORE_LOG" "db_deleted_ttl" ini
292-
defaultLastNtfsFile = combine logPath "ntf-server-last-notifications.log"
293-
exitConfigureNtfStore connstr schema = do
294-
putStrLn $ "Error: both " <> storeLogFilePath <> " file and " <> B.unpack schema <> " schema are present (database: " <> B.unpack connstr <> ")."
295-
putStrLn "Configure notification server storage."
296-
exitFailure
297224

298225
printNtfServerConfig :: [(ServiceName, ASrvTransport, AddHTTP)] -> PostgresStoreCfg -> IO ()
299226
printNtfServerConfig transports PostgresStoreCfg {dbOpts = DBOpts {connstr, schema}, dbStoreLogPath} = do
@@ -305,9 +232,6 @@ data CliCommand
305232
| OnlineCert CertOptions
306233
| Start StartOptions
307234
| Delete
308-
| Database StoreCmd DBOpts
309-
310-
data StoreCmd = SCImport (Set NtfTokenId) | SCExport
311235

312236
data InitOptions = InitOptions
313237
{ enableStoreLog :: Bool,
@@ -338,22 +262,8 @@ cliCommandP cfgPath logPath iniFile =
338262
<> command "cert" (info (OnlineCert <$> certOptionsP) (progDesc $ "Generate new online TLS server credentials (configuration: " <> iniFile <> ")"))
339263
<> command "start" (info (Start <$> startOptionsP) (progDesc $ "Start server (configuration: " <> iniFile <> ")"))
340264
<> command "delete" (info (pure Delete) (progDesc "Delete configuration and log files"))
341-
<> command "database" (info (Database <$> databaseCmdP <*> dbOptsP defaultNtfDBOpts) (progDesc "Import/export notifications server store to/from PostgreSQL database"))
342265
)
343266
where
344-
databaseCmdP =
345-
hsubparser
346-
( command "import" (info (SCImport <$> skipTokensP) (progDesc $ "Import store logs into a new PostgreSQL database schema"))
347-
<> command "export" (info (pure SCExport) (progDesc $ "Export PostgreSQL database schema to store logs"))
348-
)
349-
skipTokensP :: Parser (Set NtfTokenId)
350-
skipTokensP =
351-
option
352-
strParse
353-
( long "skip-tokens"
354-
<> help "Skip tokens during import"
355-
<> value S.empty
356-
)
357267
initP :: Parser InitOptions
358268
initP = do
359269
enableStoreLog <-

0 commit comments

Comments
 (0)