2022-02-16 23:24:48 +00:00
|
|
|
{-# LANGUAGE CPP #-}
|
2023-09-02 23:34:00 +01:00
|
|
|
{-# LANGUAGE ScopedTypeVariables #-}
|
2022-02-06 16:18:01 +00:00
|
|
|
|
|
|
|
module MobileTests where
|
|
|
|
|
2023-02-01 17:21:13 +00:00
|
|
|
import ChatTests.Utils
|
2022-02-06 16:18:01 +00:00
|
|
|
import Control.Monad.Except
|
2023-09-02 23:34:00 +01:00
|
|
|
import Crypto.Random (getRandomBytes)
|
|
|
|
import Data.ByteString (ByteString)
|
|
|
|
import qualified Data.ByteString as B
|
|
|
|
import qualified Data.ByteString.Char8 as BS
|
|
|
|
import Data.Word (Word8)
|
|
|
|
import Foreign.C
|
|
|
|
import Foreign.Marshal.Alloc (mallocBytes)
|
|
|
|
import Foreign.Ptr
|
2022-02-06 16:18:01 +00:00
|
|
|
import Simplex.Chat.Mobile
|
2023-09-02 23:34:00 +01:00
|
|
|
import Simplex.Chat.Mobile.Shared
|
|
|
|
import Simplex.Chat.Mobile.WebRTC
|
2022-02-06 16:18:01 +00:00
|
|
|
import Simplex.Chat.Store
|
2023-06-18 10:20:11 +01:00
|
|
|
import Simplex.Chat.Store.Profiles
|
2023-01-13 13:54:07 +04:00
|
|
|
import Simplex.Chat.Types (AgentUserId (..), Profile (..))
|
2023-03-27 18:34:48 +01:00
|
|
|
import Simplex.Messaging.Agent.Store.SQLite (MigrationConfirmation (..))
|
2023-09-02 23:34:00 +01:00
|
|
|
import qualified Simplex.Messaging.Crypto as C
|
|
|
|
import Simplex.Messaging.Encoding.String
|
2023-01-31 11:07:48 +00:00
|
|
|
import System.FilePath ((</>))
|
2022-02-06 16:18:01 +00:00
|
|
|
import Test.Hspec
|
|
|
|
|
2023-09-02 23:34:00 +01:00
|
|
|
mobileTests :: HasCallStack => SpecWith FilePath
|
2022-02-06 16:18:01 +00:00
|
|
|
mobileTests = do
|
|
|
|
describe "mobile API" $ do
|
|
|
|
it "start new chat without user" testChatApiNoUser
|
2023-07-13 23:48:25 +01:00
|
|
|
it "start new chat with existing user" testChatApi
|
2023-09-02 23:34:00 +01:00
|
|
|
fit "should encrypt/decrypt WebRTC frames" testMediaApi
|
|
|
|
fit "should encrypt/decrypt WebRTC frames via C API" testMediaCApi
|
2022-02-06 16:18:01 +00:00
|
|
|
|
|
|
|
noActiveUser :: String
|
2022-04-12 12:24:34 +01:00
|
|
|
#if defined(darwin_HOST_OS) && defined(swiftJSON)
|
2022-02-06 16:18:01 +00:00
|
|
|
noActiveUser = "{\"resp\":{\"chatCmdError\":{\"chatError\":{\"error\":{\"errorType\":{\"noActiveUser\":{}}}}}}}"
|
2022-02-16 23:24:48 +00:00
|
|
|
#else
|
|
|
|
noActiveUser = "{\"resp\":{\"type\":\"chatCmdError\",\"chatError\":{\"type\":\"error\",\"errorType\":{\"type\":\"noActiveUser\"}}}}"
|
|
|
|
#endif
|
2022-02-06 16:18:01 +00:00
|
|
|
|
|
|
|
activeUserExists :: String
|
2022-04-12 12:24:34 +01:00
|
|
|
#if defined(darwin_HOST_OS) && defined(swiftJSON)
|
2023-07-26 14:49:35 +04:00
|
|
|
activeUserExists = "{\"resp\":{\"chatCmdError\":{\"user_\":{\"userId\":1,\"agentUserId\":\"1\",\"userContactId\":1,\"localDisplayName\":\"alice\",\"profile\":{\"profileId\":1,\"displayName\":\"alice\",\"fullName\":\"Alice\",\"localAlias\":\"\"},\"fullPreferences\":{\"timedMessages\":{\"allow\":\"yes\"},\"fullDelete\":{\"allow\":\"no\"},\"reactions\":{\"allow\":\"yes\"},\"voice\":{\"allow\":\"yes\"},\"calls\":{\"allow\":\"yes\"}},\"activeUser\":true,\"showNtfs\":true,\"sendRcptsContacts\":true,\"sendRcptsSmallGroups\":true},\"chatError\":{\"error\":{\"errorType\":{\"userExists\":{\"contactName\":\"alice\"}}}}}}}"
|
2022-02-16 23:24:48 +00:00
|
|
|
#else
|
2023-07-26 14:49:35 +04:00
|
|
|
activeUserExists = "{\"resp\":{\"type\":\"chatCmdError\",\"user_\":{\"userId\":1,\"agentUserId\":\"1\",\"userContactId\":1,\"localDisplayName\":\"alice\",\"profile\":{\"profileId\":1,\"displayName\":\"alice\",\"fullName\":\"Alice\",\"localAlias\":\"\"},\"fullPreferences\":{\"timedMessages\":{\"allow\":\"yes\"},\"fullDelete\":{\"allow\":\"no\"},\"reactions\":{\"allow\":\"yes\"},\"voice\":{\"allow\":\"yes\"},\"calls\":{\"allow\":\"yes\"}},\"activeUser\":true,\"showNtfs\":true,\"sendRcptsContacts\":true,\"sendRcptsSmallGroups\":true},\"chatError\":{\"type\":\"error\",\"errorType\":{\"type\":\"userExists\",\"contactName\":\"alice\"}}}}"
|
2022-02-16 23:24:48 +00:00
|
|
|
#endif
|
2022-02-06 16:18:01 +00:00
|
|
|
|
|
|
|
activeUser :: String
|
2022-04-12 12:24:34 +01:00
|
|
|
#if defined(darwin_HOST_OS) && defined(swiftJSON)
|
2023-07-26 14:49:35 +04:00
|
|
|
activeUser = "{\"resp\":{\"activeUser\":{\"user\":{\"userId\":1,\"agentUserId\":\"1\",\"userContactId\":1,\"localDisplayName\":\"alice\",\"profile\":{\"profileId\":1,\"displayName\":\"alice\",\"fullName\":\"Alice\",\"localAlias\":\"\"},\"fullPreferences\":{\"timedMessages\":{\"allow\":\"yes\"},\"fullDelete\":{\"allow\":\"no\"},\"reactions\":{\"allow\":\"yes\"},\"voice\":{\"allow\":\"yes\"},\"calls\":{\"allow\":\"yes\"}},\"activeUser\":true,\"showNtfs\":true,\"sendRcptsContacts\":true,\"sendRcptsSmallGroups\":true}}}}"
|
2022-02-16 23:24:48 +00:00
|
|
|
#else
|
2023-07-26 14:49:35 +04:00
|
|
|
activeUser = "{\"resp\":{\"type\":\"activeUser\",\"user\":{\"userId\":1,\"agentUserId\":\"1\",\"userContactId\":1,\"localDisplayName\":\"alice\",\"profile\":{\"profileId\":1,\"displayName\":\"alice\",\"fullName\":\"Alice\",\"localAlias\":\"\"},\"fullPreferences\":{\"timedMessages\":{\"allow\":\"yes\"},\"fullDelete\":{\"allow\":\"no\"},\"reactions\":{\"allow\":\"yes\"},\"voice\":{\"allow\":\"yes\"},\"calls\":{\"allow\":\"yes\"}},\"activeUser\":true,\"showNtfs\":true,\"sendRcptsContacts\":true,\"sendRcptsSmallGroups\":true}}}"
|
2022-02-16 23:24:48 +00:00
|
|
|
#endif
|
|
|
|
|
|
|
|
chatStarted :: String
|
2022-04-12 12:24:34 +01:00
|
|
|
#if defined(darwin_HOST_OS) && defined(swiftJSON)
|
2022-02-16 23:24:48 +00:00
|
|
|
chatStarted = "{\"resp\":{\"chatStarted\":{}}}"
|
|
|
|
#else
|
|
|
|
chatStarted = "{\"resp\":{\"type\":\"chatStarted\"}}"
|
|
|
|
#endif
|
2022-02-06 16:18:01 +00:00
|
|
|
|
2022-06-11 11:52:55 +01:00
|
|
|
contactSubSummary :: String
|
|
|
|
#if defined(darwin_HOST_OS) && defined(swiftJSON)
|
2023-01-14 15:45:13 +04:00
|
|
|
contactSubSummary = "{\"resp\":{\"contactSubSummary\":{" <> userJSON <> ",\"contactSubscriptions\":[]}}}"
|
2022-06-11 11:52:55 +01:00
|
|
|
#else
|
2023-01-14 15:45:13 +04:00
|
|
|
contactSubSummary = "{\"resp\":{\"type\":\"contactSubSummary\"," <> userJSON <> ",\"contactSubscriptions\":[]}}"
|
2022-06-11 11:52:55 +01:00
|
|
|
#endif
|
|
|
|
|
2022-07-17 15:51:17 +01:00
|
|
|
memberSubSummary :: String
|
2022-06-11 11:52:55 +01:00
|
|
|
#if defined(darwin_HOST_OS) && defined(swiftJSON)
|
2023-01-14 15:45:13 +04:00
|
|
|
memberSubSummary = "{\"resp\":{\"memberSubSummary\":{" <> userJSON <> ",\"memberSubscriptions\":[]}}}"
|
2022-06-11 11:52:55 +01:00
|
|
|
#else
|
2023-01-14 15:45:13 +04:00
|
|
|
memberSubSummary = "{\"resp\":{\"type\":\"memberSubSummary\"," <> userJSON <> ",\"memberSubscriptions\":[]}}"
|
2022-06-11 11:52:55 +01:00
|
|
|
#endif
|
|
|
|
|
2022-10-13 17:12:22 +04:00
|
|
|
userContactSubSummary :: String
|
|
|
|
#if defined(darwin_HOST_OS) && defined(swiftJSON)
|
2023-01-14 15:45:13 +04:00
|
|
|
userContactSubSummary = "{\"resp\":{\"userContactSubSummary\":{" <> userJSON <> ",\"userContactSubscriptions\":[]}}}"
|
2022-10-13 17:12:22 +04:00
|
|
|
#else
|
2023-01-14 15:45:13 +04:00
|
|
|
userContactSubSummary = "{\"resp\":{\"type\":\"userContactSubSummary\"," <> userJSON <> ",\"userContactSubscriptions\":[]}}"
|
2022-10-13 17:12:22 +04:00
|
|
|
#endif
|
|
|
|
|
2022-06-11 11:52:55 +01:00
|
|
|
pendingSubSummary :: String
|
|
|
|
#if defined(darwin_HOST_OS) && defined(swiftJSON)
|
2023-01-14 15:45:13 +04:00
|
|
|
pendingSubSummary = "{\"resp\":{\"pendingSubSummary\":{" <> userJSON <> ",\"pendingSubscriptions\":[]}}}"
|
2022-06-11 11:52:55 +01:00
|
|
|
#else
|
2023-01-14 15:45:13 +04:00
|
|
|
pendingSubSummary = "{\"resp\":{\"type\":\"pendingSubSummary\"," <> userJSON <> ",\"pendingSubscriptions\":[]}}"
|
2022-06-11 11:52:55 +01:00
|
|
|
#endif
|
|
|
|
|
2023-01-14 15:45:13 +04:00
|
|
|
userJSON :: String
|
2023-07-26 14:49:35 +04:00
|
|
|
userJSON = "\"user\":{\"userId\":1,\"agentUserId\":\"1\",\"userContactId\":1,\"localDisplayName\":\"alice\",\"profile\":{\"profileId\":1,\"displayName\":\"alice\",\"fullName\":\"Alice\",\"localAlias\":\"\"},\"fullPreferences\":{\"timedMessages\":{\"allow\":\"yes\"},\"fullDelete\":{\"allow\":\"no\"},\"reactions\":{\"allow\":\"yes\"},\"voice\":{\"allow\":\"yes\"},\"calls\":{\"allow\":\"yes\"}},\"activeUser\":true,\"showNtfs\":true,\"sendRcptsContacts\":true,\"sendRcptsSmallGroups\":true}"
|
2023-01-14 15:45:13 +04:00
|
|
|
|
2022-06-11 11:52:55 +01:00
|
|
|
parsedMarkdown :: String
|
|
|
|
#if defined(darwin_HOST_OS) && defined(swiftJSON)
|
|
|
|
parsedMarkdown = "{\"formattedText\":[{\"format\":{\"bold\":{}},\"text\":\"hello\"}]}"
|
|
|
|
#else
|
|
|
|
parsedMarkdown = "{\"formattedText\":[{\"format\":{\"type\":\"bold\"},\"text\":\"hello\"}]}"
|
|
|
|
#endif
|
|
|
|
|
2023-01-31 11:07:48 +00:00
|
|
|
testChatApiNoUser :: FilePath -> IO ()
|
|
|
|
testChatApiNoUser tmp = do
|
|
|
|
let dbPrefix = tmp </> "1"
|
2023-03-27 18:34:48 +01:00
|
|
|
Right cc <- chatMigrateInit dbPrefix "" "yesUp"
|
|
|
|
Left (DBMErrorNotADatabase _) <- chatMigrateInit dbPrefix "myKey" "yesUp"
|
2022-02-06 16:18:01 +00:00
|
|
|
chatSendCmd cc "/u" `shouldReturn` noActiveUser
|
|
|
|
chatSendCmd cc "/_start" `shouldReturn` noActiveUser
|
2023-01-04 21:06:28 +04:00
|
|
|
chatSendCmd cc "/create user alice Alice" `shouldReturn` activeUser
|
2022-02-16 23:24:48 +00:00
|
|
|
chatSendCmd cc "/_start" `shouldReturn` chatStarted
|
2022-02-06 16:18:01 +00:00
|
|
|
|
2023-01-31 11:07:48 +00:00
|
|
|
testChatApi :: FilePath -> IO ()
|
|
|
|
testChatApi tmp = do
|
|
|
|
let dbPrefix = tmp </> "1"
|
2022-09-02 16:38:41 +01:00
|
|
|
f = chatStoreFile dbPrefix
|
2023-03-27 18:34:48 +01:00
|
|
|
Right st <- createChatStore f "myKey" MCYesUp
|
2023-01-13 13:54:07 +04:00
|
|
|
Right _ <- withTransaction st $ \db -> runExceptT $ createUserRecord db (AgentUserId 1) aliceProfile {preferences = Nothing} True
|
2023-03-27 18:34:48 +01:00
|
|
|
Right cc <- chatMigrateInit dbPrefix "myKey" "yesUp"
|
|
|
|
Left (DBMErrorNotADatabase _) <- chatMigrateInit dbPrefix "" "yesUp"
|
|
|
|
Left (DBMErrorNotADatabase _) <- chatMigrateInit dbPrefix "anotherKey" "yesUp"
|
2022-02-06 16:18:01 +00:00
|
|
|
chatSendCmd cc "/u" `shouldReturn` activeUser
|
2023-01-04 21:06:28 +04:00
|
|
|
chatSendCmd cc "/create user alice Alice" `shouldReturn` activeUserExists
|
2022-02-16 23:24:48 +00:00
|
|
|
chatSendCmd cc "/_start" `shouldReturn` chatStarted
|
2022-06-11 11:52:55 +01:00
|
|
|
chatRecvMsg cc `shouldReturn` contactSubSummary
|
2022-10-13 17:12:22 +04:00
|
|
|
chatRecvMsg cc `shouldReturn` userContactSubSummary
|
2022-07-17 15:51:17 +01:00
|
|
|
chatRecvMsg cc `shouldReturn` memberSubSummary
|
2022-06-11 11:52:55 +01:00
|
|
|
chatRecvMsgWait cc 10000 `shouldReturn` pendingSubSummary
|
|
|
|
chatRecvMsgWait cc 10000 `shouldReturn` ""
|
|
|
|
chatParseMarkdown "hello" `shouldBe` "{}"
|
|
|
|
chatParseMarkdown "*hello*" `shouldBe` parsedMarkdown
|
2023-09-02 23:34:00 +01:00
|
|
|
|
|
|
|
testMediaApi :: HasCallStack => FilePath -> IO ()
|
|
|
|
testMediaApi _ = do
|
|
|
|
key :: ByteString <- getRandomBytes 32
|
|
|
|
frame <- getRandomBytes 100
|
|
|
|
let keyStr = strEncode key
|
|
|
|
reserved = B.replicate (C.authTagSize + C.gcmIVSize) 0
|
|
|
|
frame' = frame <> reserved
|
|
|
|
Right encrypted <- runExceptT $ chatEncryptMedia keyStr frame'
|
|
|
|
encrypted `shouldNotBe` frame'
|
|
|
|
B.length encrypted `shouldBe` B.length frame'
|
|
|
|
runExceptT (chatDecryptMedia keyStr encrypted) `shouldReturn` Right frame'
|
|
|
|
|
|
|
|
testMediaCApi :: HasCallStack => FilePath -> IO ()
|
|
|
|
testMediaCApi _ = do
|
|
|
|
key :: ByteString <- getRandomBytes 32
|
|
|
|
frame <- getRandomBytes 100
|
|
|
|
let keyStr = strEncode key
|
|
|
|
reserved = B.replicate (C.authTagSize + C.gcmIVSize) 0
|
|
|
|
frame' = frame <> reserved
|
|
|
|
encrypted <- test cChatEncryptMedia keyStr frame'
|
|
|
|
encrypted `shouldNotBe` frame'
|
|
|
|
test cChatDecryptMedia keyStr encrypted `shouldReturn` frame'
|
|
|
|
where
|
|
|
|
test :: HasCallStack => (CString -> Ptr Word8 -> CInt -> IO CString) -> ByteString -> ByteString -> IO ByteString
|
|
|
|
test f keyStr frame = do
|
|
|
|
let len = B.length frame
|
|
|
|
cLen = fromIntegral len
|
|
|
|
ptr <- mallocBytes len
|
|
|
|
putByteString ptr frame
|
|
|
|
cKeyStr <- newCString $ BS.unpack keyStr
|
|
|
|
(f cKeyStr ptr cLen >>= peekCString) `shouldReturn` ""
|
|
|
|
getByteString ptr cLen
|