@@ -69,6 +69,7 @@ import qualified Data.List.NonEmpty as L
6969import qualified Data.Map.Strict as M
7070import Data.Maybe (catMaybes , fromMaybe , isJust , isNothing )
7171import Data.Semigroup (Sum (.. ))
72+ import Data.Text (Text )
7273import qualified Data.Text as T
7374import Data.Text.Encoding (decodeLatin1 )
7475import qualified Data.Text.IO as T
@@ -104,14 +105,15 @@ import Simplex.Messaging.Server.QueueStore
104105import Simplex.Messaging.Server.QueueStore.QueueInfo
105106import Simplex.Messaging.Server.QueueStore.STM
106107import Simplex.Messaging.Server.Stats
108+ import Simplex.Messaging.Server.StoreLog (foldLogLines )
107109import Simplex.Messaging.TMap (TMap )
108110import qualified Simplex.Messaging.TMap as TM
109111import Simplex.Messaging.Transport
110112import Simplex.Messaging.Transport.Buffer (trimCR )
111113import Simplex.Messaging.Transport.Server
112114import Simplex.Messaging.Util
113115import Simplex.Messaging.Version
114- import System.Exit (exitFailure )
116+ import System.Exit (exitFailure , exitSuccess )
115117import System.IO (hPrint , hPutStrLn , hSetNewlineMode , universalNewlineMode )
116118import System.Mem.Weak (deRefWeak )
117119import UnliftIO (timeout )
@@ -162,14 +164,18 @@ newMessageStats :: MessageStats
162164newMessageStats = MessageStats 0 0 0
163165
164166smpServer :: TMVar Bool -> ServerConfig -> Maybe AttachHTTP -> M ()
165- smpServer started cfg@ ServerConfig {transports, transportConfig = tCfg} attachHTTP_ = do
167+ smpServer started cfg@ ServerConfig {transports, transportConfig = tCfg, startOptions } attachHTTP_ = do
166168 s <- asks server
167169 pa <- asks proxyAgent
168- msgStats_ <- processServerMessages
170+ msgStats_ <- processServerMessages startOptions
169171 ntfStats <- restoreServerNtfs
170172 liftIO $ mapM_ (printMessageStats " messages" ) msgStats_
171173 liftIO $ printMessageStats " notifications" ntfStats
172174 restoreServerStats msgStats_ ntfStats
175+ when (maintenance startOptions) $ do
176+ liftIO $ putStrLn " Server started in 'maintenance' mode, exiting"
177+ stopServer s
178+ liftIO $ exitSuccess
173179 raceAny_
174180 ( serverThread s " server subscribedQ" subscribedQ subscribers subClients pendingSubEvents subscriptions cancelSub
175181 : serverThread s " server ntfSubscribedQ" ntfSubscribedQ Env. notifiers ntfSubClients pendingNtfSubEvents ntfSubscriptions (\ _ -> pure () )
@@ -1816,16 +1822,16 @@ exportMessages tty ms f drainMsgs = do
18161822 exitFailure
18171823 encodeMessages rId = mconcat . map (\ msg -> BLD. byteString (strEncode $ MLRv3 rId msg) <> BLD. char8 ' \n ' )
18181824
1819- processServerMessages :: M (Maybe MessageStats )
1820- processServerMessages = do
1825+ processServerMessages :: StartOptions -> M (Maybe MessageStats )
1826+ processServerMessages StartOptions {skipWarnings} = do
18211827 old_ <- asks (messageExpiration . config) $>>= (liftIO . fmap Just . expireBeforeEpoch)
18221828 expire <- asks $ expireMessagesOnStart . config
18231829 asks msgStore >>= liftIO . processMessages old_ expire
18241830 where
18251831 processMessages :: Maybe Int64 -> Bool -> AMsgStore -> IO (Maybe MessageStats )
18261832 processMessages old_ expire = \ case
18271833 AMS SMSMemory ms@ STMMsgStore {storeConfig = STMStoreConfig {storePath}} -> case storePath of
1828- Just f -> ifM (doesFileExist f) (Just <$> importMessages False ms f old_) (pure Nothing )
1834+ Just f -> ifM (doesFileExist f) (Just <$> importMessages False ms f old_ skipWarnings ) (pure Nothing )
18291835 Nothing -> pure Nothing
18301836 AMS SMSJournal ms
18311837 | expire -> Just <$> case old_ of
@@ -1858,44 +1864,56 @@ processServerMessages = do
18581864 logError $ " STORE: processValidateQueue, failed opening message queue, " <> tshow e
18591865 exitFailure
18601866
1861- -- TODO this function should be called after importing queues from store log
1862- importMessages :: forall s . STMStoreClass s => Bool -> s -> FilePath -> Maybe Int64 -> IO MessageStats
1863- importMessages tty ms f old_ = do
1867+ importMessages :: forall s . STMStoreClass s => Bool -> s -> FilePath -> Maybe Int64 -> Bool -> IO MessageStats
1868+ importMessages tty ms f old_ skipWarnings = do
18641869 logInfo $ " restoring messages from file " <> T. pack f
1865- LB. readFile f >>= runExceptT . foldM restoreMsg (0 , Nothing , (0 , 0 , M. empty)) . LB. lines >>= \ case
1866- Left e -> do
1867- when tty $ putStrLn " "
1868- logError . T. pack $ " error restoring messages: " <> e
1869- liftIO exitFailure
1870- Right (lineCount, _, (storedMsgsCount, expiredMsgsCount, overQuota)) -> do
1871- putStrLn $ progress lineCount
1872- renameFile f $ f <> " .bak"
1873- mapM_ setOverQuota_ overQuota
1874- logQueueStates ms
1875- storedQueues <- M. size <$> readTVarIO (queues $ stmQueueStore ms)
1876- pure MessageStats {storedMsgsCount, expiredMsgsCount, storedQueues}
1870+ (lineCount, _, (storedMsgsCount, expiredMsgsCount, overQuota)) <-
1871+ foldLogLines tty f restoreMsg (0 , Nothing , (0 , 0 , M. empty))
1872+ putStrLn $ progress lineCount
1873+ renameFile f $ f <> " .bak"
1874+ mapM_ setOverQuota_ overQuota
1875+ logQueueStates ms
1876+ storedQueues <- M. size <$> readTVarIO (queues $ stmQueueStore ms)
1877+ pure MessageStats {storedMsgsCount, expiredMsgsCount, storedQueues}
18771878 where
18781879 progress i = " Processed " <> show i <> " lines"
1879- restoreMsg :: (Int , Maybe (RecipientId , StoreQueue s ), (Int , Int , M. Map RecipientId (StoreQueue s ))) -> LB. ByteString -> ExceptT String IO (Int , Maybe (RecipientId , StoreQueue s ), (Int , Int , M. Map RecipientId (StoreQueue s )))
1880- restoreMsg (! i, q_, (! stored, ! expired, ! overQuota)) s' = do
1881- when (tty && i `mod` 1000 == 0 ) $ liftIO $ putStr (progress i <> " \r " ) >> hFlush stdout
1882- MLRv3 rId msg <- liftEither . first (msgErr " parsing" ) $ strDecode s
1883- liftError show $ addToMsgQueue rId msg
1880+ restoreMsg :: (Int , Maybe (RecipientId , StoreQueue s ), (Int , Int , M. Map RecipientId (StoreQueue s ))) -> Bool -> ByteString -> IO (Int , Maybe (RecipientId , StoreQueue s ), (Int , Int , M. Map RecipientId (StoreQueue s )))
1881+ restoreMsg (! i, q_, counts@ (! stored, ! expired, ! overQuota)) eof s = do
1882+ when (tty && i `mod` 1000 == 0 ) $ putStr (progress i <> " \r " ) >> hFlush stdout
1883+ case strDecode s of
1884+ Right (MLRv3 rId msg) -> runExceptT (addToMsgQueue rId msg) >>= either (exitErr . tshow) pure
1885+ Left e
1886+ | eof -> warnOrExit (parsingErr e) $> (i + 1 , q_, counts)
1887+ | otherwise -> exitErr $ parsingErr e
18841888 where
1885- s = LB. toStrict s'
1889+ exitErr e = do
1890+ when tty $ putStrLn " "
1891+ logError $ " error restoring messages: " <> e
1892+ liftIO exitFailure
1893+ parsingErr :: String -> Text
1894+ parsingErr e = " parsing error (" <> T. pack e <> " ): " <> safeDecodeUtf8 (B. take 100 s)
18861895 addToMsgQueue rId msg = do
1887- q <- case q_ of
1896+ qOrErr <- case q_ of
18881897 -- to avoid lookup when restoring the next message to the same queue
1889- Just (rId', q') | rId' == rId -> pure q'
1890- _ -> ExceptT $ getQueue ms SRecipient rId
1898+ Just (rId', q') | rId' == rId -> pure $ Right q'
1899+ _ -> liftIO $ getQueue ms SRecipient rId
1900+ case qOrErr of
1901+ Right q -> addToQueue_ q rId msg
1902+ Left AUTH -> liftIO $ do
1903+ when tty $ putStrLn " "
1904+ warnOrExit $ " queue " <> safeDecodeUtf8 (encode $ unEntityId rId) <> " does not exist"
1905+ pure (i + 1 , Nothing , counts)
1906+ Left e -> throwE e
1907+ addToQueue_ q rId msg =
18911908 (i + 1 ,Just (rId, q),) <$> case msg of
18921909 Message {msgTs}
18931910 | maybe True (systemSeconds msgTs >= ) old_ -> do
18941911 writeMsg ms q False msg >>= \ case
18951912 Just _ -> pure (stored + 1 , expired, overQuota)
1896- Nothing -> do
1913+ Nothing -> liftIO $ do
1914+ when tty $ putStrLn " "
18971915 logError $ decodeLatin1 $ " message queue " <> strEncode rId <> " is full, message not restored: " <> strEncode (messageId msg)
1898- pure (stored, expired, overQuota)
1916+ pure counts
18991917 | otherwise -> pure (stored, expired + 1 , overQuota)
19001918 MessageQuota {} ->
19011919 -- queue was over quota at some point,
@@ -1907,8 +1925,13 @@ importMessages tty ms f old_ = do
19071925 withPeekMsgQueue ms q " mergeQuotaMsgs" $ maybe (pure () ) $ \ case
19081926 (mq, MessageQuota {}) -> tryDeleteMsg_ q mq False
19091927 _ -> pure ()
1910- msgErr :: Show e => String -> e -> String
1911- msgErr op e = op <> " error (" <> show e <> " ): " <> B. unpack (B. take 100 s)
1928+ warnOrExit e
1929+ | skipWarnings = logWarn e'
1930+ | otherwise = do
1931+ logWarn $ e' <> " , start with --skip-warnings option to ignore this error"
1932+ exitFailure
1933+ where
1934+ e' = " warning restoring messages: " <> e
19121935
19131936printMessageStats :: T. Text -> MessageStats -> IO ()
19141937printMessageStats name MessageStats {storedMsgsCount, expiredMsgsCount, storedQueues} =
0 commit comments