mirror of
https://github.com/simplex-chat/simplex-chat.git
synced 2025-06-28 20:29:53 +00:00
core: incognito connections (#926)
This commit is contained in:
parent
404b7093b7
commit
5e67654249
19 changed files with 4408 additions and 460 deletions
|
@ -1,7 +1,6 @@
|
|||
{-# LANGUAGE DuplicateRecordFields #-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
{-# LANGUAGE GADTs #-}
|
||||
{-# LANGUAGE LambdaCase #-}
|
||||
{-# LANGUAGE NamedFieldPuns #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
|
@ -40,7 +39,7 @@ mySquaringBot _user cc = do
|
|||
race_ (forever $ void getLine) . forever $ do
|
||||
(_, resp) <- atomically . readTBQueue $ outputQ cc
|
||||
case resp of
|
||||
CRContactConnected contact -> do
|
||||
CRContactConnected contact _ -> do
|
||||
contactConnected contact
|
||||
void . sendMsg contact $ "Hello! I am a simple squaring bot - if you send me a number, I will calculate its square"
|
||||
CRNewChatItem (AChatItem _ SMDRcv (DirectChat contact) ChatItem {content}) -> do
|
||||
|
|
51
docs/rfcs/2022-08-10-incognito-connections.md
Normal file
51
docs/rfcs/2022-08-10-incognito-connections.md
Normal file
|
@ -0,0 +1,51 @@
|
|||
# Incognito connections
|
||||
|
||||
## Problems
|
||||
|
||||
Allow users to connect with incognito profile using the same user account without exposing main profile - either with randomly generated per connection profile / no profile, or custom profile created by user per connection. The latter option involves designing complex UI for creating profile on connection and seems to detract from UX, so we consider first two options.
|
||||
|
||||
## Proposal
|
||||
|
||||
Add incognito mode determining whether newly created connections are incognito, and a switch on connection pages affecting current connection.
|
||||
|
||||
Add API to turn incognito mode on/off - it is saved as part of ChatController state to allow terminal users to set it. We can save preference on mobile and set it on chat start. We can also persist it to database to carry across terminal sessions, but it seems unnecessary.
|
||||
|
||||
Parameterize `AddContact`, `Connect` and `ConnectSimplex` API - create connection as incognito based on incognito mode and parameter, parameter is given preference.
|
||||
|
||||
### Option 1 - random profile
|
||||
|
||||
Add nullable field `custom_user_profile_id` to `connections` table - `incognitoProfile: Maybe Profile` in `Connection` type; when connection is created as incognito on API call, random profile is created and saved to `profiles` table.
|
||||
|
||||
Incognito profile is created only with a display name, it can be:
|
||||
|
||||
- Some prefix followed by sequence of random character/digits
|
||||
- Passphrase-like (2-4 random words)
|
||||
- A name from a dictionary(ies)?
|
||||
- One of above chosen randomly.
|
||||
|
||||
We could generate other parts of profile (picture?) but it's not necessary for MVP.
|
||||
|
||||
When user initiates connection as incognito, incognito profile is sent as part of XInfo upon receiving CONF from joining user.
|
||||
|
||||
### Option 2 - no profile
|
||||
|
||||
Add `incognito` flag to `connections` table - `incognito: Bool` in `Connection` type.
|
||||
|
||||
Instead of XInfo both in `Connect` API and on receiving CONF when initiating, send a message that doesn't contain profile, e.g. XOk.
|
||||
|
||||
When saving connection profile (`saveConnInfo`) or processing contact request on receiving XOk / other message, contact generates a random profile for the user to distinguish from other connections. He is also able to mark this connection as incognito.
|
||||
|
||||
### Considerations
|
||||
|
||||
- Don't broadcast user profile updates to contacts with whom the user has established incognito connections.
|
||||
- Add indication on chat info page that connection was established as incognito, show profile name so the user knows how the contact sees him.
|
||||
- While profile names generated in option 1 may be distinguishable as incognito depending on generator, technically the fact that connection was established as incognito is not explicitly leaked, which is clear with option 2.
|
||||
- We could offer same random profile generator on creating profiles, which would blend users with such profile as permanent and users who chose to connect with incognito profile to an observer (i.e. the fact that user chooses to be incognito for this specific connection is no longer leaked, just that he chose to be incognito generally).
|
||||
- There's a use case for custom incognito profile created by user for a given connection in case user wants to hide the fact of incognito connection (leaked by distinguishable pattern in profile name or lack of profile), but it may better be solved by multi-profile.
|
||||
- Send incognito profile when accepting contact requests in incognito mode? Parameterize API and give option in dialog?
|
||||
|
||||
### Groups
|
||||
|
||||
- If host used user's incognito connection when inviting, save same field marking group as incognito in `groups` table?
|
||||
- Use incognito profile in XGrpMemInfo
|
||||
- Allow host to create group in incognito profile - all connections with members are created as incognito?
|
|
@ -31,6 +31,7 @@ dependencies:
|
|||
- network >= 3.1.2.7 && < 3.2
|
||||
- optparse-applicative >= 0.15 && < 0.17
|
||||
- process == 1.6.*
|
||||
- random >= 1.1 && < 1.3
|
||||
- simple-logger == 0.1.*
|
||||
- simplexmq >= 3.0
|
||||
- socks == 0.6.*
|
||||
|
|
|
@ -43,8 +43,10 @@ library
|
|||
Simplex.Chat.Migrations.M20220702_calls
|
||||
Simplex.Chat.Migrations.M20220715_groups_chat_item_id
|
||||
Simplex.Chat.Migrations.M20220811_chat_items_indices
|
||||
Simplex.Chat.Migrations.M20220812_incognito_profiles
|
||||
Simplex.Chat.Mobile
|
||||
Simplex.Chat.Options
|
||||
Simplex.Chat.ProfileGenerator
|
||||
Simplex.Chat.Protocol
|
||||
Simplex.Chat.Store
|
||||
Simplex.Chat.Styled
|
||||
|
@ -80,6 +82,7 @@ library
|
|||
, network >=3.1.2.7 && <3.2
|
||||
, optparse-applicative >=0.15 && <0.17
|
||||
, process ==1.6.*
|
||||
, random >=1.1 && <1.3
|
||||
, simple-logger ==0.1.*
|
||||
, simplexmq >=3.0
|
||||
, socks ==0.6.*
|
||||
|
@ -120,6 +123,7 @@ executable simplex-bot
|
|||
, network >=3.1.2.7 && <3.2
|
||||
, optparse-applicative >=0.15 && <0.17
|
||||
, process ==1.6.*
|
||||
, random >=1.1 && <1.3
|
||||
, simple-logger ==0.1.*
|
||||
, simplex-chat
|
||||
, simplexmq >=3.0
|
||||
|
@ -161,6 +165,7 @@ executable simplex-bot-advanced
|
|||
, network >=3.1.2.7 && <3.2
|
||||
, optparse-applicative >=0.15 && <0.17
|
||||
, process ==1.6.*
|
||||
, random >=1.1 && <1.3
|
||||
, simple-logger ==0.1.*
|
||||
, simplex-chat
|
||||
, simplexmq >=3.0
|
||||
|
@ -203,6 +208,7 @@ executable simplex-chat
|
|||
, network ==3.1.*
|
||||
, optparse-applicative >=0.15 && <0.17
|
||||
, process ==1.6.*
|
||||
, random >=1.1 && <1.3
|
||||
, simple-logger ==0.1.*
|
||||
, simplex-chat
|
||||
, simplexmq >=3.0
|
||||
|
@ -254,6 +260,7 @@ test-suite simplex-chat-test
|
|||
, network ==3.1.*
|
||||
, optparse-applicative >=0.15 && <0.17
|
||||
, process ==1.6.*
|
||||
, random >=1.1 && <1.3
|
||||
, simple-logger ==0.1.*
|
||||
, simplex-chat
|
||||
, simplexmq >=3.0
|
||||
|
|
|
@ -31,13 +31,12 @@ import Data.Either (fromRight)
|
|||
import Data.Fixed (div')
|
||||
import Data.Functor (($>))
|
||||
import Data.Int (Int64)
|
||||
import Data.List (find, isSuffixOf, sortBy, sortOn)
|
||||
import Data.List (find, isSuffixOf, sortOn)
|
||||
import Data.List.NonEmpty (NonEmpty, nonEmpty)
|
||||
import qualified Data.List.NonEmpty as L
|
||||
import Data.Map.Strict (Map)
|
||||
import qualified Data.Map.Strict as M
|
||||
import Data.Maybe (fromMaybe, isJust, isNothing, mapMaybe)
|
||||
import Data.Ord (comparing)
|
||||
import Data.Text (Text)
|
||||
import qualified Data.Text as T
|
||||
import Data.Time.Clock (UTCTime, diffUTCTime, getCurrentTime, nominalDiffTimeToSeconds)
|
||||
|
@ -51,6 +50,7 @@ import Simplex.Chat.Controller
|
|||
import Simplex.Chat.Markdown
|
||||
import Simplex.Chat.Messages
|
||||
import Simplex.Chat.Options
|
||||
import Simplex.Chat.ProfileGenerator (generateRandomProfile)
|
||||
import Simplex.Chat.Protocol
|
||||
import Simplex.Chat.Store
|
||||
import Simplex.Chat.Types
|
||||
|
@ -143,8 +143,9 @@ newChatController chatStore user cfg@ChatConfig {agentConfig = aCfg, tbqSize, de
|
|||
rcvFiles <- newTVarIO M.empty
|
||||
currentCalls <- atomically TM.empty
|
||||
filesFolder <- newTVarIO Nothing
|
||||
incognitoMode <- newTVarIO False
|
||||
chatStoreChanged <- newTVarIO False
|
||||
pure ChatController {activeTo, firstTime, currentUser, smpAgent, agentAsync, chatStore, chatStoreChanged, idsDrg, inputQ, outputQ, notifyQ, chatLock, sndFiles, rcvFiles, currentCalls, config, sendNotification, filesFolder}
|
||||
pure ChatController {activeTo, firstTime, currentUser, smpAgent, agentAsync, chatStore, chatStoreChanged, idsDrg, inputQ, outputQ, notifyQ, chatLock, sndFiles, rcvFiles, currentCalls, config, sendNotification, incognitoMode, filesFolder}
|
||||
where
|
||||
resolveServers :: InitialAgentServers -> IO InitialAgentServers
|
||||
resolveServers ss@InitialAgentServers {smp = defaultSMPServers} = case nonEmpty smpServers of
|
||||
|
@ -233,6 +234,10 @@ processChatCommand = \case
|
|||
ff <- asks filesFolder
|
||||
atomically . writeTVar ff $ Just filesFolder'
|
||||
pure CRCmdOk
|
||||
SetIncognito onOff -> do
|
||||
incognito <- asks incognitoMode
|
||||
atomically . writeTVar incognito $ onOff
|
||||
pure CRCmdOk
|
||||
APIExportArchive cfg -> checkChatStopped $ exportArchive cfg $> CRCmdOk
|
||||
APIImportArchive cfg -> checkChatStopped $ importArchive cfg >> setStoreChanged $> CRCmdOk
|
||||
APIDeleteStorage -> checkChatStopped $ deleteStorage >> setStoreChanged $> CRCmdOk
|
||||
|
@ -254,16 +259,14 @@ processChatCommand = \case
|
|||
pure . CRNewChatItem $ AChatItem SCTDirect SMDSnd (DirectChat ct) ci
|
||||
where
|
||||
setupSndFileTransfer :: Contact -> m (Maybe (FileInvitation, CIFile 'MDSnd))
|
||||
setupSndFileTransfer ct = case file_ of
|
||||
Nothing -> pure Nothing
|
||||
Just file -> do
|
||||
(fileSize, chSize) <- checkSndFile file
|
||||
(agentConnId, fileConnReq) <- withAgent (`createConnection` SCMInvitation)
|
||||
let fileName = takeFileName file
|
||||
fileInvitation = FileInvitation {fileName, fileSize, fileConnReq = Just fileConnReq}
|
||||
fileId <- withStore' $ \db -> createSndFileTransfer db userId ct file fileInvitation agentConnId chSize
|
||||
let ciFile = CIFile {fileId, fileName, fileSize, filePath = Just file, fileStatus = CIFSSndStored}
|
||||
pure $ Just (fileInvitation, ciFile)
|
||||
setupSndFileTransfer ct = forM file_ $ \file -> do
|
||||
(fileSize, chSize) <- checkSndFile file
|
||||
(agentConnId, fileConnReq) <- withAgent (`createConnection` SCMInvitation)
|
||||
let fileName = takeFileName file
|
||||
fileInvitation = FileInvitation {fileName, fileSize, fileConnReq = Just fileConnReq}
|
||||
fileId <- withStore' $ \db -> createSndFileTransfer db userId ct file fileInvitation agentConnId chSize
|
||||
let ciFile = CIFile {fileId, fileName, fileSize, filePath = Just file, fileStatus = CIFSSndStored}
|
||||
pure (fileInvitation, ciFile)
|
||||
prepareMsg :: Maybe FileInvitation -> m (MsgContainer, Maybe (CIQuote 'CTDirect))
|
||||
prepareMsg fileInvitation_ = case quotedItemId_ of
|
||||
Nothing -> pure (MCSimple (ExtMsgContent mc fileInvitation_), Nothing)
|
||||
|
@ -291,15 +294,13 @@ processChatCommand = \case
|
|||
pure . CRNewChatItem $ AChatItem SCTGroup SMDSnd (GroupChat gInfo) ci
|
||||
where
|
||||
setupSndFileTransfer :: GroupInfo -> m (Maybe (FileInvitation, CIFile 'MDSnd))
|
||||
setupSndFileTransfer gInfo = case file_ of
|
||||
Nothing -> pure Nothing
|
||||
Just file -> do
|
||||
(fileSize, chSize) <- checkSndFile file
|
||||
let fileName = takeFileName file
|
||||
fileInvitation = FileInvitation {fileName, fileSize, fileConnReq = Nothing}
|
||||
fileId <- withStore' $ \db -> createSndGroupFileTransfer db userId gInfo file fileInvitation chSize
|
||||
let ciFile = CIFile {fileId, fileName, fileSize, filePath = Just file, fileStatus = CIFSSndStored}
|
||||
pure $ Just (fileInvitation, ciFile)
|
||||
setupSndFileTransfer gInfo = forM file_ $ \file -> do
|
||||
(fileSize, chSize) <- checkSndFile file
|
||||
let fileName = takeFileName file
|
||||
fileInvitation = FileInvitation {fileName, fileSize, fileConnReq = Nothing}
|
||||
fileId <- withStore' $ \db -> createSndGroupFileTransfer db userId gInfo file fileInvitation chSize
|
||||
let ciFile = CIFile {fileId, fileName, fileSize, filePath = Just file, fileStatus = CIFSSndStored}
|
||||
pure (fileInvitation, ciFile)
|
||||
prepareMsg :: Maybe FileInvitation -> GroupMember -> m (MsgContainer, Maybe (CIQuote 'CTGroup))
|
||||
prepareMsg fileInvitation_ membership = case quotedItemId_ of
|
||||
Nothing -> pure (MCSimple (ExtMsgContent mc fileInvitation_), Nothing)
|
||||
|
@ -597,11 +598,17 @@ processChatCommand = \case
|
|||
APISetNetworkConfig cfg -> withUser' $ \_ -> withAgent (`setNetworkConfig` cfg) $> CRCmdOk
|
||||
APIGetNetworkConfig -> CRNetworkConfig <$> withUser' (\_ -> withAgent getNetworkConfig)
|
||||
APIContactInfo contactId -> withUser $ \User {userId} -> do
|
||||
ct <- withStore $ \db -> getContact db userId contactId
|
||||
CRContactInfo ct <$> withAgent (`getConnectionServers` contactConnId ct)
|
||||
APIGroupMemberInfo gId gMemberId -> withUser $ \user -> do
|
||||
(g, m) <- withStore $ \db -> (,) <$> getGroupInfo db user gId <*> getGroupMember db user gId gMemberId
|
||||
CRGroupMemberInfo g m <$> mapM (withAgent . flip getConnectionServers) (memberConnId m)
|
||||
-- [incognito] print user's incognito profile for this contact
|
||||
ct@Contact {activeConn = Connection {customUserProfileId}} <- withStore $ \db -> getContact db userId contactId
|
||||
incognitoProfile <- forM customUserProfileId $ \profileId -> withStore (\db -> getProfileById db userId profileId)
|
||||
connectionStats <- withAgent (`getConnectionServers` contactConnId ct)
|
||||
pure $ CRContactInfo ct connectionStats incognitoProfile
|
||||
APIGroupMemberInfo gId gMemberId -> withUser $ \user@User {userId} -> do
|
||||
-- [incognito] print group member main profile
|
||||
(g, m@GroupMember {memberContactProfileId}) <- withStore $ \db -> (,) <$> getGroupInfo db user gId <*> getGroupMember db user gId gMemberId
|
||||
mainProfile <- if memberIncognito m then Just <$> withStore (\db -> getProfileById db userId memberContactProfileId) else pure Nothing
|
||||
connectionStats <- mapM (withAgent . flip getConnectionServers) (memberConnId m)
|
||||
pure $ CRGroupMemberInfo g m connectionStats mainProfile
|
||||
ContactInfo cName -> withUser $ \User {userId} -> do
|
||||
contactId <- withStore $ \db -> getContactIdByName db userId cName
|
||||
processChatCommand $ APIContactInfo contactId
|
||||
|
@ -611,20 +618,29 @@ processChatCommand = \case
|
|||
ChatHelp section -> pure $ CRChatHelp section
|
||||
Welcome -> withUser $ pure . CRWelcome
|
||||
AddContact -> withUser $ \User {userId} -> withChatLock . procCmd $ do
|
||||
-- [incognito] generate profile for connection
|
||||
incognito <- readTVarIO =<< asks incognitoMode
|
||||
incognitoProfile <- if incognito then Just <$> liftIO generateRandomProfile else pure Nothing
|
||||
(connId, cReq) <- withAgent (`createConnection` SCMInvitation)
|
||||
conn <- withStore' $ \db -> createDirectConnection db userId connId ConnNew
|
||||
conn <- withStore' $ \db -> createDirectConnection db userId connId ConnNew incognitoProfile
|
||||
toView $ CRNewContactConnection conn
|
||||
pure $ CRInvitation cReq
|
||||
Connect (Just (ACR SCMInvitation cReq)) -> withUser $ \User {userId, profile} -> withChatLock . procCmd $ do
|
||||
connId <- withAgent $ \a -> joinConnection a cReq . directMessage $ XInfo profile
|
||||
conn <- withStore' $ \db -> createDirectConnection db userId connId ConnJoined
|
||||
-- [incognito] generate profile to send
|
||||
incognito <- readTVarIO =<< asks incognitoMode
|
||||
incognitoProfile <- if incognito then Just <$> liftIO generateRandomProfile else pure Nothing
|
||||
let profileToSend = fromMaybe (fromLocalProfile profile) incognitoProfile
|
||||
connId <- withAgent $ \a -> joinConnection a cReq . directMessage $ XInfo profileToSend
|
||||
conn <- withStore' $ \db -> createDirectConnection db userId connId ConnJoined incognitoProfile
|
||||
toView $ CRNewContactConnection conn
|
||||
pure CRSentConfirmation
|
||||
Connect (Just (ACR SCMContact cReq)) -> withUser $ \User {userId, profile} ->
|
||||
connectViaContact userId cReq profile
|
||||
-- [incognito] generate profile to send
|
||||
connectViaContact userId cReq $ fromLocalProfile profile
|
||||
Connect Nothing -> throwChatError CEInvalidConnReq
|
||||
ConnectSimplex -> withUser $ \User {userId, profile} ->
|
||||
connectViaContact userId adminContactReq profile
|
||||
-- [incognito] generate profile to send
|
||||
connectViaContact userId adminContactReq $ fromLocalProfile profile
|
||||
DeleteContact cName -> withUser $ \User {userId} -> do
|
||||
contactId <- withStore $ \db -> getContactIdByName db userId cName
|
||||
processChatCommand $ APIDeleteChat (ChatRef CTDirect contactId)
|
||||
|
@ -686,29 +702,37 @@ processChatCommand = \case
|
|||
processChatCommand $ APIUpdateChatItem chatRef editedItemId mc
|
||||
NewGroup gProfile -> withUser $ \user -> do
|
||||
gVar <- asks idsDrg
|
||||
CRGroupCreated <$> withStore (\db -> createNewGroup db gVar user gProfile)
|
||||
-- [incognito] create membership with incognito profile
|
||||
incognito <- readTVarIO =<< asks incognitoMode
|
||||
incognitoProfile <- if incognito then Just <$> liftIO generateRandomProfile else pure Nothing
|
||||
groupInfo <- withStore (\db -> createNewGroup db gVar user gProfile incognitoProfile)
|
||||
pure $ CRGroupCreated groupInfo incognitoProfile
|
||||
APIAddMember groupId contactId memRole -> withUser $ \user@User {userId} -> withChatLock $ do
|
||||
-- TODO for large groups: no need to load all members to determine if contact is a member
|
||||
(group, contact) <- withStore $ \db -> (,) <$> getGroup db user groupId <*> getContact db userId contactId
|
||||
-- [incognito] forbid to invite contact to whom user is connected as incognito if user's membership is not incognito
|
||||
let Group gInfo@GroupInfo {localDisplayName, groupProfile, membership} members = group
|
||||
GroupMember {memberRole = userRole, memberId = userMemberId} = membership
|
||||
Contact {localDisplayName = cName} = contact
|
||||
when (contactConnIncognito contact && not (memberIncognito membership)) $ throwChatError CEGroupNotIncognitoCantInvite
|
||||
when (userRole < GRAdmin || userRole < memRole) $ throwChatError CEGroupUserRole
|
||||
when (memberStatus membership == GSMemInvited) $ throwChatError (CEGroupNotJoined gInfo)
|
||||
unless (memberActive membership) $ throwChatError CEGroupMemberNotActive
|
||||
let sendInvitation member@GroupMember {groupMemberId, memberId} cReq = do
|
||||
let groupInv = GroupInvitation (MemberIdRole userMemberId userRole) (MemberIdRole memberId memRole) cReq groupProfile
|
||||
-- [incognito] if membership is incognito, send its incognito profile in GroupInvitation
|
||||
let incognitoProfile = if memberIncognito membership then Just (fromLocalProfile $ memberProfile membership) else Nothing
|
||||
groupInv = GroupInvitation (MemberIdRole userMemberId userRole) incognitoProfile (MemberIdRole memberId memRole) cReq groupProfile
|
||||
msg <- sendDirectContactMessage contact $ XGrpInv groupInv
|
||||
let content = CISndGroupInvitation (CIGroupInvitation {groupId, groupMemberId, localDisplayName, groupProfile, status = CIGISPending}) memRole
|
||||
let content = CISndGroupInvitation (CIGroupInvitation {groupId, groupMemberId, localDisplayName, groupProfile, status = CIGISPending, invitedIncognito = Just $ memberIncognito membership}) memRole
|
||||
ci <- saveSndChatItem user (CDDirectSnd contact) msg content Nothing Nothing
|
||||
toView . CRNewChatItem $ AChatItem SCTDirect SMDSnd (DirectChat contact) ci
|
||||
setActive $ ActiveG localDisplayName
|
||||
pure $ CRSentGroupInvitation gInfo contact member
|
||||
pure $ CRSentGroupInvitation gInfo contact member incognitoProfile
|
||||
case contactMember contact members of
|
||||
Nothing -> do
|
||||
gVar <- asks idsDrg
|
||||
(agentConnId, cReq) <- withAgent (`createConnection` SCMInvitation)
|
||||
member <- withStore $ \db -> createContactMember db gVar user groupId contact memRole agentConnId cReq
|
||||
member <- withStore $ \db -> createNewContactMember db gVar user groupId contact memRole agentConnId cReq
|
||||
sendInvitation member cReq
|
||||
Just member@GroupMember {groupMemberId, memberStatus}
|
||||
| memberStatus == GSMemInvited ->
|
||||
|
@ -719,13 +743,30 @@ processChatCommand = \case
|
|||
APIJoinGroup groupId -> withUser $ \user@User {userId} -> do
|
||||
ReceivedGroupInvitation {fromMember, connRequest, groupInfo = g@GroupInfo {membership}} <- withStore $ \db -> getGroupInvitation db user groupId
|
||||
withChatLock . procCmd $ do
|
||||
agentConnId <- withAgent $ \a -> joinConnection a connRequest . directMessage . XGrpAcpt $ memberId (membership :: GroupMember)
|
||||
-- [incognito] if (incognito mode is enabled OR direct connection with host is incognito) [AND membership is not incognito] update membership to use incognito profile
|
||||
incognito <- readTVarIO =<< asks incognitoMode
|
||||
hostConnIncognito <- case (incognito, memberContactId fromMember) of
|
||||
(True, _) -> pure True -- we don't need to check whether connection with host is incognito if incognito mode is on
|
||||
(_, Just hostContactId) -> do
|
||||
hostContact <- withStore $ \db -> getContact db userId hostContactId
|
||||
pure $ contactConnIncognito hostContact
|
||||
_ -> pure False
|
||||
g'@GroupInfo {membership = membership'} <-
|
||||
if (incognito || hostConnIncognito) && not (memberIncognito membership)
|
||||
then do
|
||||
incognitoProfile <- liftIO generateRandomProfile
|
||||
membership' <- withStore $ \db -> createMemberIncognitoProfile db userId membership (Just incognitoProfile)
|
||||
pure g {membership = membership'}
|
||||
else pure g
|
||||
-- [incognito] if membership is incognito, send its incognito profile in XGrpAcpt
|
||||
let incognitoProfile = if memberIncognito membership' then Just (fromLocalProfile $ memberProfile membership') else Nothing
|
||||
agentConnId <- withAgent $ \a -> joinConnection a connRequest . directMessage $ XGrpAcpt (memberId (membership' :: GroupMember)) incognitoProfile
|
||||
withStore' $ \db -> do
|
||||
createMemberConnection db userId fromMember agentConnId
|
||||
updateGroupMemberStatus db userId fromMember GSMemAccepted
|
||||
updateGroupMemberStatus db userId membership GSMemAccepted
|
||||
updateGroupMemberStatus db userId membership' GSMemAccepted
|
||||
updateCIGroupInvitationStatus user
|
||||
pure $ CRUserAcceptedGroupSent g {membership = membership {memberStatus = GSMemAccepted}}
|
||||
pure $ CRUserAcceptedGroupSent g' {membership = membership' {memberStatus = GSMemAccepted}}
|
||||
where
|
||||
updateCIGroupInvitationStatus user@User {userId} = do
|
||||
AChatItem _ _ cInfo ChatItem {content, meta = CIMeta {itemId}} <- withStore $ \db -> getChatItemByGroupId db user groupId
|
||||
|
@ -750,7 +791,7 @@ processChatCommand = \case
|
|||
withStore' $ \db -> deleteGroupMember db user m
|
||||
_ -> do
|
||||
msg <- sendGroupMessage gInfo members $ XGrpMemDel mId
|
||||
ci <- saveSndChatItem user (CDGroupSnd gInfo) msg (CISndGroupEvent $ SGEMemberDeleted memberId memberProfile) Nothing Nothing
|
||||
ci <- saveSndChatItem user (CDGroupSnd gInfo) msg (CISndGroupEvent $ SGEMemberDeleted memberId (fromLocalProfile memberProfile)) Nothing Nothing
|
||||
toView . CRNewChatItem $ AChatItem SCTGroup SMDSnd (GroupChat gInfo) ci
|
||||
deleteMemberConnection m
|
||||
withStore' $ \db -> updateGroupMemberStatus db userId m GSMemRemoved
|
||||
|
@ -861,12 +902,12 @@ processChatCommand = \case
|
|||
pure $ CRRcvFileCancelled ftr
|
||||
FileStatus fileId ->
|
||||
CRFileTransferStatus <$> withUser (\user -> withStore $ \db -> getFileTransferProgress db user fileId)
|
||||
ShowProfile -> withUser $ \User {profile} -> pure $ CRUserProfile profile
|
||||
ShowProfile -> withUser $ \User {profile} -> pure $ CRUserProfile (fromLocalProfile profile)
|
||||
UpdateProfile displayName fullName -> withUser $ \user@User {profile} -> do
|
||||
let p = (profile :: Profile) {displayName = displayName, fullName = fullName}
|
||||
let p = (fromLocalProfile profile :: Profile) {displayName = displayName, fullName = fullName}
|
||||
updateProfile user p
|
||||
UpdateProfileImage image -> withUser $ \user@User {profile} -> do
|
||||
let p = (profile :: Profile) {image}
|
||||
let p = (fromLocalProfile profile :: Profile) {image}
|
||||
updateProfile user p
|
||||
QuitChat -> liftIO exitSuccess
|
||||
ShowVersion -> pure $ CRVersionInfo versionNumber
|
||||
|
@ -910,10 +951,18 @@ processChatCommand = \case
|
|||
(_, xContactId_) -> procCmd $ do
|
||||
let randomXContactId = XContactId <$> (asks idsDrg >>= liftIO . (`randomBytes` 16))
|
||||
xContactId <- maybe randomXContactId pure xContactId_
|
||||
connId <- withAgent $ \a -> joinConnection a cReq $ directMessage (XContact profile $ Just xContactId)
|
||||
conn <- withStore' $ \db -> createConnReqConnection db userId connId cReqHash xContactId
|
||||
-- [incognito] generate profile to send
|
||||
-- if user makes a contact request using main profile, then turns on incognito mode and repeats the request,
|
||||
-- an incognito profile will be sent even though the address holder will have user's main profile received as well;
|
||||
-- we ignore this edge case as we already allow profile updates on repeat contact requests;
|
||||
-- alternatively we can re-send the main profile even if incognito mode is enabled
|
||||
incognito <- readTVarIO =<< asks incognitoMode
|
||||
incognitoProfile <- if incognito then Just <$> liftIO generateRandomProfile else pure Nothing
|
||||
let profileToSend = fromMaybe profile incognitoProfile
|
||||
connId <- withAgent $ \a -> joinConnection a cReq $ directMessage (XContact profileToSend $ Just xContactId)
|
||||
conn <- withStore' $ \db -> createConnReqConnection db userId connId cReqHash xContactId incognitoProfile
|
||||
toView $ CRNewContactConnection conn
|
||||
pure CRSentInvitation
|
||||
pure $ CRSentInvitation incognitoProfile
|
||||
contactMember :: Contact -> [GroupMember] -> Maybe GroupMember
|
||||
contactMember Contact {contactId} =
|
||||
find $ \GroupMember {memberContactId = cId, memberStatus = s} ->
|
||||
|
@ -924,17 +973,20 @@ processChatCommand = \case
|
|||
unlessM (doesFileExist fsFilePath) . throwChatError $ CEFileNotFound f
|
||||
(,) <$> getFileSize fsFilePath <*> asks (fileChunkSize . config)
|
||||
updateProfile :: User -> Profile -> m ChatResponse
|
||||
updateProfile user@User {profile = p} p'@Profile {displayName}
|
||||
| p' == p = pure CRUserProfileNoChange
|
||||
updateProfile user@User {profile = p@LocalProfile {profileId}} p'@Profile {displayName}
|
||||
| p' == fromLocalProfile p = pure CRUserProfileNoChange
|
||||
| otherwise = do
|
||||
withStore $ \db -> updateUserProfile db user p'
|
||||
let user' = (user :: User) {localDisplayName = displayName, profile = p'}
|
||||
let user' = (user :: User) {localDisplayName = displayName, profile = toLocalProfile profileId p'}
|
||||
asks currentUser >>= atomically . (`writeTVar` Just user')
|
||||
contacts <- filter isReady <$> withStore' (`getUserContacts` user)
|
||||
-- [incognito] filter out contacts with whom user has incognito connections
|
||||
contacts <-
|
||||
filter (\ct -> isReady ct && not (contactConnIncognito ct))
|
||||
<$> withStore' (`getUserContacts` user)
|
||||
withChatLock . procCmd $ do
|
||||
forM_ contacts $ \ct ->
|
||||
void (sendDirectContactMessage ct $ XInfo p') `catchError` (toView . CRChatError)
|
||||
pure $ CRUserProfileUpdated p p'
|
||||
pure $ CRUserProfileUpdated (fromLocalProfile p) p'
|
||||
isReady :: Contact -> Bool
|
||||
isReady ct =
|
||||
let s = connStatus $ activeConn (ct :: Contact)
|
||||
|
@ -1117,8 +1169,12 @@ acceptFileReceive user@User {userId} RcvFileTransfer {fileId, fileInvitation = F
|
|||
|
||||
acceptContactRequest :: ChatMonad m => User -> UserContactRequest -> m Contact
|
||||
acceptContactRequest User {userId, profile} UserContactRequest {agentInvitationId = AgentInvId invId, localDisplayName = cName, profileId, profile = p, userContactLinkId, xContactId} = do
|
||||
connId <- withAgent $ \a -> acceptContact a invId . directMessage $ XInfo profile
|
||||
withStore' $ \db -> createAcceptedContact db userId connId cName profileId p userContactLinkId xContactId
|
||||
-- [incognito] generate profile to send, create connection with incognito profile
|
||||
incognito <- readTVarIO =<< asks incognitoMode
|
||||
incognitoProfile <- if incognito then Just <$> liftIO generateRandomProfile else pure Nothing
|
||||
let profileToSend = fromMaybe (fromLocalProfile profile) incognitoProfile
|
||||
connId <- withAgent $ \a -> acceptContact a invId . directMessage $ XInfo profileToSend
|
||||
withStore' $ \db -> createAcceptedContact db userId connId cName profileId p userContactLinkId xContactId incognitoProfile
|
||||
|
||||
agentSubscriber :: (MonadUnliftIO m, MonadReader ChatController m) => m ()
|
||||
agentSubscriber = do
|
||||
|
@ -1192,7 +1248,7 @@ subscribeUserConnections agentBatchSubscribe user = do
|
|||
groupSubsToView :: Map ConnId (Either AgentErrorType ()) -> [Group] -> Map ConnId GroupMember -> Bool -> m ()
|
||||
groupSubsToView rs gs ms ce = do
|
||||
mapM_ groupSub $
|
||||
sortBy (comparing $ \(Group GroupInfo {localDisplayName = g} _) -> g) gs
|
||||
sortOn (\(Group GroupInfo {localDisplayName = g} _) -> g) gs
|
||||
toView . CRMemberSubSummary $ map (uncurry MemberSubStatus) mRs
|
||||
where
|
||||
mRs = resultsFor rs ms
|
||||
|
@ -1293,11 +1349,14 @@ processAgentMessage (Just user@User {userId, profile}) agentConnId agentMessage
|
|||
_ -> Nothing
|
||||
|
||||
processDirectMessage :: ACommand 'Agent -> Connection -> Maybe Contact -> m ()
|
||||
processDirectMessage agentMsg conn@Connection {connId, viaUserContactLink} = \case
|
||||
processDirectMessage agentMsg conn@Connection {connId, viaUserContactLink, customUserProfileId} = \case
|
||||
Nothing -> case agentMsg of
|
||||
CONF confId _ connInfo -> do
|
||||
-- [incognito] send saved profile
|
||||
incognitoProfile <- forM customUserProfileId $ \profileId -> withStore (\db -> getProfileById db userId profileId)
|
||||
let profileToSend = fromMaybe (fromLocalProfile profile) incognitoProfile
|
||||
saveConnInfo conn connInfo
|
||||
allowAgentConnection conn confId $ XInfo profile
|
||||
allowAgentConnection conn confId $ XInfo profileToSend
|
||||
INFO connInfo ->
|
||||
saveConnInfo conn connInfo
|
||||
MSG meta _msgFlags msgBody -> do
|
||||
|
@ -1358,7 +1417,9 @@ processAgentMessage (Just user@User {userId, profile}) agentConnId agentMessage
|
|||
CON ->
|
||||
withStore' (\db -> getViaGroupMember db user ct) >>= \case
|
||||
Nothing -> do
|
||||
toView $ CRContactConnected ct
|
||||
-- [incognito] print incognito profile used for this contact
|
||||
incognitoProfile <- forM customUserProfileId $ \profileId -> withStore (\db -> getProfileById db userId profileId)
|
||||
toView $ CRContactConnected ct incognitoProfile
|
||||
setActive $ ActiveC c
|
||||
showToast (c <> "> ") "connected"
|
||||
forM_ viaUserContactLink $ \userContactLinkId -> do
|
||||
|
@ -1386,25 +1447,26 @@ processAgentMessage (Just user@User {userId, profile}) agentConnId agentMessage
|
|||
-- TODO print errors
|
||||
MERR msgId err -> do
|
||||
chatItemId_ <- withStore' $ \db -> getChatItemIdByAgentMsgId db connId msgId
|
||||
case chatItemId_ of
|
||||
Nothing -> pure ()
|
||||
Just chatItemId -> do
|
||||
chatItem <- withStore $ \db -> updateDirectChatItemStatus db userId contactId chatItemId (agentErrToItemStatus err)
|
||||
toView $ CRChatItemStatusUpdated (AChatItem SCTDirect SMDSnd (DirectChat ct) chatItem)
|
||||
forM_ chatItemId_ $ \chatItemId -> do
|
||||
chatItem <- withStore $ \db -> updateDirectChatItemStatus db userId contactId chatItemId (agentErrToItemStatus err)
|
||||
toView $ CRChatItemStatusUpdated (AChatItem SCTDirect SMDSnd (DirectChat ct) chatItem)
|
||||
ERR err -> toView . CRChatError $ ChatErrorAgent err
|
||||
-- TODO add debugging output
|
||||
_ -> pure ()
|
||||
|
||||
processGroupMessage :: ACommand 'Agent -> Connection -> GroupInfo -> GroupMember -> m ()
|
||||
processGroupMessage agentMsg conn gInfo@GroupInfo {groupId, localDisplayName = gName, membership} m = case agentMsg of
|
||||
processGroupMessage agentMsg conn gInfo@GroupInfo {groupId, localDisplayName = gName, membership} m@GroupMember {memberContactProfileId} = case agentMsg of
|
||||
CONF confId _ connInfo -> do
|
||||
ChatMessage {chatMsgEvent} <- liftEither $ parseChatMessage connInfo
|
||||
case memberCategory m of
|
||||
GCInviteeMember ->
|
||||
case chatMsgEvent of
|
||||
XGrpAcpt memId
|
||||
XGrpAcpt memId incognitoProfile
|
||||
| sameMemberId memId m -> do
|
||||
withStore' $ \db -> updateGroupMemberStatus db userId m GSMemAccepted
|
||||
-- [incognito] update member profile to incognito profile
|
||||
withStore $ \db -> do
|
||||
liftIO $ updateGroupMemberStatus db userId m GSMemAccepted
|
||||
void $ createMemberIncognitoProfile db userId m incognitoProfile
|
||||
allowAgentConnection conn confId XOk
|
||||
| otherwise -> messageError "x.grp.acpt: memberId is different from expected"
|
||||
_ -> messageError "CONF from invited member must have x.grp.acpt"
|
||||
|
@ -1413,7 +1475,8 @@ processAgentMessage (Just user@User {userId, profile}) agentConnId agentMessage
|
|||
XGrpMemInfo memId _memProfile
|
||||
| sameMemberId memId m -> do
|
||||
-- TODO update member profile
|
||||
allowAgentConnection conn confId $ XGrpMemInfo (memberId (membership :: GroupMember)) profile
|
||||
-- [incognito] send membership incognito profile
|
||||
allowAgentConnection conn confId $ XGrpMemInfo (memberId (membership :: GroupMember)) (fromLocalProfile $ memberProfile membership)
|
||||
| otherwise -> messageError "x.grp.mem.info: memberId is different from expected"
|
||||
_ -> messageError "CONF from member must have x.grp.mem.info"
|
||||
INFO connInfo -> do
|
||||
|
@ -1436,13 +1499,17 @@ processAgentMessage (Just user@User {userId, profile}) agentConnId agentMessage
|
|||
sendPendingGroupMessages m conn
|
||||
case memberCategory m of
|
||||
GCHostMember -> do
|
||||
memberConnectedChatItem gInfo m
|
||||
toView $ CRUserJoinedGroup gInfo {membership = membership {memberStatus = GSMemConnected}} m {memberStatus = GSMemConnected}
|
||||
-- [incognito] chat item & event with indication that host connected incognito
|
||||
mainProfile <- if memberIncognito m then Just <$> withStore (\db -> getProfileById db userId memberContactProfileId) else pure Nothing
|
||||
memberConnectedChatItem gInfo m mainProfile
|
||||
toView $ CRUserJoinedGroup gInfo {membership = membership {memberStatus = GSMemConnected}} m {memberStatus = GSMemConnected} (memberIncognito membership)
|
||||
setActive $ ActiveG gName
|
||||
showToast ("#" <> gName) "you are connected to group"
|
||||
GCInviteeMember -> do
|
||||
memberConnectedChatItem gInfo m
|
||||
toView $ CRJoinedGroupMember gInfo m {memberStatus = GSMemConnected}
|
||||
-- [incognito] chat item & event with indication that invitee connected incognito
|
||||
mainProfile <- if memberIncognito m then Just <$> withStore (\db -> getProfileById db userId memberContactProfileId) else pure Nothing
|
||||
memberConnectedChatItem gInfo m mainProfile
|
||||
toView $ CRJoinedGroupMember gInfo m {memberStatus = GSMemConnected} mainProfile
|
||||
setActive $ ActiveG gName
|
||||
showToast ("#" <> gName) $ "member " <> localDisplayName (m :: GroupMember) <> " is connected"
|
||||
intros <- withStore' $ \db -> createIntroductions db members m
|
||||
|
@ -1629,10 +1696,12 @@ processAgentMessage (Just user@User {userId, profile}) agentConnId agentMessage
|
|||
cancelRcvFileTransfer user ft
|
||||
throwChatError $ CEFileRcvChunk err
|
||||
|
||||
memberConnectedChatItem :: GroupInfo -> GroupMember -> m ()
|
||||
memberConnectedChatItem gInfo m = do
|
||||
memberConnectedChatItem :: GroupInfo -> GroupMember -> Maybe Profile -> m ()
|
||||
memberConnectedChatItem gInfo m mainProfile_ = do
|
||||
createdAt <- liftIO getCurrentTime
|
||||
let content = CIRcvGroupEvent RGEMemberConnected
|
||||
let content = CIRcvGroupEvent $ case mainProfile_ of
|
||||
Just mainProfile -> RGEMemberConnected $ Just mainProfile
|
||||
_ -> RGEMemberConnected Nothing
|
||||
cd = CDGroupRcv gInfo m
|
||||
-- first ts should be broker ts but we don't have it for CON
|
||||
ciId <- withStore' $ \db -> createNewChatItemNoMsg db user cd content createdAt createdAt
|
||||
|
@ -1641,7 +1710,7 @@ processAgentMessage (Just user@User {userId, profile}) agentConnId agentMessage
|
|||
|
||||
notifyMemberConnected :: GroupInfo -> GroupMember -> m ()
|
||||
notifyMemberConnected gInfo m@GroupMember {localDisplayName = c} = do
|
||||
memberConnectedChatItem gInfo m
|
||||
memberConnectedChatItem gInfo m Nothing
|
||||
toView $ CRConnectedToGroupMember gInfo m
|
||||
let g = groupName' gInfo
|
||||
setActive $ ActiveG g
|
||||
|
@ -1679,13 +1748,12 @@ processAgentMessage (Just user@User {userId, profile}) agentConnId agentMessage
|
|||
setActive $ ActiveC c
|
||||
|
||||
processFileInvitation :: Maybe FileInvitation -> (FileInvitation -> Integer -> m RcvFileTransfer) -> m (Maybe (CIFile 'MDRcv))
|
||||
processFileInvitation fileInvitation_ createRcvFileTransferF = case fileInvitation_ of
|
||||
Nothing -> pure Nothing
|
||||
Just fileInvitation@FileInvitation {fileName, fileSize} -> do
|
||||
processFileInvitation fileInvitation_ createRcvFileTransferF =
|
||||
forM fileInvitation_ $ \fileInvitation@FileInvitation {fileName, fileSize} -> do
|
||||
chSize <- asks $ fileChunkSize . config
|
||||
RcvFileTransfer {fileId} <- createRcvFileTransferF fileInvitation chSize
|
||||
let ciFile = CIFile {fileId, fileName, fileSize, filePath = Nothing, fileStatus = CIFSRcvInvitation}
|
||||
pure $ Just ciFile
|
||||
pure ciFile
|
||||
|
||||
messageUpdate :: Contact -> SharedMsgId -> MsgContent -> RcvMessage -> MsgMeta -> m ()
|
||||
messageUpdate ct@Contact {contactId, localDisplayName = c} sharedMsgId mc msg@RcvMessage {msgId} msgMeta = do
|
||||
|
@ -1830,16 +1898,19 @@ processAgentMessage (Just user@User {userId, profile}) agentConnId agentMessage
|
|||
toView . CRNewChatItem $ AChatItem SCTGroup SMDRcv (GroupChat gInfo) ci
|
||||
|
||||
processGroupInvitation :: Contact -> GroupInvitation -> RcvMessage -> MsgMeta -> m ()
|
||||
processGroupInvitation ct@Contact {localDisplayName = c} inv@(GroupInvitation (MemberIdRole fromMemId fromRole) (MemberIdRole memId memRole) _ _) msg msgMeta = do
|
||||
processGroupInvitation ct@Contact {localDisplayName = c} inv@GroupInvitation {fromMember = (MemberIdRole fromMemId fromRole), fromMemberProfile, invitedMember = (MemberIdRole memId memRole)} msg msgMeta = do
|
||||
checkIntegrityCreateItem (CDDirectRcv ct) msgMeta
|
||||
when (fromRole < GRAdmin || fromRole < memRole) $ throwChatError (CEGroupContactRole c)
|
||||
when (fromMemId == memId) $ throwChatError CEGroupDuplicateMemberId
|
||||
gInfo@GroupInfo {groupId, localDisplayName, groupProfile, membership = GroupMember {groupMemberId}} <- withStore $ \db -> createGroupInvitation db user ct inv
|
||||
let content = CIRcvGroupInvitation (CIGroupInvitation {groupId, groupMemberId, localDisplayName, groupProfile, status = CIGISPending}) memRole
|
||||
-- [incognito] if received group invitation has host's incognito profile, create membership with new incognito profile; incognito mode is checked when joining group
|
||||
let invitedIncognito = isJust fromMemberProfile
|
||||
incognitoProfile <- if invitedIncognito then Just <$> liftIO generateRandomProfile else pure Nothing
|
||||
gInfo@GroupInfo {groupId, localDisplayName, groupProfile, membership = GroupMember {groupMemberId}} <- withStore $ \db -> createGroupInvitation db user ct inv incognitoProfile
|
||||
let content = CIRcvGroupInvitation (CIGroupInvitation {groupId, groupMemberId, localDisplayName, groupProfile, status = CIGISPending, invitedIncognito = Just invitedIncognito}) memRole
|
||||
ci <- saveRcvChatItem user (CDDirectRcv ct) msg msgMeta content Nothing
|
||||
withStore' $ \db -> setGroupInvitationChatItemId db user groupId (chatItemId' ci)
|
||||
toView . CRNewChatItem $ AChatItem SCTDirect SMDRcv (DirectChat ct) ci
|
||||
toView $ CRReceivedGroupInvitation gInfo ct memRole
|
||||
toView $ CRReceivedGroupInvitation gInfo ct memRole fromMemberProfile
|
||||
showToast ("#" <> localDisplayName <> " " <> c <> "> ") "invited you to join the group"
|
||||
|
||||
checkIntegrityCreateItem :: forall c. ChatTypeI c => ChatDirection c 'MDRcv -> MsgMeta -> m ()
|
||||
|
@ -1857,23 +1928,27 @@ processAgentMessage (Just user@User {userId, profile}) agentConnId agentMessage
|
|||
toView $ CRNewChatItem $ AChatItem (chatTypeI @c) SMDRcv (toChatInfo cd) ci
|
||||
|
||||
xInfo :: Contact -> Profile -> m ()
|
||||
xInfo c@Contact {profile = p} p' = unless (p == p') $ do
|
||||
xInfo c@Contact {profile = p} p' = unless (fromLocalProfile p == p') $ do
|
||||
c' <- withStore $ \db -> updateContactProfile db userId c p'
|
||||
toView $ CRContactUpdated c c'
|
||||
|
||||
xInfoProbe :: Contact -> Probe -> m ()
|
||||
xInfoProbe c2 probe = do
|
||||
r <- withStore' $ \db -> matchReceivedProbe db userId c2 probe
|
||||
forM_ r $ \c1 -> probeMatch c1 c2 probe
|
||||
xInfoProbe c2 probe =
|
||||
-- [incognito] unless connected incognito
|
||||
unless (contactConnIncognito c2) $ do
|
||||
r <- withStore' $ \db -> matchReceivedProbe db userId c2 probe
|
||||
forM_ r $ \c1 -> probeMatch c1 c2 probe
|
||||
|
||||
xInfoProbeCheck :: Contact -> ProbeHash -> m ()
|
||||
xInfoProbeCheck c1 probeHash = do
|
||||
r <- withStore' $ \db -> matchReceivedProbeHash db userId c1 probeHash
|
||||
forM_ r . uncurry $ probeMatch c1
|
||||
xInfoProbeCheck c1 probeHash =
|
||||
-- [incognito] unless connected incognito
|
||||
unless (contactConnIncognito c1) $ do
|
||||
r <- withStore' $ \db -> matchReceivedProbeHash db userId c1 probeHash
|
||||
forM_ r . uncurry $ probeMatch c1
|
||||
|
||||
probeMatch :: Contact -> Contact -> Probe -> m ()
|
||||
probeMatch c1@Contact {profile = p1} c2@Contact {profile = p2} probe =
|
||||
when (p1 == p2) $ do
|
||||
when (fromLocalProfile p1 == fromLocalProfile p2) $ do
|
||||
void . sendDirectContactMessage c1 $ XInfoProbeOk probe
|
||||
mergeContacts c1 c2
|
||||
|
||||
|
@ -2009,7 +2084,7 @@ processAgentMessage (Just user@User {userId, profile}) agentConnId agentMessage
|
|||
toView $ CRJoinedGroupMemberConnecting gInfo m newMember
|
||||
|
||||
xGrpMemIntro :: Connection -> GroupInfo -> GroupMember -> MemberInfo -> m ()
|
||||
xGrpMemIntro conn gInfo@GroupInfo {groupId} m memInfo@(MemberInfo memId _ _) = do
|
||||
xGrpMemIntro conn gInfo@GroupInfo {groupId, membership} m memInfo@(MemberInfo memId _ _) = do
|
||||
case memberCategory m of
|
||||
GCHostMember -> do
|
||||
members <- withStore' $ \db -> getGroupMembers db user gInfo
|
||||
|
@ -2018,7 +2093,9 @@ processAgentMessage (Just user@User {userId, profile}) agentConnId agentMessage
|
|||
else do
|
||||
(groupConnId, groupConnReq) <- withAgent (`createConnection` SCMInvitation)
|
||||
(directConnId, directConnReq) <- withAgent (`createConnection` SCMInvitation)
|
||||
newMember <- withStore $ \db -> createIntroReMember db user gInfo m memInfo groupConnId directConnId
|
||||
-- [incognito] direct connection with member has to be established using same incognito profile
|
||||
customUserProfileId <- if memberIncognito membership then Just <$> withStore (\db -> getGroupMemberProfileId db userId membership) else pure Nothing
|
||||
newMember <- withStore $ \db -> createIntroReMember db user gInfo m memInfo groupConnId directConnId customUserProfileId
|
||||
let msg = XGrpMemInv memId IntroInvitation {groupConnReq, directConnReq}
|
||||
void $ sendDirectMessage conn msg (GroupId groupId)
|
||||
withStore' $ \db -> updateGroupMemberStatus db userId newMember GSMemIntroInvited
|
||||
|
@ -2047,10 +2124,12 @@ processAgentMessage (Just user@User {userId, profile}) agentConnId agentMessage
|
|||
Nothing -> withStore $ \db -> createNewGroupMember db user gInfo memInfo GCPostMember GSMemAnnounced
|
||||
Just m' -> pure m'
|
||||
withStore' $ \db -> saveMemberInvitation db toMember introInv
|
||||
let msg = XGrpMemInfo (memberId (membership :: GroupMember)) profile
|
||||
-- [incognito] send membership incognito profile, create direct connection as incognito
|
||||
let msg = XGrpMemInfo (memberId (membership :: GroupMember)) (fromLocalProfile $ memberProfile membership)
|
||||
groupConnId <- withAgent $ \a -> joinConnection a groupConnReq $ directMessage msg
|
||||
directConnId <- withAgent $ \a -> joinConnection a directConnReq $ directMessage msg
|
||||
withStore' $ \db -> createIntroToMemberContact db userId m toMember groupConnId directConnId
|
||||
customUserProfileId <- if memberIncognito membership then Just <$> withStore (\db -> getGroupMemberProfileId db userId membership) else pure Nothing
|
||||
withStore' $ \db -> createIntroToMemberContact db userId m toMember groupConnId directConnId customUserProfileId
|
||||
|
||||
xGrpMemDel :: GroupInfo -> GroupMember -> MemberId -> RcvMessage -> MsgMeta -> m ()
|
||||
xGrpMemDel gInfo@GroupInfo {membership} m memId msg msgMeta = do
|
||||
|
@ -2071,7 +2150,7 @@ processAgentMessage (Just user@User {userId, profile}) agentConnId agentMessage
|
|||
else do
|
||||
deleteMemberConnection member
|
||||
withStore' $ \db -> updateGroupMemberStatus db userId member GSMemRemoved
|
||||
ci <- saveRcvChatItem user (CDGroupRcv gInfo m) msg msgMeta (CIRcvGroupEvent $ RGEMemberDeleted groupMemberId memberProfile) Nothing
|
||||
ci <- saveRcvChatItem user (CDGroupRcv gInfo m) msg msgMeta (CIRcvGroupEvent $ RGEMemberDeleted groupMemberId (fromLocalProfile memberProfile)) Nothing
|
||||
groupMsgToView gInfo m ci msgMeta
|
||||
toView $ CRDeletedMember gInfo m member {memberStatus = GSMemRemoved}
|
||||
|
||||
|
@ -2388,7 +2467,7 @@ getCreateActiveUser st = do
|
|||
withTransaction st (`setActiveUser` userId user)
|
||||
pure user
|
||||
userStr :: User -> String
|
||||
userStr User {localDisplayName, profile = Profile {fullName}} =
|
||||
userStr User {localDisplayName, profile = LocalProfile {fullName}} =
|
||||
T.unpack $ localDisplayName <> if T.null fullName || localDisplayName == fullName then "" else " (" <> fullName <> ")"
|
||||
getContactName :: IO ContactName
|
||||
getContactName = do
|
||||
|
@ -2556,6 +2635,7 @@ chatCommandP =
|
|||
"/profile_image" $> UpdateProfileImage Nothing,
|
||||
("/profile " <|> "/p ") *> (uncurry UpdateProfile <$> userNames),
|
||||
("/profile" <|> "/p") $> ShowProfile,
|
||||
"/incognito " *> (SetIncognito <$> onOffP),
|
||||
("/quit" <|> "/q" <|> "/exit") $> QuitChat,
|
||||
("/version" <|> "/v") $> ShowVersion
|
||||
]
|
||||
|
|
|
@ -24,7 +24,7 @@ chatBotRepl welcome answer _user cc = do
|
|||
race_ (forever $ void getLine) . forever $ do
|
||||
(_, resp) <- atomically . readTBQueue $ outputQ cc
|
||||
case resp of
|
||||
CRContactConnected contact -> do
|
||||
CRContactConnected contact _ -> do
|
||||
contactConnected contact
|
||||
void $ sendMsg contact welcome
|
||||
CRNewChatItem (AChatItem _ SMDRcv (DirectChat contact) ChatItem {content}) -> do
|
||||
|
@ -40,7 +40,7 @@ initializeBotAddress cc = do
|
|||
sendChatCmd cc "/show_address" >>= \case
|
||||
CRUserContactLink uri _ _ -> showBotAddress uri
|
||||
CRChatCmdError (ChatErrorStore SEUserContactLinkNotFound) -> do
|
||||
putStrLn $ "No bot address, creating..."
|
||||
putStrLn "No bot address, creating..."
|
||||
sendChatCmd cc "/address" >>= \case
|
||||
CRUserContactLinkCreated uri -> showBotAddress uri
|
||||
_ -> putStrLn "can't create bot address" >> exitFailure
|
||||
|
|
|
@ -88,7 +88,8 @@ data ChatController = ChatController
|
|||
rcvFiles :: TVar (Map Int64 Handle),
|
||||
currentCalls :: TMap ContactId Call,
|
||||
config :: ChatConfig,
|
||||
filesFolder :: TVar (Maybe FilePath) -- path to files folder for mobile apps
|
||||
filesFolder :: TVar (Maybe FilePath), -- path to files folder for mobile apps,
|
||||
incognitoMode :: TVar Bool
|
||||
}
|
||||
|
||||
data HelpSection = HSMain | HSFiles | HSGroups | HSMyAddress | HSMarkdown | HSMessages | HSSettings
|
||||
|
@ -107,6 +108,7 @@ data ChatCommand
|
|||
| APISuspendChat {suspendTimeout :: Int}
|
||||
| ResubscribeAllConnections
|
||||
| SetFilesFolder FilePath
|
||||
| SetIncognito Bool
|
||||
| APIExportArchive ArchiveConfig
|
||||
| APIImportArchive ArchiveConfig
|
||||
| APIDeleteStorage
|
||||
|
@ -210,8 +212,8 @@ data ChatResponse
|
|||
| CRApiParsedMarkdown {formattedText :: Maybe MarkdownList}
|
||||
| CRUserSMPServers {smpServers :: [SMPServer]}
|
||||
| CRNetworkConfig {networkConfig :: NetworkConfig}
|
||||
| CRContactInfo {contact :: Contact, connectionStats :: ConnectionStats}
|
||||
| CRGroupMemberInfo {groupInfo :: GroupInfo, member :: GroupMember, connectionStats_ :: Maybe ConnectionStats}
|
||||
| CRContactInfo {contact :: Contact, connectionStats :: ConnectionStats, customUserProfile :: Maybe Profile}
|
||||
| CRGroupMemberInfo {groupInfo :: GroupInfo, member :: GroupMember, connectionStats_ :: Maybe ConnectionStats, mainProfile :: Maybe Profile}
|
||||
| CRNewChatItem {chatItem :: AChatItem}
|
||||
| CRChatItemStatusUpdated {chatItem :: AChatItem}
|
||||
| CRChatItemUpdated {chatItem :: AChatItem}
|
||||
|
@ -223,7 +225,7 @@ data ChatResponse
|
|||
| CRCmdOk
|
||||
| CRChatHelp {helpSection :: HelpSection}
|
||||
| CRWelcome {user :: User}
|
||||
| CRGroupCreated {groupInfo :: GroupInfo}
|
||||
| CRGroupCreated {groupInfo :: GroupInfo, customUserProfile :: Maybe Profile}
|
||||
| CRGroupMembers {group :: Group}
|
||||
| CRContactsList {contacts :: [Contact]}
|
||||
| CRUserContactLink {connReqContact :: ConnReqContact, autoAccept :: Bool, autoReply :: Maybe MsgContent}
|
||||
|
@ -232,14 +234,14 @@ data ChatResponse
|
|||
| CRUserAcceptedGroupSent {groupInfo :: GroupInfo}
|
||||
| CRUserDeletedMember {groupInfo :: GroupInfo, member :: GroupMember}
|
||||
| CRGroupsList {groups :: [GroupInfo]}
|
||||
| CRSentGroupInvitation {groupInfo :: GroupInfo, contact :: Contact, member :: GroupMember}
|
||||
| CRSentGroupInvitation {groupInfo :: GroupInfo, contact :: Contact, member :: GroupMember, sentCustomProfile :: Maybe Profile}
|
||||
| CRFileTransferStatus (FileTransfer, [Integer]) -- TODO refactor this type to FileTransferStatus
|
||||
| CRUserProfile {profile :: Profile}
|
||||
| CRUserProfileNoChange
|
||||
| CRVersionInfo {version :: String}
|
||||
| CRInvitation {connReqInvitation :: ConnReqInvitation}
|
||||
| CRSentConfirmation
|
||||
| CRSentInvitation
|
||||
| CRSentInvitation {customUserProfile :: Maybe Profile}
|
||||
| CRContactUpdated {fromContact :: Contact, toContact :: Contact}
|
||||
| CRContactsMerged {intoContact :: Contact, mergedContact :: Contact}
|
||||
| CRContactDeleted {contact :: Contact}
|
||||
|
@ -265,7 +267,7 @@ data ChatResponse
|
|||
| CRSndGroupFileCancelled {chatItem :: AChatItem, fileTransferMeta :: FileTransferMeta, sndFileTransfers :: [SndFileTransfer]}
|
||||
| CRUserProfileUpdated {fromProfile :: Profile, toProfile :: Profile}
|
||||
| CRContactConnecting {contact :: Contact}
|
||||
| CRContactConnected {contact :: Contact}
|
||||
| CRContactConnected {contact :: Contact, userCustomProfile :: Maybe Profile}
|
||||
| CRContactAnotherClient {contact :: Contact}
|
||||
| CRContactsDisconnected {server :: SMPServer, contactRefs :: [ContactRef]}
|
||||
| CRContactsSubscribed {server :: SMPServer, contactRefs :: [ContactRef]}
|
||||
|
@ -274,9 +276,9 @@ data ChatResponse
|
|||
| CRHostConnected {protocol :: AProtocolType, transportHost :: TransportHost}
|
||||
| CRHostDisconnected {protocol :: AProtocolType, transportHost :: TransportHost}
|
||||
| CRGroupInvitation {groupInfo :: GroupInfo}
|
||||
| CRReceivedGroupInvitation {groupInfo :: GroupInfo, contact :: Contact, memberRole :: GroupMemberRole}
|
||||
| CRUserJoinedGroup {groupInfo :: GroupInfo, hostMember :: GroupMember}
|
||||
| CRJoinedGroupMember {groupInfo :: GroupInfo, member :: GroupMember}
|
||||
| CRReceivedGroupInvitation {groupInfo :: GroupInfo, contact :: Contact, memberRole :: GroupMemberRole, receivedCustomProfile :: Maybe Profile}
|
||||
| CRUserJoinedGroup {groupInfo :: GroupInfo, hostMember :: GroupMember, usedCustomProfile :: Bool}
|
||||
| CRJoinedGroupMember {groupInfo :: GroupInfo, member :: GroupMember, mainProfile :: Maybe Profile}
|
||||
| CRJoinedGroupMemberConnecting {groupInfo :: GroupInfo, hostMember :: GroupMember, member :: GroupMember}
|
||||
| CRConnectedToGroupMember {groupInfo :: GroupInfo, member :: GroupMember}
|
||||
| CRDeletedMember {groupInfo :: GroupInfo, byMember :: GroupMember, deletedMember :: GroupMember}
|
||||
|
@ -383,6 +385,7 @@ data ChatErrorType
|
|||
| CEContactNotReady {contact :: Contact}
|
||||
| CEContactGroups {contact :: Contact, groupNames :: [GroupName]}
|
||||
| CEGroupUserRole
|
||||
| CEGroupNotIncognitoCantInvite
|
||||
| CEGroupContactRole {contactName :: ContactName}
|
||||
| CEGroupDuplicateMember {contactName :: ContactName}
|
||||
| CEGroupDuplicateMemberId
|
||||
|
|
|
@ -18,7 +18,7 @@ import Data.Text (Text)
|
|||
import qualified Data.Text as T
|
||||
import Simplex.Chat.Markdown
|
||||
import Simplex.Chat.Styled
|
||||
import Simplex.Chat.Types (Profile (..), User (..))
|
||||
import Simplex.Chat.Types (User (..), LocalProfile (..))
|
||||
import System.Console.ANSI.Types
|
||||
|
||||
highlight :: Text -> Markdown
|
||||
|
@ -55,7 +55,7 @@ chatWelcome user =
|
|||
"Type " <> highlight "/help" <> " for usage info, " <> highlight "/welcome" <> " to show this message"
|
||||
]
|
||||
where
|
||||
User {profile = Profile {displayName, fullName}} = user
|
||||
User {profile = LocalProfile {displayName, fullName}} = user
|
||||
userName = if T.null fullName then displayName else fullName
|
||||
|
||||
chatHelpInfo :: [StyledString]
|
||||
|
|
|
@ -501,22 +501,24 @@ ciGroupInvitationToText CIGroupInvitation {groupProfile = GroupProfile {displayN
|
|||
|
||||
rcvGroupEventToText :: RcvGroupEvent -> Text
|
||||
rcvGroupEventToText = \case
|
||||
RGEMemberAdded _ p -> "added " <> memberProfileToText p
|
||||
RGEMemberConnected -> "connected"
|
||||
RGEMemberAdded _ p -> "added " <> profileToText p
|
||||
RGEMemberConnected contactMainProfile -> case contactMainProfile of
|
||||
Just p -> profileToText p <> " connected incognito"
|
||||
Nothing -> "connected"
|
||||
RGEMemberLeft -> "left"
|
||||
RGEMemberDeleted _ p -> "removed " <> memberProfileToText p
|
||||
RGEMemberDeleted _ p -> "removed " <> profileToText p
|
||||
RGEUserDeleted -> "removed you"
|
||||
RGEGroupDeleted -> "deleted group"
|
||||
RGEGroupUpdated _ -> "group profile updated"
|
||||
|
||||
sndGroupEventToText :: SndGroupEvent -> Text
|
||||
sndGroupEventToText = \case
|
||||
SGEMemberDeleted _ p -> "removed " <> memberProfileToText p
|
||||
SGEMemberDeleted _ p -> "removed " <> profileToText p
|
||||
SGEUserLeft -> "left"
|
||||
SGEGroupUpdated _ -> "group profile updated"
|
||||
|
||||
memberProfileToText :: Profile -> Text
|
||||
memberProfileToText Profile {displayName, fullName} = displayName <> optionalFullName displayName fullName
|
||||
profileToText :: Profile -> Text
|
||||
profileToText Profile {displayName, fullName} = displayName <> optionalFullName displayName fullName
|
||||
|
||||
-- This type is used both in API and in DB, so we use different JSON encodings for the database and for the API
|
||||
data CIContent (d :: MsgDirection) where
|
||||
|
@ -536,7 +538,7 @@ deriving instance Show (CIContent d)
|
|||
|
||||
data RcvGroupEvent
|
||||
= RGEMemberAdded {groupMemberId :: GroupMemberId, profile :: Profile} -- CRJoinedGroupMemberConnecting
|
||||
| RGEMemberConnected -- CRUserJoinedGroup, CRJoinedGroupMember, CRConnectedToGroupMember
|
||||
| RGEMemberConnected {contactMainProfile :: Maybe Profile} -- CRUserJoinedGroup, CRJoinedGroupMember, CRConnectedToGroupMember
|
||||
| RGEMemberLeft -- CRLeftMember
|
||||
| RGEMemberDeleted {groupMemberId :: GroupMemberId, profile :: Profile} -- CRDeletedMember
|
||||
| RGEUserDeleted -- CRDeletedMemberUser
|
||||
|
@ -569,13 +571,14 @@ data CIGroupInvitation = CIGroupInvitation
|
|||
groupMemberId :: GroupMemberId,
|
||||
localDisplayName :: GroupName,
|
||||
groupProfile :: GroupProfile,
|
||||
status :: CIGroupInvitationStatus
|
||||
status :: CIGroupInvitationStatus,
|
||||
invitedIncognito :: Maybe Bool
|
||||
}
|
||||
deriving (Eq, Show, Generic, FromJSON)
|
||||
|
||||
instance ToJSON CIGroupInvitation where
|
||||
toJSON = J.genericToJSON J.defaultOptions
|
||||
toEncoding = J.genericToEncoding J.defaultOptions
|
||||
toJSON = J.genericToJSON J.defaultOptions {J.omitNothingFields = True}
|
||||
toEncoding = J.genericToEncoding J.defaultOptions {J.omitNothingFields = True}
|
||||
|
||||
data CIGroupInvitationStatus
|
||||
= CIGISPending
|
||||
|
|
16
src/Simplex/Chat/Migrations/M20220812_incognito_profiles.hs
Normal file
16
src/Simplex/Chat/Migrations/M20220812_incognito_profiles.hs
Normal file
|
@ -0,0 +1,16 @@
|
|||
{-# LANGUAGE QuasiQuotes #-}
|
||||
|
||||
module Simplex.Chat.Migrations.M20220812_incognito_profiles where
|
||||
|
||||
import Database.SQLite.Simple (Query)
|
||||
import Database.SQLite.Simple.QQ (sql)
|
||||
|
||||
m20220812_incognito_profiles :: Query
|
||||
m20220812_incognito_profiles =
|
||||
[sql|
|
||||
ALTER TABLE connections ADD COLUMN custom_user_profile_id INTEGER REFERENCES contact_profiles ON DELETE SET NULL; -- only set for direct connections
|
||||
|
||||
ALTER TABLE group_members ADD COLUMN member_profile_id INTEGER REFERENCES contact_profiles ON DELETE SET NULL; -- member profile id if incognito profile was saved for member (used for hosts and invitees in incognito groups)
|
||||
|
||||
ALTER TABLE contact_profiles ADD COLUMN incognito INTEGER; -- 1 for incognito
|
||||
|]
|
|
@ -13,7 +13,8 @@ CREATE TABLE contact_profiles(
|
|||
created_at TEXT CHECK(created_at NOT NULL),
|
||||
updated_at TEXT CHECK(updated_at NOT NULL),
|
||||
image TEXT,
|
||||
user_id INTEGER DEFAULT NULL REFERENCES users ON DELETE CASCADE
|
||||
user_id INTEGER DEFAULT NULL REFERENCES users ON DELETE CASCADE,
|
||||
incognito INTEGER
|
||||
);
|
||||
CREATE INDEX contact_profiles_index ON contact_profiles(
|
||||
display_name,
|
||||
|
@ -145,6 +146,7 @@ CREATE TABLE group_members(
|
|||
contact_id INTEGER REFERENCES contacts ON DELETE CASCADE,
|
||||
created_at TEXT CHECK(created_at NOT NULL),
|
||||
updated_at TEXT CHECK(updated_at NOT NULL),
|
||||
member_profile_id INTEGER REFERENCES contact_profiles ON DELETE SET NULL,
|
||||
FOREIGN KEY(user_id, local_display_name)
|
||||
REFERENCES display_names(user_id, local_display_name)
|
||||
ON DELETE CASCADE
|
||||
|
@ -236,6 +238,7 @@ CREATE TABLE connections(
|
|||
xcontact_id BLOB,
|
||||
via_user_contact_link INTEGER DEFAULT NULL
|
||||
REFERENCES user_contact_links(user_contact_link_id) ON DELETE SET NULL,
|
||||
custom_user_profile_id INTEGER REFERENCES contact_profiles ON DELETE SET NULL,
|
||||
FOREIGN KEY(snd_file_id, connection_id)
|
||||
REFERENCES snd_files(file_id, connection_id)
|
||||
ON DELETE CASCADE
|
||||
|
|
3140
src/Simplex/Chat/ProfileGenerator.hs
Normal file
3140
src/Simplex/Chat/ProfileGenerator.hs
Normal file
File diff suppressed because it is too large
Load diff
|
@ -124,7 +124,7 @@ data ChatMsgEvent
|
|||
| XInfo Profile
|
||||
| XContact Profile (Maybe XContactId)
|
||||
| XGrpInv GroupInvitation
|
||||
| XGrpAcpt MemberId
|
||||
| XGrpAcpt MemberId (Maybe Profile)
|
||||
| XGrpMemNew MemberInfo
|
||||
| XGrpMemIntro MemberInfo
|
||||
| XGrpMemInv MemberId IntroInvitation
|
||||
|
@ -413,7 +413,7 @@ toCMEventTag = \case
|
|||
XInfo _ -> XInfo_
|
||||
XContact _ _ -> XContact_
|
||||
XGrpInv _ -> XGrpInv_
|
||||
XGrpAcpt _ -> XGrpAcpt_
|
||||
XGrpAcpt _ _ -> XGrpAcpt_
|
||||
XGrpMemNew _ -> XGrpMemNew_
|
||||
XGrpMemIntro _ -> XGrpMemIntro_
|
||||
XGrpMemInv _ _ -> XGrpMemInv_
|
||||
|
@ -479,7 +479,7 @@ appToChatMessage AppMessage {msgId, event, params} = do
|
|||
XInfo_ -> XInfo <$> p "profile"
|
||||
XContact_ -> XContact <$> p "profile" <*> opt "contactReqId"
|
||||
XGrpInv_ -> XGrpInv <$> p "groupInvitation"
|
||||
XGrpAcpt_ -> XGrpAcpt <$> p "memberId"
|
||||
XGrpAcpt_ -> XGrpAcpt <$> p "memberId" <*> opt "memberProfile"
|
||||
XGrpMemNew_ -> XGrpMemNew <$> p "memberInfo"
|
||||
XGrpMemIntro_ -> XGrpMemIntro <$> p "memberInfo"
|
||||
XGrpMemInv_ -> XGrpMemInv <$> p "memberId" <*> p "memberIntro"
|
||||
|
@ -521,7 +521,7 @@ chatToAppMessage ChatMessage {msgId, chatMsgEvent} = AppMessage {msgId, event, p
|
|||
XInfo profile -> o ["profile" .= profile]
|
||||
XContact profile xContactId -> o $ ("contactReqId" .=? xContactId) ["profile" .= profile]
|
||||
XGrpInv groupInv -> o ["groupInvitation" .= groupInv]
|
||||
XGrpAcpt memId -> o ["memberId" .= memId]
|
||||
XGrpAcpt memId profile -> o $ ("memberProfile" .=? profile) ["memberId" .= memId]
|
||||
XGrpMemNew memInfo -> o ["memberInfo" .= memInfo]
|
||||
XGrpMemIntro memInfo -> o ["memberInfo" .= memInfo]
|
||||
XGrpMemInv memId memIntro -> o ["memberId" .= memId, "memberIntro" .= memIntro]
|
||||
|
|
File diff suppressed because it is too large
Load diff
|
@ -22,6 +22,7 @@ import qualified Data.Attoparsec.ByteString.Char8 as A
|
|||
import Data.ByteString.Char8 (ByteString)
|
||||
import qualified Data.ByteString.Char8 as B
|
||||
import Data.Int (Int64)
|
||||
import Data.Maybe (isJust)
|
||||
import Data.Text (Text)
|
||||
import qualified Data.Text as T
|
||||
import Data.Time.Clock (UTCTime)
|
||||
|
@ -39,7 +40,7 @@ import Simplex.Messaging.Util ((<$?>))
|
|||
|
||||
class IsContact a where
|
||||
contactId' :: a -> ContactId
|
||||
profile' :: a -> Profile
|
||||
profile' :: a -> LocalProfile
|
||||
localDisplayName' :: a -> ContactName
|
||||
|
||||
instance IsContact User where
|
||||
|
@ -56,7 +57,7 @@ data User = User
|
|||
{ userId :: UserId,
|
||||
userContactId :: ContactId,
|
||||
localDisplayName :: ContactName,
|
||||
profile :: Profile,
|
||||
profile :: LocalProfile,
|
||||
activeUser :: Bool
|
||||
}
|
||||
deriving (Show, Generic, FromJSON)
|
||||
|
@ -67,10 +68,12 @@ type UserId = ContactId
|
|||
|
||||
type ContactId = Int64
|
||||
|
||||
type ProfileId = Int64
|
||||
|
||||
data Contact = Contact
|
||||
{ contactId :: ContactId,
|
||||
localDisplayName :: ContactName,
|
||||
profile :: Profile,
|
||||
profile :: LocalProfile,
|
||||
activeConn :: Connection,
|
||||
viaGroup :: Maybe Int64,
|
||||
createdAt :: UTCTime,
|
||||
|
@ -88,6 +91,9 @@ contactConn = activeConn
|
|||
contactConnId :: Contact -> ConnId
|
||||
contactConnId Contact {activeConn} = aConnId activeConn
|
||||
|
||||
contactConnIncognito :: Contact -> Bool
|
||||
contactConnIncognito Contact {activeConn = Connection {customUserProfileId}} = isJust customUserProfileId
|
||||
|
||||
data ContactRef = ContactRef
|
||||
{ contactId :: ContactId,
|
||||
localDisplayName :: ContactName
|
||||
|
@ -198,6 +204,7 @@ data Profile = Profile
|
|||
{ displayName :: ContactName,
|
||||
fullName :: Text,
|
||||
image :: Maybe ImageData
|
||||
-- incognito field should not be read as is into this data type to prevent sending it as part of profile to contacts
|
||||
}
|
||||
deriving (Eq, Show, Generic, FromJSON)
|
||||
|
||||
|
@ -205,6 +212,29 @@ instance ToJSON Profile where
|
|||
toJSON = J.genericToJSON J.defaultOptions {J.omitNothingFields = True}
|
||||
toEncoding = J.genericToEncoding J.defaultOptions {J.omitNothingFields = True}
|
||||
|
||||
data LocalProfile = LocalProfile
|
||||
{ profileId :: ProfileId,
|
||||
displayName :: ContactName,
|
||||
fullName :: Text,
|
||||
image :: Maybe ImageData
|
||||
}
|
||||
deriving (Eq, Show, Generic, FromJSON)
|
||||
|
||||
instance ToJSON LocalProfile where
|
||||
toJSON = J.genericToJSON J.defaultOptions {J.omitNothingFields = True}
|
||||
toEncoding = J.genericToEncoding J.defaultOptions {J.omitNothingFields = True}
|
||||
|
||||
localProfileId :: LocalProfile -> ProfileId
|
||||
localProfileId = profileId
|
||||
|
||||
toLocalProfile :: ProfileId -> Profile -> LocalProfile
|
||||
toLocalProfile profileId Profile {displayName, fullName, image} =
|
||||
LocalProfile {profileId, displayName, fullName, image}
|
||||
|
||||
fromLocalProfile :: LocalProfile -> Profile
|
||||
fromLocalProfile LocalProfile {displayName, fullName, image} =
|
||||
Profile {displayName, fullName, image}
|
||||
|
||||
data GroupProfile = GroupProfile
|
||||
{ displayName :: GroupName,
|
||||
fullName :: Text,
|
||||
|
@ -232,13 +262,16 @@ instance FromField ImageData where fromField = fmap ImageData . fromField
|
|||
|
||||
data GroupInvitation = GroupInvitation
|
||||
{ fromMember :: MemberIdRole,
|
||||
fromMemberProfile :: Maybe Profile,
|
||||
invitedMember :: MemberIdRole,
|
||||
connRequest :: ConnReqInvitation,
|
||||
groupProfile :: GroupProfile
|
||||
}
|
||||
deriving (Eq, Show, Generic, FromJSON)
|
||||
|
||||
instance ToJSON GroupInvitation where toEncoding = J.genericToEncoding J.defaultOptions
|
||||
instance ToJSON GroupInvitation where
|
||||
toJSON = J.genericToJSON J.defaultOptions {J.omitNothingFields = True}
|
||||
toEncoding = J.genericToEncoding J.defaultOptions {J.omitNothingFields = True}
|
||||
|
||||
data MemberIdRole = MemberIdRole
|
||||
{ memberId :: MemberId,
|
||||
|
@ -267,7 +300,7 @@ instance ToJSON MemberInfo where toEncoding = J.genericToEncoding J.defaultOptio
|
|||
|
||||
memberInfo :: GroupMember -> MemberInfo
|
||||
memberInfo GroupMember {memberId, memberRole, memberProfile} =
|
||||
MemberInfo memberId memberRole memberProfile
|
||||
MemberInfo memberId memberRole (fromLocalProfile memberProfile)
|
||||
|
||||
data ReceivedGroupInvitation = ReceivedGroupInvitation
|
||||
{ fromMember :: GroupMember,
|
||||
|
@ -278,6 +311,8 @@ data ReceivedGroupInvitation = ReceivedGroupInvitation
|
|||
|
||||
type GroupMemberId = Int64
|
||||
|
||||
-- memberProfile's profileId is COALESCE(member_profile_id, contact_profile_id), member_profile_id is non null
|
||||
-- if incognito profile was saved for member (used for hosts and invitees in incognito groups)
|
||||
data GroupMember = GroupMember
|
||||
{ groupMemberId :: GroupMemberId,
|
||||
groupId :: GroupId,
|
||||
|
@ -287,8 +322,9 @@ data GroupMember = GroupMember
|
|||
memberStatus :: GroupMemberStatus,
|
||||
invitedBy :: InvitedBy,
|
||||
localDisplayName :: ContactName,
|
||||
memberProfile :: Profile,
|
||||
memberContactId :: Maybe Int64,
|
||||
memberProfile :: LocalProfile,
|
||||
memberContactId :: Maybe ContactId,
|
||||
memberContactProfileId :: ProfileId,
|
||||
activeConn :: Maybe Connection
|
||||
}
|
||||
deriving (Eq, Show, Generic)
|
||||
|
@ -306,6 +342,9 @@ memberConnId GroupMember {activeConn} = aConnId <$> activeConn
|
|||
groupMemberId' :: GroupMember -> GroupMemberId
|
||||
groupMemberId' GroupMember {groupMemberId} = groupMemberId
|
||||
|
||||
memberIncognito :: GroupMember -> Bool
|
||||
memberIncognito GroupMember {memberProfile, memberContactProfileId} = localProfileId memberProfile /= memberContactProfileId
|
||||
|
||||
data NewGroupMember = NewGroupMember
|
||||
{ memInfo :: MemberInfo,
|
||||
memCategory :: GroupMemberCategory,
|
||||
|
@ -695,6 +734,7 @@ data Connection = Connection
|
|||
connLevel :: Int,
|
||||
viaContact :: Maybe Int64, -- group member contact ID, if not direct connection
|
||||
viaUserContactLink :: Maybe Int64, -- user contact link ID, if connected via "user address"
|
||||
customUserProfileId :: Maybe Int64,
|
||||
connType :: ConnType,
|
||||
connStatus :: ConnStatus,
|
||||
entityId :: Maybe Int64, -- contact, group member, file ID or user contact ID
|
||||
|
@ -705,6 +745,9 @@ data Connection = Connection
|
|||
aConnId :: Connection -> ConnId
|
||||
aConnId Connection {agentConnId = AgentConnId cId} = cId
|
||||
|
||||
connCustomUserProfileId :: Connection -> Maybe Int64
|
||||
connCustomUserProfileId Connection {customUserProfileId} = customUserProfileId
|
||||
|
||||
instance ToJSON Connection where
|
||||
toJSON = J.genericToJSON J.defaultOptions {J.omitNothingFields = True}
|
||||
toEncoding = J.genericToEncoding J.defaultOptions {J.omitNothingFields = True}
|
||||
|
@ -715,6 +758,7 @@ data PendingContactConnection = PendingContactConnection
|
|||
pccConnStatus :: ConnStatus,
|
||||
viaContactUri :: Bool,
|
||||
viaUserContactLink :: Maybe Int64,
|
||||
customUserProfileId :: Maybe Int64,
|
||||
createdAt :: UTCTime,
|
||||
updatedAt :: UTCTime
|
||||
}
|
||||
|
|
|
@ -54,7 +54,7 @@ serializeChatResponse = unlines . map unStyle . responseToView False
|
|||
|
||||
responseToView :: Bool -> ChatResponse -> [StyledString]
|
||||
responseToView testView = \case
|
||||
CRActiveUser User {profile} -> viewUserProfile profile
|
||||
CRActiveUser User {profile} -> viewUserProfile $ fromLocalProfile profile
|
||||
CRChatStarted -> ["chat started"]
|
||||
CRChatRunning -> ["chat is running"]
|
||||
CRChatStopped -> ["chat stopped"]
|
||||
|
@ -64,8 +64,8 @@ responseToView testView = \case
|
|||
CRApiParsedMarkdown ft -> [plain . bshow $ J.encode ft]
|
||||
CRUserSMPServers smpServers -> viewSMPServers smpServers testView
|
||||
CRNetworkConfig cfg -> viewNetworkConfig cfg
|
||||
CRContactInfo ct cStats -> viewContactInfo ct cStats
|
||||
CRGroupMemberInfo g m cStats -> viewGroupMemberInfo g m cStats
|
||||
CRContactInfo ct cStats customUserProfile -> viewContactInfo ct cStats customUserProfile
|
||||
CRGroupMemberInfo g m cStats mainProfile -> viewGroupMemberInfo g m cStats mainProfile
|
||||
CRNewChatItem (AChatItem _ _ chat item) -> viewChatItem chat item False
|
||||
CRLastMessages chatItems -> concatMap (\(AChatItem _ _ chat item) -> viewChatItem chat item True) chatItems
|
||||
CRChatItemStatusUpdated _ -> []
|
||||
|
@ -89,10 +89,10 @@ responseToView testView = \case
|
|||
CRUserContactLink cReqUri autoAccept autoReply -> connReqContact_ "Your chat address:" cReqUri <> autoAcceptStatus_ autoAccept autoReply
|
||||
CRUserContactLinkUpdated _ autoAccept autoReply -> autoAcceptStatus_ autoAccept autoReply
|
||||
CRContactRequestRejected UserContactRequest {localDisplayName = c} -> [ttyContact c <> ": contact request rejected"]
|
||||
CRGroupCreated g -> viewGroupCreated g
|
||||
CRGroupCreated g customUserProfile -> viewGroupCreated g customUserProfile testView
|
||||
CRGroupMembers g -> viewGroupMembers g
|
||||
CRGroupsList gs -> viewGroupsList gs
|
||||
CRSentGroupInvitation g c _ -> ["invitation to join the group " <> ttyGroup' g <> " sent to " <> ttyContact' c]
|
||||
CRSentGroupInvitation g c _ sentCustomProfile -> viewSentGroupInvitation g c sentCustomProfile
|
||||
CRFileTransferStatus ftStatus -> viewFileTransferStatus ftStatus
|
||||
CRUserProfile p -> viewUserProfile p
|
||||
CRUserProfileNoChange -> ["user profile did not change"]
|
||||
|
@ -100,7 +100,7 @@ responseToView testView = \case
|
|||
CRChatCmdError e -> viewChatError e
|
||||
CRInvitation cReq -> viewConnReqInvitation cReq
|
||||
CRSentConfirmation -> ["confirmation sent!"]
|
||||
CRSentInvitation -> ["connection request sent!"]
|
||||
CRSentInvitation customUserProfile -> viewSentInvitation customUserProfile testView
|
||||
CRContactDeleted c -> [ttyContact' c <> ": contact is deleted"]
|
||||
CRChatCleared chatInfo -> viewChatCleared chatInfo
|
||||
CRAcceptingContactRequest c -> [ttyFullContact c <> ": accepting contact request..."]
|
||||
|
@ -129,7 +129,7 @@ responseToView testView = \case
|
|||
CRSndFileRcvCancelled _ ft@SndFileTransfer {recipientDisplayName = c} ->
|
||||
[ttyContact c <> " cancelled receiving " <> sndFile ft]
|
||||
CRContactConnecting _ -> []
|
||||
CRContactConnected ct -> [ttyFullContact ct <> ": contact is connected"]
|
||||
CRContactConnected ct userCustomProfile -> viewContactConnected ct userCustomProfile testView
|
||||
CRContactAnotherClient c -> [ttyContact' c <> ": contact is connected to another client"]
|
||||
CRContactsDisconnected srv cs -> [plain $ "server disconnected " <> showSMPServer srv <> " (" <> contactList cs <> ")"]
|
||||
CRContactsSubscribed srv cs -> [plain $ "server connected " <> showSMPServer srv <> " (" <> contactList cs <> ")"]
|
||||
|
@ -138,13 +138,13 @@ responseToView testView = \case
|
|||
[sShow (length subscribed) <> " contacts connected (use " <> highlight' "/cs" <> " for the list)" | not (null subscribed)] <> viewErrorsSummary errors " contact errors"
|
||||
where
|
||||
(errors, subscribed) = partition (isJust . contactError) summary
|
||||
CRGroupInvitation GroupInfo {localDisplayName = ldn, groupProfile = GroupProfile {fullName}, membership} ->
|
||||
[groupInvitation' ldn fullName $ memberIncognito membership]
|
||||
CRReceivedGroupInvitation g c role receivedCustomProfile -> viewReceivedGroupInvitation g c role receivedCustomProfile
|
||||
CRUserJoinedGroup g _ usedCustomProfile -> viewUserJoinedGroup g usedCustomProfile testView
|
||||
CRJoinedGroupMember g m mainProfile -> viewJoinedGroupMember g m mainProfile
|
||||
CRHostConnected p h -> [plain $ "connected to " <> viewHostEvent p h]
|
||||
CRHostDisconnected p h -> [plain $ "disconnected from " <> viewHostEvent p h]
|
||||
CRGroupInvitation GroupInfo {localDisplayName = ldn, groupProfile = GroupProfile {fullName}} ->
|
||||
[groupInvitation' ldn fullName]
|
||||
CRReceivedGroupInvitation g c role -> viewReceivedGroupInvitation g c role
|
||||
CRUserJoinedGroup g _ -> [ttyGroup' g <> ": you joined the group"]
|
||||
CRJoinedGroupMember g m -> [ttyGroup' g <> ": " <> ttyMember m <> " joined the group "]
|
||||
CRJoinedGroupMemberConnecting g host m -> [ttyGroup' g <> ": " <> ttyMember host <> " added " <> ttyFullMember m <> " to the group (connecting...)"]
|
||||
CRConnectedToGroupMember g m -> [ttyGroup' g <> ": " <> connectedMember m <> " is connected"]
|
||||
CRDeletedMemberUser g by -> [ttyGroup' g <> ": " <> ttyMember by <> " removed you from the group"] <> groupPreserved g
|
||||
|
@ -156,7 +156,7 @@ responseToView testView = \case
|
|||
CRGroupUpdated g g' m -> viewGroupUpdated g g' m
|
||||
CRMemberSubError g m e -> [ttyGroup' g <> " member " <> ttyMember m <> " error: " <> sShow e]
|
||||
CRMemberSubSummary summary -> viewErrorsSummary (filter (isJust . memberError) summary) " group member errors"
|
||||
CRGroupSubscribed g -> [ttyFullGroup g <> ": connected to server(s)"]
|
||||
CRGroupSubscribed g -> viewGroupSubscribed g
|
||||
CRPendingSubSummary _ -> []
|
||||
CRSndFileSubError SndFileTransfer {fileId, fileName} e ->
|
||||
["sent file " <> sShow fileId <> " (" <> plain fileName <> ") error: " <> sShow e]
|
||||
|
@ -208,6 +208,12 @@ responseToView testView = \case
|
|||
contactList :: [ContactRef] -> String
|
||||
contactList cs = T.unpack . T.intercalate ", " $ map (\ContactRef {localDisplayName = n} -> "@" <> n) cs
|
||||
|
||||
viewGroupSubscribed :: GroupInfo -> [StyledString]
|
||||
viewGroupSubscribed g@GroupInfo {membership} =
|
||||
[incognito <> ttyFullGroup g <> ": connected to server(s)"]
|
||||
where
|
||||
incognito = if memberIncognito membership then incognitoPrefix else ""
|
||||
|
||||
showSMPServer :: SMPServer -> String
|
||||
showSMPServer = B.unpack . strEncode . host
|
||||
|
||||
|
@ -363,6 +369,12 @@ viewConnReqInvitation cReq =
|
|||
"and ask them to connect: " <> highlight' "/c <invitation_link_above>"
|
||||
]
|
||||
|
||||
viewSentGroupInvitation :: GroupInfo -> Contact -> Maybe Profile -> [StyledString]
|
||||
viewSentGroupInvitation g c sentCustomProfile =
|
||||
if isJust sentCustomProfile
|
||||
then ["invitation to join the group " <> ttyGroup' g <> " incognito sent to " <> ttyContact' c]
|
||||
else ["invitation to join the group " <> ttyGroup' g <> " sent to " <> ttyContact' c]
|
||||
|
||||
viewChatCleared :: AChatInfo -> [StyledString]
|
||||
viewChatCleared (AChatInfo _ chatInfo) = case chatInfo of
|
||||
DirectChat ct -> [ttyContact' ct <> ": all messages are removed locally ONLY"]
|
||||
|
@ -372,7 +384,8 @@ viewChatCleared (AChatInfo _ chatInfo) = case chatInfo of
|
|||
viewContactsList :: [Contact] -> [StyledString]
|
||||
viewContactsList =
|
||||
let ldn = T.toLower . (localDisplayName :: Contact -> ContactName)
|
||||
in map ttyFullContact . sortOn ldn
|
||||
incognito ct = if contactConnIncognito ct then incognitoPrefix else ""
|
||||
in map (\ct -> incognito ct <> ttyFullContact ct) . sortOn ldn
|
||||
|
||||
viewUserContactLinkDeleted :: [StyledString]
|
||||
viewUserContactLinkDeleted =
|
||||
|
@ -396,6 +409,17 @@ autoAcceptStatus_ autoAccept autoReply =
|
|||
("auto_accept " <> if autoAccept then "on" else "off") :
|
||||
maybe [] ((["auto reply:"] <>) . ttyMsgContent) autoReply
|
||||
|
||||
viewSentInvitation :: Maybe Profile -> Bool -> [StyledString]
|
||||
viewSentInvitation incognitoProfile testView =
|
||||
case incognitoProfile of
|
||||
Just profile ->
|
||||
if testView
|
||||
then incognitoProfile' profile : message
|
||||
else message
|
||||
where
|
||||
message = ["connection request sent incognito!"]
|
||||
Nothing -> ["connection request sent!"]
|
||||
|
||||
viewReceivedContactRequest :: ContactName -> Profile -> [StyledString]
|
||||
viewReceivedContactRequest c Profile {fullName} =
|
||||
[ ttyFullName c fullName <> " wants to connect to you!",
|
||||
|
@ -403,11 +427,22 @@ viewReceivedContactRequest c Profile {fullName} =
|
|||
"to reject: " <> highlight ("/rc " <> c) <> " (the sender will NOT be notified)"
|
||||
]
|
||||
|
||||
viewGroupCreated :: GroupInfo -> [StyledString]
|
||||
viewGroupCreated g@GroupInfo {localDisplayName} =
|
||||
[ "group " <> ttyFullGroup g <> " is created",
|
||||
"use " <> highlight ("/a " <> localDisplayName <> " <name>") <> " to add members"
|
||||
]
|
||||
viewGroupCreated :: GroupInfo -> Maybe Profile -> Bool -> [StyledString]
|
||||
viewGroupCreated g@GroupInfo {localDisplayName} incognitoProfile testView =
|
||||
case incognitoProfile of
|
||||
Just profile ->
|
||||
if testView
|
||||
then incognitoProfile' profile : message
|
||||
else message
|
||||
where
|
||||
message =
|
||||
[ "group " <> ttyFullGroup g <> " is created incognito, your profile for this group: " <> incognitoProfile' profile,
|
||||
"use " <> highlight ("/a " <> localDisplayName <> " <name>") <> " to add members"
|
||||
]
|
||||
Nothing ->
|
||||
[ "group " <> ttyFullGroup g <> " is created",
|
||||
"use " <> highlight ("/a " <> localDisplayName <> " <name>") <> " to add members"
|
||||
]
|
||||
|
||||
viewCannotResendInvitation :: GroupInfo -> ContactName -> [StyledString]
|
||||
viewCannotResendInvitation GroupInfo {localDisplayName = gn} c =
|
||||
|
@ -415,11 +450,33 @@ viewCannotResendInvitation GroupInfo {localDisplayName = gn} c =
|
|||
"to re-send invitation: " <> highlight ("/rm " <> gn <> " " <> c) <> ", " <> highlight ("/a " <> gn <> " " <> c)
|
||||
]
|
||||
|
||||
viewReceivedGroupInvitation :: GroupInfo -> Contact -> GroupMemberRole -> [StyledString]
|
||||
viewReceivedGroupInvitation g c role =
|
||||
[ ttyFullGroup g <> ": " <> ttyContact' c <> " invites you to join the group as " <> plain (strEncode role),
|
||||
"use " <> highlight ("/j " <> groupName' g) <> " to accept"
|
||||
]
|
||||
viewUserJoinedGroup :: GroupInfo -> Bool -> Bool -> [StyledString]
|
||||
viewUserJoinedGroup g@GroupInfo {membership = GroupMember {memberProfile}} incognito testView =
|
||||
if incognito
|
||||
then
|
||||
if testView
|
||||
then incognitoProfile' (fromLocalProfile memberProfile) : incognitoMessage
|
||||
else incognitoMessage
|
||||
else [ttyGroup' g <> ": you joined the group"]
|
||||
where
|
||||
incognitoMessage = [ttyGroup' g <> ": you joined the group incognito as " <> incognitoProfile' (fromLocalProfile memberProfile)]
|
||||
|
||||
viewJoinedGroupMember :: GroupInfo -> GroupMember -> Maybe Profile -> [StyledString]
|
||||
viewJoinedGroupMember g m@GroupMember {localDisplayName} = \case
|
||||
Just Profile {displayName = mainProfileName} -> [ttyGroup' g <> ": " <> ttyContact mainProfileName <> " joined the group incognito as " <> styleIncognito localDisplayName]
|
||||
Nothing -> [ttyGroup' g <> ": " <> ttyMember m <> " joined the group "]
|
||||
|
||||
viewReceivedGroupInvitation :: GroupInfo -> Contact -> GroupMemberRole -> Maybe Profile -> [StyledString]
|
||||
viewReceivedGroupInvitation g c role hostIncognitoProfile =
|
||||
case hostIncognitoProfile of
|
||||
Just profile ->
|
||||
[ ttyFullGroup g <> ": " <> ttyContact' c <> " (known to the group as " <> incognitoProfile' profile <> ") invites you to join the group incognito as " <> plain (strEncode role),
|
||||
"use " <> highlight ("/j " <> groupName' g) <> " to join this group incognito"
|
||||
]
|
||||
Nothing ->
|
||||
[ ttyFullGroup g <> ": " <> ttyContact' c <> " invites you to join the group as " <> plain (strEncode role),
|
||||
"use " <> highlight ("/j " <> groupName' g) <> " to accept"
|
||||
]
|
||||
|
||||
groupPreserved :: GroupInfo -> [StyledString]
|
||||
groupPreserved g = ["use " <> highlight ("/d #" <> groupName' g) <> " to delete the group"]
|
||||
|
@ -434,7 +491,8 @@ viewGroupMembers :: Group -> [StyledString]
|
|||
viewGroupMembers (Group GroupInfo {membership} members) = map groupMember . filter (not . removedOrLeft) $ membership : members
|
||||
where
|
||||
removedOrLeft m = let s = memberStatus m in s == GSMemRemoved || s == GSMemLeft
|
||||
groupMember m = ttyFullMember m <> ": " <> role m <> ", " <> category m <> status m
|
||||
groupMember m = incognito m <> ttyFullMember m <> ": " <> role m <> ", " <> category m <> status m
|
||||
incognito m = if memberIncognito m then incognitoPrefix else ""
|
||||
role m = plain . strEncode $ memberRole (m :: GroupMember)
|
||||
category m = case memberCategory m of
|
||||
GCUserMember -> "you, "
|
||||
|
@ -450,6 +508,21 @@ viewGroupMembers (Group GroupInfo {membership} members) = map groupMember . filt
|
|||
GSMemCreator -> "created group"
|
||||
_ -> ""
|
||||
|
||||
viewContactConnected :: Contact -> Maybe Profile -> Bool -> [StyledString]
|
||||
viewContactConnected ct@Contact {localDisplayName} userIncognitoProfile testView =
|
||||
case userIncognitoProfile of
|
||||
Just profile ->
|
||||
if testView
|
||||
then incognitoProfile' profile : message
|
||||
else message
|
||||
where
|
||||
message =
|
||||
[ ttyFullContact ct <> ": contact is connected, your incognito profile for this contact is " <> incognitoProfile' profile,
|
||||
"use " <> highlight ("/info " <> localDisplayName) <> " to print out this incognito profile again"
|
||||
]
|
||||
Nothing ->
|
||||
[ttyFullContact ct <> ": contact is connected"]
|
||||
|
||||
viewGroupsList :: [GroupInfo] -> [StyledString]
|
||||
viewGroupsList [] = ["you have no groups!", "to create: " <> highlight' "/g <name>"]
|
||||
viewGroupsList gs = map groupSS $ sortOn ldn_ gs
|
||||
|
@ -457,9 +530,10 @@ viewGroupsList gs = map groupSS $ sortOn ldn_ gs
|
|||
ldn_ = T.toLower . (localDisplayName :: GroupInfo -> GroupName)
|
||||
groupSS GroupInfo {localDisplayName = ldn, groupProfile = GroupProfile {fullName}, membership} =
|
||||
case memberStatus membership of
|
||||
GSMemInvited -> groupInvitation' ldn fullName
|
||||
s -> ttyGroup ldn <> optFullName ldn fullName <> viewMemberStatus s
|
||||
GSMemInvited -> groupInvitation' ldn fullName $ memberIncognito membership
|
||||
s -> incognito <> ttyGroup ldn <> optFullName ldn fullName <> viewMemberStatus s
|
||||
where
|
||||
incognito = if memberIncognito membership then incognitoPrefix else ""
|
||||
viewMemberStatus = \case
|
||||
GSMemRemoved -> delete "you are removed"
|
||||
GSMemLeft -> delete "you left"
|
||||
|
@ -467,15 +541,20 @@ viewGroupsList gs = map groupSS $ sortOn ldn_ gs
|
|||
_ -> ""
|
||||
delete reason = " (" <> reason <> ", delete local copy: " <> highlight ("/d #" <> ldn) <> ")"
|
||||
|
||||
groupInvitation' :: GroupName -> Text -> StyledString
|
||||
groupInvitation' displayName fullName =
|
||||
groupInvitation' :: GroupName -> Text -> Bool -> StyledString
|
||||
groupInvitation' displayName fullName membershipIncognito =
|
||||
highlight ("#" <> displayName)
|
||||
<> optFullName displayName fullName
|
||||
<> " - you are invited ("
|
||||
<> invitationText
|
||||
<> highlight ("/j " <> displayName)
|
||||
<> " to join, "
|
||||
<> highlight ("/d #" <> displayName)
|
||||
<> " to delete invitation)"
|
||||
where
|
||||
invitationText =
|
||||
if membershipIncognito
|
||||
then " - you are invited incognito ("
|
||||
else " - you are invited ("
|
||||
|
||||
viewContactsMerged :: Contact -> Contact -> [StyledString]
|
||||
viewContactsMerged _into@Contact {localDisplayName = c1} _merged@Contact {localDisplayName = c2} =
|
||||
|
@ -514,16 +593,24 @@ viewNetworkConfig NetworkConfig {socksProxy, tcpTimeout} =
|
|||
"use `/network socks=<on/off/[ipv4]:port>[ timeout=<seconds>]` to change settings"
|
||||
]
|
||||
|
||||
viewContactInfo :: Contact -> ConnectionStats -> [StyledString]
|
||||
viewContactInfo Contact {contactId} stats =
|
||||
viewContactInfo :: Contact -> ConnectionStats -> Maybe Profile -> [StyledString]
|
||||
viewContactInfo Contact {contactId} stats incognitoProfile =
|
||||
["contact ID: " <> sShow contactId] <> viewConnectionStats stats
|
||||
<> maybe
|
||||
["you've shared main profile with this contact"]
|
||||
(\p -> ["you've shared incognito profile with this contact: " <> incognitoProfile' p])
|
||||
incognitoProfile
|
||||
|
||||
viewGroupMemberInfo :: GroupInfo -> GroupMember -> Maybe ConnectionStats -> [StyledString]
|
||||
viewGroupMemberInfo GroupInfo {groupId} GroupMember {groupMemberId} stats =
|
||||
viewGroupMemberInfo :: GroupInfo -> GroupMember -> Maybe ConnectionStats -> Maybe Profile -> [StyledString]
|
||||
viewGroupMemberInfo GroupInfo {groupId} GroupMember {groupMemberId} stats mainProfile =
|
||||
[ "group ID: " <> sShow groupId,
|
||||
"member ID: " <> sShow groupMemberId
|
||||
]
|
||||
<> maybe ["member not connected"] viewConnectionStats stats
|
||||
<> maybe
|
||||
["unknown whether group member uses his main profile or incognito one for the group"]
|
||||
(\Profile {displayName, fullName} -> ["member is using " <> styleIncognito' "incognito" <> " profile for the group, main profile known: " <> ttyFullName displayName fullName])
|
||||
mainProfile
|
||||
|
||||
viewConnectionStats :: ConnectionStats -> [StyledString]
|
||||
viewConnectionStats ConnectionStats {rcvServers, sndServers} =
|
||||
|
@ -559,8 +646,8 @@ viewGroupUpdated
|
|||
|
||||
viewContactUpdated :: Contact -> Contact -> [StyledString]
|
||||
viewContactUpdated
|
||||
Contact {localDisplayName = n, profile = Profile {fullName}}
|
||||
Contact {localDisplayName = n', profile = Profile {fullName = fullName'}}
|
||||
Contact {localDisplayName = n, profile = LocalProfile {fullName}}
|
||||
Contact {localDisplayName = n', profile = LocalProfile {fullName = fullName'}}
|
||||
| n == n' && fullName == fullName' = []
|
||||
| n == n' = ["contact " <> ttyContact n <> fullNameUpdate]
|
||||
| otherwise =
|
||||
|
@ -817,6 +904,7 @@ viewChatError = \case
|
|||
CEGroupDuplicateMember c -> ["contact " <> ttyContact c <> " is already in the group"]
|
||||
CEGroupDuplicateMemberId -> ["cannot add member - duplicate member ID"]
|
||||
CEGroupUserRole -> ["you have insufficient permissions for this group command"]
|
||||
CEGroupNotIncognitoCantInvite -> ["you're using main profile for this group - prohibited to invite contact to whom you are connected incognito"]
|
||||
CEGroupContactRole c -> ["contact " <> ttyContact c <> " has insufficient permissions for this group action"]
|
||||
CEGroupNotJoined g -> ["you did not join this group, use " <> highlight ("/join #" <> groupName' g)]
|
||||
CEGroupMemberNotActive -> ["you cannot invite other members yet, try later"]
|
||||
|
@ -883,14 +971,14 @@ ttyContact' :: Contact -> StyledString
|
|||
ttyContact' Contact {localDisplayName = c} = ttyContact c
|
||||
|
||||
ttyFullContact :: Contact -> StyledString
|
||||
ttyFullContact Contact {localDisplayName, profile = Profile {fullName}} =
|
||||
ttyFullContact Contact {localDisplayName, profile = LocalProfile {fullName}} =
|
||||
ttyFullName localDisplayName fullName
|
||||
|
||||
ttyMember :: GroupMember -> StyledString
|
||||
ttyMember GroupMember {localDisplayName} = ttyContact localDisplayName
|
||||
|
||||
ttyFullMember :: GroupMember -> StyledString
|
||||
ttyFullMember GroupMember {localDisplayName, memberProfile = Profile {fullName}} =
|
||||
ttyFullMember GroupMember {localDisplayName, memberProfile = LocalProfile {fullName}} =
|
||||
ttyFullName localDisplayName fullName
|
||||
|
||||
ttyFullName :: ContactName -> Text -> StyledString
|
||||
|
@ -909,7 +997,8 @@ ttyFromContactDeleted :: ContactName -> StyledString
|
|||
ttyFromContactDeleted c = ttyFrom $ c <> "> [deleted] "
|
||||
|
||||
ttyToContact' :: Contact -> StyledString
|
||||
ttyToContact' Contact {localDisplayName = c} = ttyToContact c
|
||||
ttyToContact' Contact {localDisplayName = c, activeConn = Connection {customUserProfileId}} =
|
||||
maybe "" (const incognitoPrefix) customUserProfileId <> ttyToContact c
|
||||
|
||||
ttyQuotedContact :: Contact -> StyledString
|
||||
ttyQuotedContact Contact {localDisplayName = c} = ttyFrom $ c <> ">"
|
||||
|
@ -919,7 +1008,8 @@ ttyQuotedMember (Just GroupMember {localDisplayName = c}) = "> " <> ttyFrom c
|
|||
ttyQuotedMember _ = "> " <> ttyFrom "?"
|
||||
|
||||
ttyFromContact' :: Contact -> StyledString
|
||||
ttyFromContact' Contact {localDisplayName = c} = ttyFromContact c
|
||||
ttyFromContact' Contact {localDisplayName = c, activeConn = Connection {customUserProfileId}} =
|
||||
maybe "" (const incognitoPrefix) customUserProfileId <> ttyFromContact c
|
||||
|
||||
ttyGroup :: GroupName -> StyledString
|
||||
ttyGroup g = styled (colored Blue) $ "#" <> g
|
||||
|
@ -949,10 +1039,12 @@ ttyFrom :: Text -> StyledString
|
|||
ttyFrom = styled $ colored Yellow
|
||||
|
||||
ttyFromGroup' :: GroupInfo -> GroupMember -> StyledString
|
||||
ttyFromGroup' g GroupMember {localDisplayName = m} = ttyFromGroup g m
|
||||
ttyFromGroup' g@GroupInfo {membership} GroupMember {localDisplayName = m} =
|
||||
(if memberIncognito membership then incognitoPrefix else "") <> ttyFromGroup g m
|
||||
|
||||
ttyToGroup :: GroupInfo -> StyledString
|
||||
ttyToGroup GroupInfo {localDisplayName = g} = styled (colored Cyan) $ "#" <> g <> " "
|
||||
ttyToGroup GroupInfo {localDisplayName = g, membership} =
|
||||
(if memberIncognito membership then incognitoPrefix else "") <> styled (colored Cyan) ("#" <> g <> " ")
|
||||
|
||||
ttyFilePath :: FilePath -> StyledString
|
||||
ttyFilePath = plain
|
||||
|
@ -960,12 +1052,24 @@ ttyFilePath = plain
|
|||
optFullName :: ContactName -> Text -> StyledString
|
||||
optFullName localDisplayName fullName = plain $ optionalFullName localDisplayName fullName
|
||||
|
||||
incognitoPrefix :: StyledString
|
||||
incognitoPrefix = styleIncognito' "i "
|
||||
|
||||
incognitoProfile' :: Profile -> StyledString
|
||||
incognitoProfile' Profile {displayName} = styleIncognito displayName
|
||||
|
||||
highlight :: StyledFormat a => a -> StyledString
|
||||
highlight = styled $ colored Cyan
|
||||
|
||||
highlight' :: String -> StyledString
|
||||
highlight' = highlight
|
||||
|
||||
styleIncognito :: StyledFormat a => a -> StyledString
|
||||
styleIncognito = styled $ colored Magenta
|
||||
|
||||
styleIncognito' :: String -> StyledString
|
||||
styleIncognito' = styleIncognito
|
||||
|
||||
styleTime :: String -> StyledString
|
||||
styleTime = Styled [SetColor Foreground Vivid Black]
|
||||
|
||||
|
|
|
@ -19,7 +19,7 @@ import qualified Data.Text as T
|
|||
import Simplex.Chat.Call
|
||||
import Simplex.Chat.Controller (ChatController (..))
|
||||
import Simplex.Chat.Options (ChatOpts (..))
|
||||
import Simplex.Chat.Types (ConnStatus (..), ImageData (..), Profile (..), User (..))
|
||||
import Simplex.Chat.Types (ConnStatus (..), ImageData (..), LocalProfile (..), Profile (..), User (..))
|
||||
import Simplex.Messaging.Util (unlessM)
|
||||
import System.Directory (copyFile, doesDirectoryExist, doesFileExist)
|
||||
import System.FilePath ((</>))
|
||||
|
@ -88,6 +88,13 @@ chatTests = do
|
|||
it "reject contact and delete contact link" testRejectContactAndDeleteUserContact
|
||||
it "delete connection requests when contact link deleted" testDeleteConnectionRequests
|
||||
it "auto-reply message" testAutoReplyMessage
|
||||
describe "incognito mode" $ do
|
||||
it "connect incognito via invitation link" testConnectIncognitoInvitationLink
|
||||
it "connect incognito via contact address" testConnectIncognitoContactAddress
|
||||
it "accept contact request incognito" testAcceptContactRequestIncognito
|
||||
it "create group incognito" testCreateGroupIncognito
|
||||
it "join group incognito" testJoinGroupIncognito
|
||||
it "can't invite contact to whom user connected incognito to non incognito group" testCantInviteIncognitoConnectionNonIncognitoGroup
|
||||
describe "SMP servers" $
|
||||
it "get and set SMP servers" testGetSetSMPServers
|
||||
describe "async connection handshake" $ do
|
||||
|
@ -2045,6 +2052,394 @@ testAutoReplyMessage = testChat2 aliceProfile bobProfile $
|
|||
alice <# "@bob hello!"
|
||||
]
|
||||
|
||||
testConnectIncognitoInvitationLink :: IO ()
|
||||
testConnectIncognitoInvitationLink = testChat3 aliceProfile bobProfile cathProfile $
|
||||
\alice bob cath -> do
|
||||
alice #$> ("/incognito on", id, "ok")
|
||||
bob #$> ("/incognito on", id, "ok")
|
||||
alice ##> "/c"
|
||||
inv <- getInvitation alice
|
||||
bob ##> ("/c " <> inv)
|
||||
bob <## "confirmation sent!"
|
||||
bobIncognito <- getTermLine bob
|
||||
aliceIncognito <- getTermLine alice
|
||||
concurrentlyN_
|
||||
[ do
|
||||
bob <## (aliceIncognito <> ": contact is connected, your incognito profile for this contact is " <> bobIncognito)
|
||||
bob <## ("use /info " <> aliceIncognito <> " to print out this incognito profile again"),
|
||||
do
|
||||
alice <## (bobIncognito <> ": contact is connected, your incognito profile for this contact is " <> aliceIncognito)
|
||||
alice <## ("use /info " <> bobIncognito <> " to print out this incognito profile again")
|
||||
]
|
||||
-- after turning incognito mode off conversation is incognito
|
||||
alice #$> ("/incognito off", id, "ok")
|
||||
bob #$> ("/incognito off", id, "ok")
|
||||
alice ?#> ("@" <> bobIncognito <> " psst, I'm incognito")
|
||||
bob ?<# (aliceIncognito <> "> psst, I'm incognito")
|
||||
bob ?#> ("@" <> aliceIncognito <> " <whispering> me too")
|
||||
alice ?<# (bobIncognito <> "> <whispering> me too")
|
||||
-- new contact is connected non incognito
|
||||
connectUsers alice cath
|
||||
alice <##> cath
|
||||
-- bob is not notified on profile change
|
||||
alice ##> "/p alice"
|
||||
concurrentlyN_
|
||||
[ alice <## "user full name removed (your contacts are notified)",
|
||||
cath <## "contact alice removed full name"
|
||||
]
|
||||
alice ?#> ("@" <> bobIncognito <> " do you see that I've changed profile?")
|
||||
bob ?<# (aliceIncognito <> "> do you see that I've changed profile?")
|
||||
bob ?#> ("@" <> aliceIncognito <> " no")
|
||||
alice ?<# (bobIncognito <> "> no")
|
||||
|
||||
testConnectIncognitoContactAddress :: IO ()
|
||||
testConnectIncognitoContactAddress = testChat2 aliceProfile bobProfile $
|
||||
\alice bob -> do
|
||||
alice ##> "/ad"
|
||||
cLink <- getContactLink alice True
|
||||
bob #$> ("/incognito on", id, "ok")
|
||||
bob ##> ("/c " <> cLink)
|
||||
bobIncognito <- getTermLine bob
|
||||
bob <## "connection request sent incognito!"
|
||||
alice <## (bobIncognito <> " wants to connect to you!")
|
||||
alice <## ("to accept: /ac " <> bobIncognito)
|
||||
alice <## ("to reject: /rc " <> bobIncognito <> " (the sender will NOT be notified)")
|
||||
alice ##> ("/ac " <> bobIncognito)
|
||||
alice <## (bobIncognito <> ": accepting contact request...")
|
||||
_ <- getTermLine bob
|
||||
concurrentlyN_
|
||||
[ do
|
||||
bob <## ("alice (Alice): contact is connected, your incognito profile for this contact is " <> bobIncognito)
|
||||
bob <## "use /info alice to print out this incognito profile again",
|
||||
alice <## (bobIncognito <> ": contact is connected")
|
||||
]
|
||||
-- after turning incognito mode off conversation is incognito
|
||||
alice #$> ("/incognito off", id, "ok")
|
||||
bob #$> ("/incognito off", id, "ok")
|
||||
alice #> ("@" <> bobIncognito <> " who are you?")
|
||||
bob ?<# "alice> who are you?"
|
||||
bob ?#> "@alice I'm Batman"
|
||||
alice <# (bobIncognito <> "> I'm Batman")
|
||||
|
||||
testAcceptContactRequestIncognito :: IO ()
|
||||
testAcceptContactRequestIncognito = testChat2 aliceProfile bobProfile $
|
||||
\alice bob -> do
|
||||
alice ##> "/ad"
|
||||
cLink <- getContactLink alice True
|
||||
bob ##> ("/c " <> cLink)
|
||||
alice <#? bob
|
||||
alice #$> ("/incognito on", id, "ok")
|
||||
alice ##> "/ac bob"
|
||||
alice <## "bob (Bob): accepting contact request..."
|
||||
aliceIncognito <- getTermLine alice
|
||||
concurrentlyN_
|
||||
[ bob <## (aliceIncognito <> ": contact is connected"),
|
||||
do
|
||||
alice <## ("bob (Bob): contact is connected, your incognito profile for this contact is " <> aliceIncognito)
|
||||
alice <## "use /info bob to print out this incognito profile again"
|
||||
]
|
||||
-- after turning incognito mode off conversation is incognito
|
||||
alice #$> ("/incognito off", id, "ok")
|
||||
bob #$> ("/incognito off", id, "ok")
|
||||
alice ?#> "@bob my profile is totally inconspicuous"
|
||||
bob <# (aliceIncognito <> "> my profile is totally inconspicuous")
|
||||
bob #> ("@" <> aliceIncognito <> " I know!")
|
||||
alice ?<# "bob> I know!"
|
||||
|
||||
testCreateGroupIncognito :: IO ()
|
||||
testCreateGroupIncognito = testChat3 aliceProfile bobProfile cathProfile $
|
||||
\alice bob cath -> do
|
||||
-- non incognito connections
|
||||
connectUsers alice cath
|
||||
connectUsers bob cath
|
||||
-- bob connected incognito to alice
|
||||
alice ##> "/c"
|
||||
inv <- getInvitation alice
|
||||
bob #$> ("/incognito on", id, "ok")
|
||||
bob ##> ("/c " <> inv)
|
||||
bob <## "confirmation sent!"
|
||||
bobIncognito <- getTermLine bob
|
||||
concurrentlyN_
|
||||
[ do
|
||||
bob <## ("alice (Alice): contact is connected, your incognito profile for this contact is " <> bobIncognito)
|
||||
bob <## "use /info alice to print out this incognito profile again",
|
||||
alice <## (bobIncognito <> ": contact is connected")
|
||||
]
|
||||
-- alice creates group incognito
|
||||
alice #$> ("/incognito on", id, "ok")
|
||||
alice ##> "/g secret_club"
|
||||
aliceMemIncognito <- getTermLine alice
|
||||
alice <## ("group #secret_club is created incognito, your profile for this group: " <> aliceMemIncognito)
|
||||
alice <## "use /a secret_club <name> to add members"
|
||||
alice ##> ("/a secret_club " <> bobIncognito)
|
||||
concurrentlyN_
|
||||
[ alice <## ("invitation to join the group #secret_club incognito sent to " <> bobIncognito),
|
||||
do
|
||||
bob <## ("#secret_club: alice (known to the group as " <> aliceMemIncognito <> ") invites you to join the group incognito as admin")
|
||||
bob <## "use /j secret_club to join this group incognito"
|
||||
]
|
||||
-- bob uses different profile when joining group
|
||||
bob ##> "/j secret_club"
|
||||
bobMemIncognito <- getTermLine bob
|
||||
concurrently_
|
||||
(alice <## ("#secret_club: " <> bobIncognito <> " joined the group incognito as " <> bobMemIncognito))
|
||||
(bob <## ("#secret_club: you joined the group incognito as " <> bobMemIncognito))
|
||||
-- cath is invited incognito
|
||||
alice ##> "/a secret_club cath"
|
||||
concurrentlyN_
|
||||
[ alice <## "invitation to join the group #secret_club incognito sent to cath",
|
||||
do
|
||||
cath <## ("#secret_club: alice (known to the group as " <> aliceMemIncognito <> ") invites you to join the group incognito as admin")
|
||||
cath <## "use /j secret_club to join this group incognito"
|
||||
]
|
||||
cath ##> "/j secret_club"
|
||||
cathMemIncognito <- getTermLine cath
|
||||
-- bob and cath don't merge contacts
|
||||
concurrentlyN_
|
||||
[ alice <## ("#secret_club: cath joined the group incognito as " <> cathMemIncognito),
|
||||
do
|
||||
cath <## ("#secret_club: you joined the group incognito as " <> cathMemIncognito)
|
||||
cath <## ("#secret_club: member " <> bobMemIncognito <> " is connected"),
|
||||
do
|
||||
bob <## ("#secret_club: " <> aliceMemIncognito <> " added " <> cathMemIncognito <> " to the group (connecting...)")
|
||||
bob <## ("#secret_club: new member " <> cathMemIncognito <> " is connected")
|
||||
]
|
||||
-- send messages - group is incognito for everybody
|
||||
alice #$> ("/incognito off", id, "ok")
|
||||
bob #$> ("/incognito off", id, "ok")
|
||||
cath #$> ("/incognito off", id, "ok")
|
||||
alice ?#> "#secret_club hello"
|
||||
concurrently_
|
||||
(bob ?<# ("#secret_club " <> aliceMemIncognito <> "> hello"))
|
||||
(cath ?<# ("#secret_club " <> aliceMemIncognito <> "> hello"))
|
||||
bob ?#> "#secret_club hi there"
|
||||
concurrently_
|
||||
(alice ?<# ("#secret_club " <> bobMemIncognito <> "> hi there"))
|
||||
(cath ?<# ("#secret_club " <> bobMemIncognito <> "> hi there"))
|
||||
cath ?#> "#secret_club hey"
|
||||
concurrently_
|
||||
(alice ?<# ("#secret_club " <> cathMemIncognito <> "> hey"))
|
||||
(bob ?<# ("#secret_club " <> cathMemIncognito <> "> hey"))
|
||||
-- bob and cath can send messages via direct incognito connections
|
||||
bob ?#> ("@" <> cathMemIncognito <> " hi, I'm bob")
|
||||
cath ?<# (bobMemIncognito <> "> hi, I'm bob")
|
||||
cath ?#> ("@" <> bobMemIncognito <> " hey, I'm cath")
|
||||
bob ?<# (cathMemIncognito <> "> hey, I'm cath")
|
||||
-- non incognito connections are separate
|
||||
bob <##> cath
|
||||
-- list groups
|
||||
alice ##> "/gs"
|
||||
alice <## "i #secret_club"
|
||||
-- list group members
|
||||
alice ##> "/ms secret_club"
|
||||
alice
|
||||
<### [ "i " <> aliceMemIncognito <> ": owner, you, created group",
|
||||
"i " <> bobMemIncognito <> ": admin, invited, connected",
|
||||
"i " <> cathMemIncognito <> ": admin, invited, connected"
|
||||
]
|
||||
-- remove member
|
||||
bob ##> ("/rm secret_club " <> cathMemIncognito)
|
||||
concurrentlyN_
|
||||
[ bob <## ("#secret_club: you removed " <> cathMemIncognito <> " from the group"),
|
||||
alice <## ("#secret_club: " <> bobMemIncognito <> " removed " <> cathMemIncognito <> " from the group"),
|
||||
do
|
||||
cath <## ("#secret_club: " <> bobMemIncognito <> " removed you from the group")
|
||||
cath <## "use /d #secret_club to delete the group"
|
||||
]
|
||||
bob ?#> "#secret_club hi"
|
||||
concurrently_
|
||||
(alice ?<# ("#secret_club " <> bobMemIncognito <> "> hi"))
|
||||
(cath </)
|
||||
alice ?#> "#secret_club hello"
|
||||
concurrently_
|
||||
(bob ?<# ("#secret_club " <> aliceMemIncognito <> "> hello"))
|
||||
(cath </)
|
||||
cath ##> "#secret_club hello"
|
||||
cath <## "you are no longer a member of the group"
|
||||
bob ?#> ("@" <> cathMemIncognito <> " I removed you from group")
|
||||
cath ?<# (bobMemIncognito <> "> I removed you from group")
|
||||
cath ?#> ("@" <> bobMemIncognito <> " ok")
|
||||
bob ?<# (cathMemIncognito <> "> ok")
|
||||
|
||||
testJoinGroupIncognito :: IO ()
|
||||
testJoinGroupIncognito = testChat4 aliceProfile bobProfile cathProfile danProfile $
|
||||
\alice bob cath dan -> do
|
||||
-- non incognito connections
|
||||
connectUsers alice cath
|
||||
connectUsers bob cath
|
||||
connectUsers cath dan
|
||||
-- bob connected incognito to alice
|
||||
alice ##> "/c"
|
||||
inv <- getInvitation alice
|
||||
bob #$> ("/incognito on", id, "ok")
|
||||
bob ##> ("/c " <> inv)
|
||||
bob <## "confirmation sent!"
|
||||
bobIncognito <- getTermLine bob
|
||||
concurrentlyN_
|
||||
[ do
|
||||
bob <## ("alice (Alice): contact is connected, your incognito profile for this contact is " <> bobIncognito)
|
||||
bob <## "use /info alice to print out this incognito profile again",
|
||||
alice <## (bobIncognito <> ": contact is connected")
|
||||
]
|
||||
-- alice creates group non incognito
|
||||
alice ##> "/g club"
|
||||
alice <## "group #club is created"
|
||||
alice <## "use /a club <name> to add members"
|
||||
alice ##> ("/a club " <> bobIncognito)
|
||||
concurrentlyN_
|
||||
[ alice <## ("invitation to join the group #club sent to " <> bobIncognito),
|
||||
do
|
||||
bob <## "#club: alice invites you to join the group as admin"
|
||||
bob <## "use /j club to accept"
|
||||
]
|
||||
-- since bob is connected incognito to host, he uses different profile when joining group even though he turned incognito mode off
|
||||
bob #$> ("/incognito off", id, "ok")
|
||||
bob ##> "/j club"
|
||||
bobMemIncognito <- getTermLine bob
|
||||
concurrently_
|
||||
(alice <## ("#club: " <> bobIncognito <> " joined the group incognito as " <> bobMemIncognito))
|
||||
(bob <## ("#club: you joined the group incognito as " <> bobMemIncognito))
|
||||
-- cath joins incognito
|
||||
alice ##> "/a club cath"
|
||||
concurrentlyN_
|
||||
[ alice <## "invitation to join the group #club sent to cath",
|
||||
do
|
||||
cath <## "#club: alice invites you to join the group as admin"
|
||||
cath <## "use /j club to accept"
|
||||
]
|
||||
cath #$> ("/incognito on", id, "ok")
|
||||
cath ##> "/j club"
|
||||
cathMemIncognito <- getTermLine cath
|
||||
-- bob and cath don't merge contacts
|
||||
concurrentlyN_
|
||||
[ alice <## ("#club: cath joined the group incognito as " <> cathMemIncognito),
|
||||
do
|
||||
cath <## ("#club: you joined the group incognito as " <> cathMemIncognito)
|
||||
cath <## ("#club: member " <> bobMemIncognito <> " is connected"),
|
||||
do
|
||||
bob <## ("#club: alice added " <> cathMemIncognito <> " to the group (connecting...)")
|
||||
bob <## ("#club: new member " <> cathMemIncognito <> " is connected")
|
||||
]
|
||||
-- cath invites dan incognito
|
||||
cath ##> "/a club dan"
|
||||
concurrentlyN_
|
||||
[ cath <## "invitation to join the group #club incognito sent to dan",
|
||||
do
|
||||
dan <## ("#club: cath (known to the group as " <> cathMemIncognito <> ") invites you to join the group incognito as admin")
|
||||
dan <## "use /j club to join this group incognito"
|
||||
]
|
||||
dan ##> "/j club"
|
||||
danMemIncognito <- getTermLine dan
|
||||
concurrentlyN_
|
||||
[ cath <## ("#club: dan joined the group incognito as " <> danMemIncognito),
|
||||
do
|
||||
dan <## ("#club: you joined the group incognito as " <> danMemIncognito)
|
||||
dan
|
||||
<### [ "#club: member alice (Alice) is connected",
|
||||
"#club: member " <> bobMemIncognito <> " is connected"
|
||||
],
|
||||
do
|
||||
alice <## ("#club: " <> cathMemIncognito <> " added " <> danMemIncognito <> " to the group (connecting...)")
|
||||
alice <## ("#club: new member " <> danMemIncognito <> " is connected"),
|
||||
do
|
||||
bob <## ("#club: " <> cathMemIncognito <> " added " <> danMemIncognito <> " to the group (connecting...)")
|
||||
bob <## ("#club: new member " <> danMemIncognito <> " is connected")
|
||||
]
|
||||
-- send messages - group is incognito for cath and dan
|
||||
alice #$> ("/incognito off", id, "ok")
|
||||
bob #$> ("/incognito off", id, "ok")
|
||||
cath #$> ("/incognito off", id, "ok")
|
||||
dan #$> ("/incognito off", id, "ok")
|
||||
alice #> "#club hello"
|
||||
concurrentlyN_
|
||||
[ bob ?<# "#club alice> hello",
|
||||
cath ?<# "#club alice> hello",
|
||||
dan ?<# "#club alice> hello"
|
||||
]
|
||||
bob ?#> "#club hi there"
|
||||
concurrentlyN_
|
||||
[ alice <# ("#club " <> bobMemIncognito <> "> hi there"),
|
||||
cath ?<# ("#club " <> bobMemIncognito <> "> hi there"),
|
||||
dan ?<# ("#club " <> bobMemIncognito <> "> hi there")
|
||||
]
|
||||
cath ?#> "#club hey"
|
||||
concurrentlyN_
|
||||
[ alice <# ("#club " <> cathMemIncognito <> "> hey"),
|
||||
bob ?<# ("#club " <> cathMemIncognito <> "> hey"),
|
||||
dan ?<# ("#club " <> cathMemIncognito <> "> hey")
|
||||
]
|
||||
dan ?#> "#club how is it going?"
|
||||
concurrentlyN_
|
||||
[ alice <# ("#club " <> danMemIncognito <> "> how is it going?"),
|
||||
bob ?<# ("#club " <> danMemIncognito <> "> how is it going?"),
|
||||
cath ?<# ("#club " <> danMemIncognito <> "> how is it going?")
|
||||
]
|
||||
-- bob and cath can send messages via direct incognito connections
|
||||
bob ?#> ("@" <> cathMemIncognito <> " hi, I'm bob")
|
||||
cath ?<# (bobMemIncognito <> "> hi, I'm bob")
|
||||
cath ?#> ("@" <> bobMemIncognito <> " hey, I'm cath")
|
||||
bob ?<# (cathMemIncognito <> "> hey, I'm cath")
|
||||
-- non incognito connections are separate
|
||||
bob <##> cath
|
||||
-- bob and dan can send messages via direct incognito connections
|
||||
bob ?#> ("@" <> danMemIncognito <> " hi, I'm bob")
|
||||
dan ?<# (bobMemIncognito <> "> hi, I'm bob")
|
||||
dan ?#> ("@" <> bobMemIncognito <> " hey, I'm dan")
|
||||
bob ?<# (danMemIncognito <> "> hey, I'm dan")
|
||||
-- list group members
|
||||
alice ##> "/ms club"
|
||||
alice
|
||||
<### [ "alice (Alice): owner, you, created group",
|
||||
"i " <> bobMemIncognito <> ": admin, invited, connected",
|
||||
"i " <> cathMemIncognito <> ": admin, invited, connected",
|
||||
danMemIncognito <> ": admin, connected"
|
||||
]
|
||||
bob ##> "/ms club"
|
||||
bob
|
||||
<### [ "alice (Alice): owner, host, connected",
|
||||
"i " <> bobMemIncognito <> ": admin, you, connected",
|
||||
cathMemIncognito <> ": admin, connected",
|
||||
danMemIncognito <> ": admin, connected"
|
||||
]
|
||||
cath ##> "/ms club"
|
||||
cath
|
||||
<### [ "alice (Alice): owner, host, connected",
|
||||
bobMemIncognito <> ": admin, connected",
|
||||
"i " <> cathMemIncognito <> ": admin, you, connected",
|
||||
"i " <> danMemIncognito <> ": admin, invited, connected"
|
||||
]
|
||||
dan ##> "/ms club"
|
||||
dan
|
||||
<### [ "alice (Alice): owner, connected",
|
||||
bobMemIncognito <> ": admin, connected",
|
||||
"i " <> cathMemIncognito <> ": admin, host, connected",
|
||||
"i " <> danMemIncognito <> ": admin, you, connected"
|
||||
]
|
||||
|
||||
testCantInviteIncognitoConnectionNonIncognitoGroup :: IO ()
|
||||
testCantInviteIncognitoConnectionNonIncognitoGroup = testChat2 aliceProfile bobProfile $
|
||||
\alice bob -> do
|
||||
-- alice connected incognito to bob
|
||||
alice #$> ("/incognito on", id, "ok")
|
||||
alice ##> "/c"
|
||||
inv <- getInvitation alice
|
||||
bob ##> ("/c " <> inv)
|
||||
bob <## "confirmation sent!"
|
||||
aliceIncognito <- getTermLine alice
|
||||
concurrentlyN_
|
||||
[ bob <## (aliceIncognito <> ": contact is connected"),
|
||||
do
|
||||
alice <## ("bob (Bob): contact is connected, your incognito profile for this contact is " <> aliceIncognito)
|
||||
alice <## "use /info bob to print out this incognito profile again"
|
||||
]
|
||||
-- alice creates group non incognito
|
||||
alice #$> ("/incognito off", id, "ok")
|
||||
alice ##> "/g club"
|
||||
alice <## "group #club is created"
|
||||
alice <## "use /a club <name> to add members"
|
||||
alice ##> "/a club bob"
|
||||
alice <## "you're using main profile for this group - prohibited to invite contact to whom you are connected incognito"
|
||||
|
||||
testGetSetSMPServers :: IO ()
|
||||
testGetSetSMPServers =
|
||||
testChat2 aliceProfile bobProfile $
|
||||
|
@ -2513,7 +2908,7 @@ connectUsers cc1 cc2 = do
|
|||
|
||||
showName :: TestCC -> IO String
|
||||
showName (TestCC ChatController {currentUser} _ _ _ _) = do
|
||||
Just User {localDisplayName, profile = Profile {fullName}} <- readTVarIO currentUser
|
||||
Just User {localDisplayName, profile = LocalProfile {fullName}} <- readTVarIO currentUser
|
||||
pure . T.unpack $ localDisplayName <> " (" <> fullName <> ")"
|
||||
|
||||
createGroup2 :: String -> TestCC -> TestCC -> IO ()
|
||||
|
@ -2580,6 +2975,11 @@ cc #> cmd = do
|
|||
cc `send` cmd
|
||||
cc <# cmd
|
||||
|
||||
(?#>) :: TestCC -> String -> IO ()
|
||||
cc ?#> cmd = do
|
||||
cc `send` cmd
|
||||
cc <# ("i " <> cmd)
|
||||
|
||||
(#$>) :: (Eq a, Show a) => TestCC -> (String, String -> a, a) -> Expectation
|
||||
cc #$> (cmd, f, res) = do
|
||||
cc ##> cmd
|
||||
|
@ -2632,6 +3032,9 @@ getInAnyOrder f cc ls = do
|
|||
(<#) :: TestCC -> String -> Expectation
|
||||
cc <# line = (dropTime <$> getTermLine cc) `shouldReturn` line
|
||||
|
||||
(?<#) :: TestCC -> String -> Expectation
|
||||
cc ?<# line = (dropTime <$> getTermLine cc) `shouldReturn` "i " <> line
|
||||
|
||||
(</) :: TestCC -> Expectation
|
||||
(</) = (<// 500000)
|
||||
|
||||
|
|
|
@ -31,9 +31,9 @@ activeUserExists = "{\"resp\":{\"type\":\"chatCmdError\",\"chatError\":{\"type\"
|
|||
|
||||
activeUser :: String
|
||||
#if defined(darwin_HOST_OS) && defined(swiftJSON)
|
||||
activeUser = "{\"resp\":{\"activeUser\":{\"user\":{\"userId\":1,\"userContactId\":1,\"localDisplayName\":\"alice\",\"profile\":{\"displayName\":\"alice\",\"fullName\":\"Alice\"},\"activeUser\":true}}}}"
|
||||
activeUser = "{\"resp\":{\"activeUser\":{\"user\":{\"userId\":1,\"userContactId\":1,\"localDisplayName\":\"alice\",\"profile\":{\"profileId\":1,\"displayName\":\"alice\",\"fullName\":\"Alice\"},\"activeUser\":true}}}}"
|
||||
#else
|
||||
activeUser = "{\"resp\":{\"type\":\"activeUser\",\"user\":{\"userId\":1,\"userContactId\":1,\"localDisplayName\":\"alice\",\"profile\":{\"displayName\":\"alice\",\"fullName\":\"Alice\"},\"activeUser\":true}}}"
|
||||
activeUser = "{\"resp\":{\"type\":\"activeUser\",\"user\":{\"userId\":1,\"userContactId\":1,\"localDisplayName\":\"alice\",\"profile\":{\"profileId\":1,\"displayName\":\"alice\",\"fullName\":\"Alice\"},\"activeUser\":true}}}"
|
||||
#endif
|
||||
|
||||
chatStarted :: String
|
||||
|
|
|
@ -187,12 +187,18 @@ decodeChatMessageTest = describe "Chat message encoding/decoding" $ do
|
|||
it "x.contact with content (ignored)" $
|
||||
"{\"event\":\"x.contact\",\"params\":{\"content\":{\"text\":\"hello\",\"type\":\"text\"},\"profile\":{\"fullName\":\"Alice\",\"displayName\":\"alice\",\"image\":\"data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAAAgAAAAIAQMAAAD+wSzIAAAABlBMVEX///+/v7+jQ3Y5AAAADklEQVQI12P4AIX8EAgALgAD/aNpbtEAAAAASUVORK5CYII=\"}}}"
|
||||
==# XContact testProfile Nothing
|
||||
it "x.grp.inv" $
|
||||
it "x.grp.inv with incognito profile" $
|
||||
"{\"event\":\"x.grp.inv\",\"params\":{\"groupInvitation\":{\"connRequest\":\"https://simplex.chat/invitation#/?v=1&smp=smp%3A%2F%2F1234-w%3D%3D%40smp.simplex.im%3A5223%2F3456-w%3D%3D%23%2F%3Fv%3D1-2%26dh%3DMCowBQYDK2VuAyEAjiswwI3O_NlS8Fk3HJUW870EY2bAwmttMBsvRB9eV3o%253D&e2e=v%3D1%26x3dh%3DMEIwBQYDK2VvAzkAmKuSYeQ_m0SixPDS8Wq8VBaTS1cW-Lp0n0h4Diu-kUpR-qXx4SDJ32YGEFoGFGSbGPry5Ychr6U%3D%2CMEIwBQYDK2VvAzkAmKuSYeQ_m0SixPDS8Wq8VBaTS1cW-Lp0n0h4Diu-kUpR-qXx4SDJ32YGEFoGFGSbGPry5Ychr6U%3D\",\"invitedMember\":{\"memberRole\":\"member\",\"memberId\":\"BQYHCA==\"},\"groupProfile\":{\"fullName\":\"Team\",\"displayName\":\"team\"},\"fromMember\":{\"memberRole\":\"admin\",\"memberId\":\"AQIDBA==\"},\"fromMemberProfile\":{\"fullName\":\"Alice\",\"displayName\":\"alice\",\"image\":\"data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAAAgAAAAIAQMAAAD+wSzIAAAABlBMVEX///+/v7+jQ3Y5AAAADklEQVQI12P4AIX8EAgALgAD/aNpbtEAAAAASUVORK5CYII=\"}}}}"
|
||||
#==# XGrpInv GroupInvitation {fromMember = MemberIdRole (MemberId "\1\2\3\4") GRAdmin, fromMemberProfile = Just testProfile, invitedMember = MemberIdRole (MemberId "\5\6\7\8") GRMember, connRequest = testConnReq, groupProfile = testGroupProfile}
|
||||
it "x.grp.inv without incognito profile" $
|
||||
"{\"event\":\"x.grp.inv\",\"params\":{\"groupInvitation\":{\"connRequest\":\"https://simplex.chat/invitation#/?v=1&smp=smp%3A%2F%2F1234-w%3D%3D%40smp.simplex.im%3A5223%2F3456-w%3D%3D%23%2F%3Fv%3D1-2%26dh%3DMCowBQYDK2VuAyEAjiswwI3O_NlS8Fk3HJUW870EY2bAwmttMBsvRB9eV3o%253D&e2e=v%3D1%26x3dh%3DMEIwBQYDK2VvAzkAmKuSYeQ_m0SixPDS8Wq8VBaTS1cW-Lp0n0h4Diu-kUpR-qXx4SDJ32YGEFoGFGSbGPry5Ychr6U%3D%2CMEIwBQYDK2VvAzkAmKuSYeQ_m0SixPDS8Wq8VBaTS1cW-Lp0n0h4Diu-kUpR-qXx4SDJ32YGEFoGFGSbGPry5Ychr6U%3D\",\"invitedMember\":{\"memberRole\":\"member\",\"memberId\":\"BQYHCA==\"},\"groupProfile\":{\"fullName\":\"Team\",\"displayName\":\"team\"},\"fromMember\":{\"memberRole\":\"admin\",\"memberId\":\"AQIDBA==\"}}}}"
|
||||
#==# XGrpInv GroupInvitation {fromMember = MemberIdRole (MemberId "\1\2\3\4") GRAdmin, invitedMember = MemberIdRole (MemberId "\5\6\7\8") GRMember, connRequest = testConnReq, groupProfile = testGroupProfile}
|
||||
it "x.grp.acpt" $
|
||||
#==# XGrpInv GroupInvitation {fromMember = MemberIdRole (MemberId "\1\2\3\4") GRAdmin, fromMemberProfile = Nothing, invitedMember = MemberIdRole (MemberId "\5\6\7\8") GRMember, connRequest = testConnReq, groupProfile = testGroupProfile}
|
||||
it "x.grp.acpt with incognito profile" $
|
||||
"{\"event\":\"x.grp.acpt\",\"params\":{\"memberId\":\"AQIDBA==\", \"memberProfile\":{\"fullName\":\"Alice\",\"displayName\":\"alice\",\"image\":\"data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAAAgAAAAIAQMAAAD+wSzIAAAABlBMVEX///+/v7+jQ3Y5AAAADklEQVQI12P4AIX8EAgALgAD/aNpbtEAAAAASUVORK5CYII=\"}}}"
|
||||
#==# XGrpAcpt (MemberId "\1\2\3\4") (Just testProfile)
|
||||
it "x.grp.acpt without incognito profile" $
|
||||
"{\"event\":\"x.grp.acpt\",\"params\":{\"memberId\":\"AQIDBA==\"}}"
|
||||
#==# XGrpAcpt (MemberId "\1\2\3\4")
|
||||
#==# XGrpAcpt (MemberId "\1\2\3\4") Nothing
|
||||
it "x.grp.mem.new" $
|
||||
"{\"event\":\"x.grp.mem.new\",\"params\":{\"memberInfo\":{\"memberRole\":\"admin\",\"memberId\":\"AQIDBA==\",\"profile\":{\"fullName\":\"Alice\",\"displayName\":\"alice\",\"image\":\"data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAAAgAAAAIAQMAAAD+wSzIAAAABlBMVEX///+/v7+jQ3Y5AAAADklEQVQI12P4AIX8EAgALgAD/aNpbtEAAAAASUVORK5CYII=\"}}}}"
|
||||
#==# XGrpMemNew MemberInfo {memberId = MemberId "\1\2\3\4", memberRole = GRAdmin, profile = testProfile}
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue