core: return error response when wrong passphrase is passed to start

This commit is contained in:
Evgeny Poberezkin 2023-09-27 21:15:19 +01:00
parent bbe329072e
commit ea319313f1
6 changed files with 34 additions and 27 deletions

View file

@ -34,6 +34,7 @@ import qualified Data.ByteString.Base64 as B64
import Data.ByteString.Char8 (ByteString) import Data.ByteString.Char8 (ByteString)
import qualified Data.ByteString.Char8 as B import qualified Data.ByteString.Char8 as B
import Data.Char (isSpace, toLower) import Data.Char (isSpace, toLower)
import Data.Composition ((.:))
import Data.Constraint (Dict (..)) import Data.Constraint (Dict (..))
import Data.Either (fromRight, rights) import Data.Either (fromRight, rights)
import Data.Fixed (div') import Data.Fixed (div')
@ -217,8 +218,8 @@ newChatController ChatDatabase {chatStore, agentStore} user cfg@ChatConfig {agen
where where
configServers :: DefaultAgentServers configServers :: DefaultAgentServers
configServers = configServers =
let smp' = fromMaybe (defaultServers.smp) (nonEmpty smpServers) let smp' = fromMaybe defaultServers.smp (nonEmpty smpServers)
xftp' = fromMaybe (defaultServers.xftp) (nonEmpty xftpServers) xftp' = fromMaybe defaultServers.xftp (nonEmpty xftpServers)
in defaultServers {smp = smp', xftp = xftp', netCfg = networkConfig} in defaultServers {smp = smp', xftp = xftp', netCfg = networkConfig}
agentServers :: ChatConfig -> IO InitialAgentServers agentServers :: ChatConfig -> IO InitialAgentServers
agentServers config@ChatConfig {defaultServers = defServers@DefaultAgentServers {ntf, netCfg}} = do agentServers config@ChatConfig {defaultServers = defServers@DefaultAgentServers {ntf, netCfg}} = do
@ -249,13 +250,9 @@ cfgServers p s = case p of
SPSMP -> s.smp SPSMP -> s.smp
SPXFTP -> s.xftp SPXFTP -> s.xftp
startChatController :: forall m. ChatMonad' m => ChatCtrlCfg -> m (Async ()) startChatController :: forall m. ChatMonad' m => Bool -> Bool -> Bool -> m (Async ())
startChatController ChatCtrlCfg {subConns, enableExpireCIs, startXFTPWorkers, openDBWithKey} = do startChatController subConns enableExpireCIs startXFTPWorkers = do
ChatController {chatStore, smpAgent} <- ask resumeAgentClient =<< asks smpAgent
forM_ openDBWithKey $ \(DBEncryptionKey dbKey) -> liftIO $ do
openSQLiteStore chatStore dbKey
openSQLiteStore (agentClientStore smpAgent) dbKey
resumeAgentClient smpAgent
unless subConns $ unless subConns $
chatWriteVar subscriptionMode SMOnlyCreate chatWriteVar subscriptionMode SMOnlyCreate
users <- fromRight [] <$> runExceptT (withStoreCtx' (Just "startChatController, getUsers") getUsers) users <- fromRight [] <$> runExceptT (withStoreCtx' (Just "startChatController, getUsers") getUsers)
@ -469,10 +466,17 @@ processChatCommand = \case
checkDeleteChatUser user' checkDeleteChatUser user'
withChatLock "deleteUser" . procCmd $ deleteChatUser user' delSMPQueues withChatLock "deleteUser" . procCmd $ deleteChatUser user' delSMPQueues
DeleteUser uName delSMPQueues viewPwd_ -> withUserName uName $ \userId -> APIDeleteUser userId delSMPQueues viewPwd_ DeleteUser uName delSMPQueues viewPwd_ -> withUserName uName $ \userId -> APIDeleteUser userId delSMPQueues viewPwd_
APIStartChat cfg -> withUser' $ \_ -> APIStartChat ChatCtrlCfg {subConns, enableExpireCIs, startXFTPWorkers, openDBWithKey} -> withUser' $ \_ ->
asks agentAsync >>= readTVarIO >>= \case asks agentAsync >>= readTVarIO >>= \case
Just _ -> pure CRChatRunning Just _ -> pure CRChatRunning
_ -> checkStoreNotChanged $ startChatController cfg $> CRChatStarted _ -> checkStoreNotChanged $ do
forM_ openDBWithKey $ \(DBEncryptionKey dbKey) -> do
ChatController {chatStore, smpAgent} <- ask
open chatStore dbKey
open (agentClientStore smpAgent) dbKey
startChatController subConns enableExpireCIs startXFTPWorkers $> CRChatStarted
where
open = handleDBError DBErrorOpen .: openSQLiteStore
APIStopChat closeStore -> do APIStopChat closeStore -> do
ask >>= (`stopChatController` closeStore) ask >>= (`stopChatController` closeStore)
pure CRChatStopped pure CRChatStopped

View file

@ -9,6 +9,7 @@ module Simplex.Chat.Archive
importArchive, importArchive,
deleteStorage, deleteStorage,
sqlCipherExport, sqlCipherExport,
handleDBError,
) )
where where
@ -139,17 +140,7 @@ sqlCipherExport DBEncryptionConfig {currentKey = DBEncryptionKey key, newKey = D
withDB (`SQL.exec` testSQL) DBErrorOpen withDB (`SQL.exec` testSQL) DBErrorOpen
atomically $ writeTVar dbEnc $ not (null key') atomically $ writeTVar dbEnc $ not (null key')
where where
withDB a err = withDB a err = handleDBError err $ bracket (SQL.open $ T.pack f) SQL.close a
liftIO (bracket (SQL.open $ T.pack f) SQL.close a $> Nothing)
`catch` checkSQLError
`catch` (\(e :: SomeException) -> sqliteError' e)
>>= mapM_ (throwDBError . err)
where
checkSQLError e = case SQL.sqlError e of
SQL.ErrorNotADatabase -> pure $ Just SQLiteErrorNotADatabase
_ -> sqliteError' e
sqliteError' :: Show e => e -> m (Maybe SQLiteError)
sqliteError' = pure . Just . SQLiteError . show
exportSQL = exportSQL =
T.unlines $ T.unlines $
keySQL key keySQL key
@ -166,3 +157,16 @@ sqlCipherExport DBEncryptionConfig {currentKey = DBEncryptionKey key, newKey = D
"SELECT count(*) FROM sqlite_master;" "SELECT count(*) FROM sqlite_master;"
] ]
keySQL k = ["PRAGMA key = " <> sqlString k <> ";" | not (null k)] keySQL k = ["PRAGMA key = " <> sqlString k <> ";" | not (null k)]
handleDBError :: forall m. ChatMonad m => (SQLiteError -> DatabaseError) -> IO () -> m ()
handleDBError err a =
(liftIO a $> Nothing)
`catch` checkSQLError
`catch` (\(e :: SomeException) -> sqliteError' e)
>>= mapM_ (throwDBError . err)
where
checkSQLError e = case SQL.sqlError e of
SQL.ErrorNotADatabase -> pure $ Just SQLiteErrorNotADatabase
_ -> sqliteError' e
sqliteError' :: Show e => e -> m (Maybe SQLiteError)
sqliteError' = pure . Just . SQLiteError . show

View file

@ -629,9 +629,6 @@ data ChatCtrlCfg = ChatCtrlCfg
} }
deriving (Show, Generic, FromJSON) deriving (Show, Generic, FromJSON)
defChatCtrlCfg :: ChatCtrlCfg
defChatCtrlCfg = ChatCtrlCfg True True True Nothing
newtype UserPwd = UserPwd {unUserPwd :: Text} newtype UserPwd = UserPwd {unUserPwd :: Text}
deriving (Eq, Show) deriving (Eq, Show)

View file

@ -35,7 +35,7 @@ runSimplexChat :: ChatOpts -> User -> ChatController -> (User -> ChatController
runSimplexChat ChatOpts {maintenance} u cc chat runSimplexChat ChatOpts {maintenance} u cc chat
| maintenance = wait =<< async (chat u cc) | maintenance = wait =<< async (chat u cc)
| otherwise = do | otherwise = do
a1 <- runReaderT (startChatController defChatCtrlCfg) cc a1 <- runReaderT (startChatController True True True) cc
a2 <- async $ chat u cc a2 <- async $ chat u cc
waitEither_ a1 a2 waitEither_ a1 a2

View file

@ -1648,7 +1648,7 @@ viewChatError logLevel = \case
DBErrorEncrypted -> ["error: chat database is already encrypted"] DBErrorEncrypted -> ["error: chat database is already encrypted"]
DBErrorPlaintext -> ["error: chat database is not encrypted"] DBErrorPlaintext -> ["error: chat database is not encrypted"]
DBErrorExport e -> ["error encrypting database: " <> sqliteError' e] DBErrorExport e -> ["error encrypting database: " <> sqliteError' e]
DBErrorOpen e -> ["error opening database after encryption: " <> sqliteError' e] DBErrorOpen e -> ["error opening database: " <> sqliteError' e]
e -> ["chat database error: " <> sShow e] e -> ["chat database error: " <> sShow e]
ChatErrorAgent err entity_ -> case err of ChatErrorAgent err entity_ -> case err of
CMD PROHIBITED -> [withConnEntity <> "error: command is prohibited"] CMD PROHIBITED -> [withConnEntity <> "error: command is prohibited"]

View file

@ -959,6 +959,8 @@ testDatabaseEncryption tmp = do
alice <## "chat stopped" alice <## "chat stopped"
alice ##> "/db key wrongkey nextkey" alice ##> "/db key wrongkey nextkey"
alice <## "error encrypting database: wrong passphrase or invalid database file" alice <## "error encrypting database: wrong passphrase or invalid database file"
alice ##> "/_start key=wrongkey"
alice <## "error opening database: wrong passphrase or invalid database file"
alice ##> "/_start key=mykey" alice ##> "/_start key=mykey"
alice <## "chat started" alice <## "chat started"
testChatWorking alice bob testChatWorking alice bob