2021-07-06 19:07:03 +01:00
{- # LANGUAGE DataKinds # -}
2021-07-04 18:42:24 +01:00
{- # LANGUAGE DuplicateRecordFields # -}
2021-06-25 18:18:24 +01:00
{- # LANGUAGE FlexibleContexts # -}
{- # LANGUAGE GADTs # -}
{- # LANGUAGE LambdaCase # -}
2022-10-14 13:06:33 +01:00
{- # LANGUAGE MultiWayIf # -}
2021-06-25 18:18:24 +01:00
{- # LANGUAGE NamedFieldPuns # -}
{- # LANGUAGE OverloadedStrings # -}
2021-07-04 18:42:24 +01:00
{- # LANGUAGE RankNTypes # -}
{- # LANGUAGE ScopedTypeVariables # -}
2021-07-25 20:23:52 +01:00
{- # LANGUAGE TupleSections # -}
2022-01-11 12:41:38 +00:00
{- # LANGUAGE TypeApplications # -}
2021-06-25 18:18:24 +01:00
module Simplex.Chat where
2021-09-04 07:32:56 +01:00
import Control.Applicative ( optional , ( <|> ) )
2022-09-28 20:47:06 +04:00
import Control.Concurrent.STM ( retry , stateTVar )
2021-07-07 22:46:38 +01:00
import Control.Logger.Simple
2021-06-25 18:18:24 +01:00
import Control.Monad.Except
import Control.Monad.IO.Unlift
import Control.Monad.Reader
2021-07-12 19:00:03 +01:00
import Crypto.Random ( drgNew )
2022-03-13 19:34:03 +00:00
import qualified Data.Aeson as J
2021-07-12 19:00:03 +01:00
import Data.Attoparsec.ByteString.Char8 ( Parser )
2021-06-25 18:18:24 +01:00
import qualified Data.Attoparsec.ByteString.Char8 as A
2022-10-14 13:06:33 +01:00
import Data.Bifunctor ( bimap , first )
2022-03-10 15:45:40 +04:00
import qualified Data.ByteString.Base64 as B64
2021-06-25 18:18:24 +01:00
import Data.ByteString.Char8 ( ByteString )
2021-07-11 12:22:22 +01:00
import qualified Data.ByteString.Char8 as B
2022-09-05 14:54:39 +01:00
import Data.Char ( isSpace )
2022-07-04 11:15:25 +01:00
import Data.Either ( fromRight )
2022-05-04 13:31:00 +01:00
import Data.Fixed ( div' )
2021-06-25 18:18:24 +01:00
import Data.Functor ( ( $> ) )
2021-09-04 07:32:56 +01:00
import Data.Int ( Int64 )
2022-08-18 11:35:31 +04:00
import Data.List ( find , isSuffixOf , sortOn )
2022-03-10 15:45:40 +04:00
import Data.List.NonEmpty ( NonEmpty , nonEmpty )
import qualified Data.List.NonEmpty as L
2021-09-04 07:32:56 +01:00
import Data.Map.Strict ( Map )
import qualified Data.Map.Strict as M
2022-07-17 15:51:17 +01:00
import Data.Maybe ( fromMaybe , isJust , isNothing , mapMaybe )
2021-07-04 18:42:24 +01:00
import Data.Text ( Text )
2021-06-25 18:18:24 +01:00
import qualified Data.Text as T
2022-10-05 19:54:28 +04:00
import Data.Time ( NominalDiffTime , addUTCTime )
2022-05-04 13:31:00 +01:00
import Data.Time.Clock ( UTCTime , diffUTCTime , getCurrentTime , nominalDiffTimeToSeconds )
2022-06-19 14:44:13 +01:00
import Data.Time.Clock.System ( SystemTime , systemToUTCTime )
2022-03-29 08:53:30 +01:00
import Data.Time.LocalTime ( getCurrentTimeZone , getZonedTime )
2022-06-18 20:06:13 +01:00
import qualified Database.SQLite.Simple as DB
2022-06-06 16:23:47 +01:00
import Simplex.Chat.Archive
2022-05-03 10:22:35 +01:00
import Simplex.Chat.Call
2021-06-25 18:18:24 +01:00
import Simplex.Chat.Controller
2022-02-22 14:05:45 +00:00
import Simplex.Chat.Markdown
2022-01-24 16:07:17 +00:00
import Simplex.Chat.Messages
2022-08-02 15:36:12 +01:00
import Simplex.Chat.Options
2022-08-18 11:35:31 +04:00
import Simplex.Chat.ProfileGenerator ( generateRandomProfile )
2021-07-04 18:42:24 +01:00
import Simplex.Chat.Protocol
2021-07-05 20:05:07 +01:00
import Simplex.Chat.Store
2021-07-04 18:42:24 +01:00
import Simplex.Chat.Types
2022-10-04 01:33:36 +04:00
import Simplex.Chat.Util ( safeDecodeUtf8 , uncurry3 )
2022-07-17 15:51:17 +01:00
import Simplex.Messaging.Agent as Agent
2022-09-23 19:22:56 +01:00
import Simplex.Messaging.Agent.Env.SQLite ( AgentConfig ( .. ) , AgentDatabase ( .. ) , InitialAgentServers ( .. ) , createAgentStore , defaultAgentConfig )
2021-06-25 18:18:24 +01:00
import Simplex.Messaging.Agent.Protocol
2022-10-01 15:19:41 +01:00
import Simplex.Messaging.Agent.Store.SQLite ( SQLiteStore ( dbNew ) , execSQL )
2022-08-02 15:36:12 +01:00
import Simplex.Messaging.Client ( defaultNetworkConfig )
2021-07-27 08:08:05 +01:00
import qualified Simplex.Messaging.Crypto as C
2022-01-11 12:41:38 +00:00
import Simplex.Messaging.Encoding
2022-01-11 08:50:44 +00:00
import Simplex.Messaging.Encoding.String
2022-03-10 15:45:40 +04:00
import Simplex.Messaging.Parsers ( base64P , parseAll )
2022-07-06 08:46:04 +01:00
import Simplex.Messaging.Protocol ( ErrorType ( .. ) , MsgBody , MsgFlags ( .. ) , NtfServer )
2021-09-04 07:32:56 +01:00
import qualified Simplex.Messaging.Protocol as SMP
2022-05-04 13:31:00 +01:00
import qualified Simplex.Messaging.TMap as TM
2022-07-25 14:04:27 +01:00
import Simplex.Messaging.Transport.Client ( defaultSocksProxy )
2022-07-17 15:51:17 +01:00
import Simplex.Messaging.Util
2021-07-27 08:08:05 +01:00
import System.Exit ( exitFailure , exitSuccess )
2021-09-04 07:32:56 +01:00
import System.FilePath ( combine , splitExtensions , takeFileName )
import System.IO ( Handle , IOMode ( .. ) , SeekMode ( .. ) , hFlush , openFile , stdout )
2021-07-05 19:54:44 +01:00
import Text.Read ( readMaybe )
2022-02-25 16:29:36 +04:00
import UnliftIO.Async
2021-09-04 07:32:56 +01:00
import UnliftIO.Concurrent ( forkIO , threadDelay )
2022-04-15 13:16:34 +01:00
import UnliftIO.Directory
2021-08-05 20:51:48 +01:00
import qualified UnliftIO.Exception as E
2021-09-04 07:32:56 +01:00
import UnliftIO.IO ( hClose , hSeek , hTell )
2021-06-25 18:18:24 +01:00
import UnliftIO.STM
2021-08-02 20:10:24 +01:00
defaultChatConfig :: ChatConfig
defaultChatConfig =
ChatConfig
{ agentConfig =
defaultAgentConfig
{ tcpPort = undefined , -- agent does not listen to TCP
2022-09-23 19:22:56 +01:00
database = AgentDBFile { dbFile = " simplex_v1_agent " , dbKey = " " } ,
2022-02-07 15:19:34 +04:00
yesToMigrations = False
2021-08-02 20:10:24 +01:00
} ,
2022-02-07 15:19:34 +04:00
yesToMigrations = False ,
2022-07-23 14:49:04 +01:00
defaultServers =
InitialAgentServers
{ smp = _defaultSMPServers ,
ntf = _defaultNtfServers ,
2022-08-02 15:36:12 +01:00
netCfg = defaultNetworkConfig
2022-07-23 14:49:04 +01:00
} ,
2022-02-25 16:29:36 +04:00
tbqSize = 64 ,
2022-10-14 13:06:33 +01:00
fileChunkSize = 15780 , -- do not change
inlineFiles = defaultInlineFilesConfig ,
2022-02-26 10:04:25 +00:00
subscriptionConcurrency = 16 ,
2022-02-25 16:29:36 +04:00
subscriptionEvents = False ,
2022-08-13 14:18:12 +01:00
hostEvents = False ,
2022-02-09 20:58:02 +04:00
testView = False
2021-07-07 22:46:38 +01:00
}
2022-05-11 16:52:08 +01:00
_defaultSMPServers :: NonEmpty SMPServer
_defaultSMPServers =
2022-03-10 15:45:40 +04:00
L . fromList
2022-08-13 11:53:53 +01:00
[ " smp://0YuTwO05YJWS8rkjn9eLJDjQhFKvIYd8d4xG8X1blIU=@smp8.simplex.im,beccx4yfxxbvyhqypaavemqurytl6hozr47wfc7uuecacjqdvwpw2xid.onion " ,
" smp://SkIkI6EPd2D63F4xFKfHk7I1UGZVNn6k1QWZ5rcyr6w=@smp9.simplex.im,jssqzccmrcws6bhmn77vgmhfjmhwlyr3u7puw4erkyoosywgl67slqqd.onion " ,
" smp://6iIcWT_dF2zN_w5xzZEY7HI2Prbh3ldP07YTyDexPjE=@smp10.simplex.im,rb2pbttocvnbrngnwziclp2f4ckjq65kebafws6g4hy22cdaiv5dwjqd.onion "
2022-03-10 15:45:40 +04:00
]
2022-05-11 16:52:08 +01:00
_defaultNtfServers :: [ NtfServer ]
2022-08-13 11:53:53 +01:00
_defaultNtfServers = [ " ntf://FB-Uop7RTaZZEG0ZLD2CIaTjsPh-Fw0zFAnb7QyA8Ks=@ntf2.simplex.im,ntg7jdjy2i3qbib3sykiho3enekwiaqg3icctliqhtqcg6jmoh6cxiad.onion " ]
2022-04-22 13:46:05 +01:00
2022-05-21 18:17:15 +04:00
maxImageSize :: Integer
maxImageSize = 236700
fixedImagePreview :: ImageData
fixedImagePreview = ImageData " data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAAEAAAABACAYAAACqaXHeAAAAAXNSR0IArs4c6QAAAKVJREFUeF7t1kENACEUQ0FQhnVQ9lfGO+xggITQdvbMzArPey+8fa3tAfwAEdABZQspQStgBssEcgAIkSAJkiAJljtEgiRIgmUCSZAESZAESZAEyx0iQRIkwTKBJEiCv5fgvTd1wDmn7QAP4AeIgA4oW0gJWgEzWCZwbQ7gAA7ggLKFOIADOKBMIAeAEAmSIAmSYLlDJEiCJFgmkARJkARJ8N8S/ADTZUewBvnTOQAAAABJRU5ErkJggg== "
2021-07-07 22:46:38 +01:00
logCfg :: LogConfig
logCfg = LogConfig { lc_file = Nothing , lc_stderr = True }
2022-09-23 19:22:56 +01:00
createChatDatabase :: FilePath -> String -> Bool -> IO ChatDatabase
createChatDatabase filePrefix key yesToMigrations = do
chatStore <- createChatStore ( chatStoreFile filePrefix ) key yesToMigrations
agentStore <- createAgentStore ( agentStoreFile filePrefix ) key yesToMigrations
pure ChatDatabase { chatStore , agentStore }
newChatController :: ChatDatabase -> Maybe User -> ChatConfig -> ChatOpts -> Maybe ( Notification -> IO () ) -> IO ChatController
newChatController ChatDatabase { chatStore , agentStore } user cfg @ ChatConfig { agentConfig = aCfg , tbqSize , defaultServers } ChatOpts { smpServers , networkConfig , logConnections , logServerHosts } sendToast = do
let config = cfg { subscriptionEvents = logConnections , hostEvents = logServerHosts }
2022-04-10 17:13:06 +01:00
sendNotification = fromMaybe ( const $ pure () ) sendToast
2022-09-23 19:22:56 +01:00
firstTime = dbNew chatStore
2022-01-21 11:09:33 +00:00
activeTo <- newTVarIO ActiveNone
currentUser <- newTVarIO user
2022-05-11 16:52:08 +01:00
servers <- resolveServers defaultServers
2022-09-23 19:22:56 +01:00
smpAgent <- getSMPAgentClient aCfg { database = AgentDB agentStore } servers { netCfg = networkConfig }
2022-02-06 16:18:01 +00:00
agentAsync <- newTVarIO Nothing
2021-07-12 19:00:03 +01:00
idsDrg <- newTVarIO =<< drgNew
2021-08-02 20:10:24 +01:00
inputQ <- newTBQueueIO tbqSize
2022-01-21 11:09:33 +00:00
outputQ <- newTBQueueIO tbqSize
2021-08-02 20:10:24 +01:00
notifyQ <- newTBQueueIO tbqSize
2021-08-05 20:51:48 +01:00
chatLock <- newTMVarIO ()
2021-09-04 07:32:56 +01:00
sndFiles <- newTVarIO M . empty
rcvFiles <- newTVarIO M . empty
2022-05-04 13:31:00 +01:00
currentCalls <- atomically TM . empty
2022-04-15 09:36:38 +04:00
filesFolder <- newTVarIO Nothing
2022-08-18 11:35:31 +04:00
incognitoMode <- newTVarIO False
2022-06-06 16:23:47 +01:00
chatStoreChanged <- newTVarIO False
2022-09-28 20:47:06 +04:00
expireCIsAsync <- newTVarIO Nothing
expireCIs <- newTVarIO False
pure ChatController { activeTo , firstTime , currentUser , smpAgent , agentAsync , chatStore , chatStoreChanged , idsDrg , inputQ , outputQ , notifyQ , chatLock , sndFiles , rcvFiles , currentCalls , config , sendNotification , incognitoMode , filesFolder , expireCIsAsync , expireCIs }
2022-03-10 15:45:40 +04:00
where
2022-05-11 16:52:08 +01:00
resolveServers :: InitialAgentServers -> IO InitialAgentServers
resolveServers ss @ InitialAgentServers { smp = defaultSMPServers } = case nonEmpty smpServers of
Just smpServers' -> pure ss { smp = smpServers' }
_ -> case user of
Just usr -> do
2022-06-18 20:06:13 +01:00
userSmpServers <- withTransaction chatStore ( ` getSMPServers ` usr )
2022-05-11 16:52:08 +01:00
pure ss { smp = fromMaybe defaultSMPServers $ nonEmpty userSmpServers }
_ -> pure ss
2021-07-07 22:46:38 +01:00
2022-09-28 20:47:06 +04:00
startChatController :: ( MonadUnliftIO m , MonadReader ChatController m ) => User -> Bool -> Bool -> m ( Async () )
startChatController user subConns enableExpireCIs = do
2022-06-06 16:23:47 +01:00
asks smpAgent >>= resumeAgentClient
2022-07-05 15:15:15 +04:00
restoreCalls user
2022-02-06 16:18:01 +00:00
s <- asks agentAsync
2022-07-02 10:13:06 +01:00
readTVarIO s >>= maybe ( start s ) ( pure . fst )
2022-02-06 16:18:01 +00:00
where
start s = do
2022-07-02 10:13:06 +01:00
a1 <- async $ race_ notificationSubscriber agentSubscriber
a2 <-
if subConns
2022-07-17 15:51:17 +01:00
then Just <$> async ( void . runExceptT $ subscribeUserConnections Agent . subscribeConnections user )
2022-07-02 10:13:06 +01:00
else pure Nothing
atomically . writeTVar s $ Just ( a1 , a2 )
2022-09-28 20:47:06 +04:00
when enableExpireCIs startExpireCIs
2022-07-02 10:13:06 +01:00
pure a1
2022-09-28 20:47:06 +04:00
startExpireCIs = do
expireAsync <- asks expireCIsAsync
readTVarIO expireAsync >>= \ case
Nothing -> do
a <- Just <$> async ( void $ runExceptT runExpireCIs )
atomically $ writeTVar expireAsync a
setExpireCIs True
_ -> setExpireCIs True
2022-10-06 14:00:02 +04:00
runExpireCIs = forever $ do
flip catchError ( toView . CRChatError ) $ do
2022-09-28 20:47:06 +04:00
expire <- asks expireCIs
atomically $ readTVar expire >>= \ b -> unless b retry
ttl <- withStore' ( ` getChatItemTTL ` user )
forM_ ttl $ \ t -> expireChatItems user t False
2022-10-06 14:00:02 +04:00
threadDelay $ 1800 * 1000000 -- 30 minutes
2022-07-05 15:15:15 +04:00
restoreCalls :: ( MonadUnliftIO m , MonadReader ChatController m ) => User -> m ()
restoreCalls user = do
savedCalls <- fromRight [] <$> runExceptT ( withStore' $ \ db -> getCalls db user )
let callsMap = M . fromList $ map ( \ call @ Call { contactId } -> ( contactId , call ) ) savedCalls
calls <- asks currentCalls
atomically $ writeTVar calls callsMap
2022-01-24 16:07:17 +00:00
2022-04-25 16:30:21 +01:00
stopChatController :: MonadUnliftIO m => ChatController -> m ()
2022-09-28 20:47:06 +04:00
stopChatController ChatController { smpAgent , agentAsync = s , expireCIs } = do
2022-04-25 16:30:21 +01:00
disconnectAgentClient smpAgent
2022-07-02 10:13:06 +01:00
readTVarIO s >>= mapM_ ( \ ( a1 , a2 ) -> uninterruptibleCancel a1 >> mapM_ uninterruptibleCancel a2 )
2022-09-28 20:47:06 +04:00
atomically $ do
writeTVar expireCIs False
writeTVar s Nothing
2022-04-25 16:30:21 +01:00
2022-01-24 16:07:17 +00:00
withLock :: MonadUnliftIO m => TMVar () -> m a -> m a
2021-08-05 20:51:48 +01:00
withLock lock =
E . bracket_
( void . atomically $ takeTMVar lock )
( atomically $ putTMVar lock () )
2022-02-04 12:41:43 +00:00
execChatCommand :: ( MonadUnliftIO m , MonadReader ChatController m ) => ByteString -> m ChatResponse
2022-04-10 12:18:53 +01:00
execChatCommand s = case parseChatCommand s of
2022-02-06 16:18:01 +00:00
Left e -> pure $ chatCmdError e
Right cmd -> either CRChatCmdError id <$> runExceptT ( processChatCommand cmd )
2022-01-24 16:07:17 +00:00
2022-04-10 12:18:53 +01:00
parseChatCommand :: ByteString -> Either String ChatCommand
parseChatCommand = parseAll chatCommandP . B . dropWhileEnd isSpace
2022-01-24 16:07:17 +00:00
toView :: ChatMonad m => ChatResponse -> m ()
toView event = do
q <- asks outputQ
2022-01-26 21:20:08 +00:00
atomically $ writeTBQueue q ( Nothing , event )
2022-01-24 16:07:17 +00:00
2022-02-06 16:18:01 +00:00
processChatCommand :: forall m . ChatMonad m => ChatCommand -> m ChatResponse
processChatCommand = \ case
ShowActiveUser -> withUser' $ pure . CRActiveUser
CreateActiveUser p -> do
u <- asks currentUser
whenM ( isJust <$> readTVarIO u ) $ throwChatError CEActiveUserExists
2022-06-18 20:06:13 +01:00
user <- withStore $ \ db -> createUser db p True
2022-02-06 16:18:01 +00:00
atomically . writeTVar u $ Just user
pure $ CRActiveUser user
2022-09-28 20:47:06 +04:00
StartChat subConns enableExpireCIs -> withUser' $ \ user ->
2022-02-26 20:21:32 +00:00
asks agentAsync >>= readTVarIO >>= \ case
Just _ -> pure CRChatRunning
2022-09-28 20:47:06 +04:00
_ -> checkStoreNotChanged $ startChatController user subConns enableExpireCIs $> CRChatStarted
2022-06-06 16:23:47 +01:00
APIStopChat -> do
ask >>= stopChatController
pure CRChatStopped
2022-07-05 15:15:15 +04:00
APIActivateChat -> do
withUser $ \ user -> restoreCalls user
2022-09-28 20:47:06 +04:00
withAgent activateAgent
setExpireCIs True
pure CRCmdOk
APISuspendChat t -> do
setExpireCIs False
withAgent ( ` suspendAgent ` t )
pure CRCmdOk
2022-07-17 15:51:17 +01:00
ResubscribeAllConnections -> withUser ( subscribeUserConnections Agent . resubscribeConnections ) $> CRCmdOk
2022-06-23 21:20:56 +01:00
SetFilesFolder filesFolder' -> do
2022-04-15 09:36:38 +04:00
createDirectoryIfMissing True filesFolder'
ff <- asks filesFolder
atomically . writeTVar ff $ Just filesFolder'
pure CRCmdOk
2022-08-18 11:35:31 +04:00
SetIncognito onOff -> do
incognito <- asks incognitoMode
atomically . writeTVar incognito $ onOff
pure CRCmdOk
2022-06-06 16:23:47 +01:00
APIExportArchive cfg -> checkChatStopped $ exportArchive cfg $> CRCmdOk
2022-08-31 18:07:34 +01:00
APIImportArchive cfg -> withStoreChanged $ importArchive cfg
2022-09-29 16:26:43 +01:00
APIDeleteStorage -> withStoreChanged deleteStorage
2022-09-05 14:54:39 +01:00
APIStorageEncryption cfg -> withStoreChanged $ sqlCipherExport cfg
2022-10-01 15:19:41 +01:00
ExecChatStoreSQL query -> CRSQLResult <$> withStore' ( ` execSQL ` query )
2022-09-17 16:06:27 +01:00
ExecAgentStoreSQL query -> CRSQLResult <$> withAgent ( ` execAgentStoreSQL ` query )
2022-10-07 10:55:47 +04:00
APIGetChats withPCC -> CRApiChats <$> withUser' ( \ user -> withStore' $ \ db -> getChatPreviews db user withPCC )
2022-08-08 22:48:42 +04:00
APIGetChat ( ChatRef cType cId ) pagination search -> withUser $ \ user -> case cType of
CTDirect -> CRApiChat . AChat SCTDirect <$> withStore ( \ db -> getDirectChat db user cId pagination search )
CTGroup -> CRApiChat . AChat SCTGroup <$> withStore ( \ db -> getGroupChat db user cId pagination search )
2022-02-06 16:18:01 +00:00
CTContactRequest -> pure $ chatCmdError " not implemented "
2022-04-23 17:32:40 +01:00
CTContactConnection -> pure $ chatCmdError " not supported "
2022-02-06 16:18:01 +00:00
APIGetChatItems _pagination -> pure $ chatCmdError " not implemented "
2022-05-05 14:04:03 +01:00
APISendMessage ( ChatRef cType chatId ) ( ComposedMessage file_ quotedItemId_ mc ) -> withUser $ \ user @ User { userId } -> withChatLock $ case cType of
2022-01-30 10:49:13 +00:00
CTDirect -> do
2022-06-18 20:06:13 +01:00
ct @ Contact { localDisplayName = c } <- withStore $ \ db -> getContact db userId chatId
2022-10-14 13:06:33 +01:00
( fileInvitation_ , ciFile_ , ft_ ) <- unzipMaybe3 <$> setupSndFileTransfer ct
2022-04-10 13:30:58 +04:00
( msgContainer , quotedItem_ ) <- prepareMsg fileInvitation_
2022-10-14 13:06:33 +01:00
( msg @ SndMessage { sharedMsgId } , _ ) <- sendDirectContactMessage ct ( XMsgNew msgContainer )
case ft_ of
Just ft @ FileTransferMeta { fileInline = Just IFMSent } ->
sendDirectFileInline ct ft sharedMsgId
_ -> pure ()
2022-04-10 13:30:58 +04:00
ci <- saveSndChatItem user ( CDDirectSnd ct ) msg ( CISndMsgContent mc ) ciFile_ quotedItem_
setActive $ ActiveC c
pure . CRNewChatItem $ AChatItem SCTDirect SMDSnd ( DirectChat ct ) ci
where
2022-10-14 13:06:33 +01:00
setupSndFileTransfer :: Contact -> m ( Maybe ( FileInvitation , CIFile 'MDSnd , FileTransferMeta ) )
2022-08-18 11:35:31 +04:00
setupSndFileTransfer ct = forM file_ $ \ file -> do
2022-10-14 13:06:33 +01:00
( fileSize , chSize , fileInline ) <- checkSndFile file 1
( agentConnId_ , fileConnReq ) <-
if isJust fileInline
then pure ( Nothing , Nothing )
else bimap Just Just <$> withAgent ( \ a -> createConnection a True SCMInvitation )
2022-08-18 11:35:31 +04:00
let fileName = takeFileName file
2022-10-14 13:06:33 +01:00
fileInvitation = FileInvitation { fileName , fileSize , fileConnReq , fileInline }
withStore' $ \ db -> do
ft @ FileTransferMeta { fileId } <- createSndDirectFileTransfer db userId ct file fileInvitation agentConnId_ chSize
fileStatus <- case fileInline of
Just IFMSent -> createSndDirectInlineFT db ct ft $> CIFSSndTransfer
_ -> pure CIFSSndStored
let ciFile = CIFile { fileId , fileName , fileSize , filePath = Just file , fileStatus }
pure ( fileInvitation , ciFile , ft )
2022-04-10 13:30:58 +04:00
prepareMsg :: Maybe FileInvitation -> m ( MsgContainer , Maybe ( CIQuote 'CTDirect ) )
prepareMsg fileInvitation_ = case quotedItemId_ of
Nothing -> pure ( MCSimple ( ExtMsgContent mc fileInvitation_ ) , Nothing )
Just quotedItemId -> do
2022-05-05 11:52:32 +01:00
CChatItem _ ChatItem { meta = CIMeta { itemTs , itemSharedMsgId } , content = ciContent , formattedText , file } <-
2022-06-18 20:06:13 +01:00
withStore $ \ db -> getDirectChatItem db userId chatId quotedItemId
2022-04-11 09:34:59 +01:00
( origQmc , qd , sent ) <- quoteData ciContent
2022-04-10 13:30:58 +04:00
let msgRef = MsgRef { msgId = itemSharedMsgId , sentAt = itemTs , sent , memberId = Nothing }
2022-05-06 12:04:53 +04:00
qmc = quoteContent origQmc file
2022-04-10 13:30:58 +04:00
quotedItem = CIQuote { chatDir = qd , itemId = Just quotedItemId , sharedMsgId = itemSharedMsgId , sentAt = itemTs , content = qmc , formattedText }
pure ( MCQuote QuotedMsg { msgRef , content = qmc } ( ExtMsgContent mc fileInvitation_ ) , Just quotedItem )
2022-03-16 13:20:47 +00:00
where
2022-04-11 09:34:59 +01:00
quoteData :: CIContent d -> m ( MsgContent , CIQDirection 'CTDirect , Bool )
quoteData ( CISndMsgContent qmc ) = pure ( qmc , CIQDirectSnd , True )
quoteData ( CIRcvMsgContent qmc ) = pure ( qmc , CIQDirectRcv , False )
quoteData _ = throwChatError CEInvalidQuote
2022-03-13 19:34:03 +00:00
CTGroup -> do
2022-06-18 20:06:13 +01:00
Group gInfo @ GroupInfo { membership , localDisplayName = gName } ms <- withStore $ \ db -> getGroup db user chatId
2022-03-13 19:34:03 +00:00
unless ( memberActive membership ) $ throwChatError CEGroupMemberUserRemoved
2022-10-14 13:06:33 +01:00
( fileInvitation_ , ciFile_ , ft_ ) <- unzipMaybe3 <$> setupSndFileTransfer gInfo ( length ms )
2022-04-10 13:30:58 +04:00
( msgContainer , quotedItem_ ) <- prepareMsg fileInvitation_ membership
2022-10-14 13:06:33 +01:00
msg @ SndMessage { sharedMsgId } <- sendGroupMessage gInfo ms ( XMsgNew msgContainer )
mapM_ ( sendGroupFileInline ms sharedMsgId ) ft_
2022-04-10 13:30:58 +04:00
ci <- saveSndChatItem user ( CDGroupSnd gInfo ) msg ( CISndMsgContent mc ) ciFile_ quotedItem_
setActive $ ActiveG gName
pure . CRNewChatItem $ AChatItem SCTGroup SMDSnd ( GroupChat gInfo ) ci
where
2022-10-14 13:06:33 +01:00
setupSndFileTransfer :: GroupInfo -> Int -> m ( Maybe ( FileInvitation , CIFile 'MDSnd , FileTransferMeta ) )
setupSndFileTransfer gInfo n = forM file_ $ \ file -> do
( fileSize , chSize , fileInline ) <- checkSndFile file $ fromIntegral n
2022-08-18 11:35:31 +04:00
let fileName = takeFileName file
2022-10-14 13:06:33 +01:00
fileInvitation = FileInvitation { fileName , fileSize , fileConnReq = Nothing , fileInline }
fileStatus = if fileInline == Just IFMSent then CIFSSndTransfer else CIFSSndStored
withStore' $ \ db -> do
ft @ FileTransferMeta { fileId } <- createSndGroupFileTransfer db userId gInfo file fileInvitation chSize
let ciFile = CIFile { fileId , fileName , fileSize , filePath = Just file , fileStatus }
pure ( fileInvitation , ciFile , ft )
sendGroupFileInline :: [ GroupMember ] -> SharedMsgId -> FileTransferMeta -> m ()
sendGroupFileInline ms sharedMsgId ft @ FileTransferMeta { fileInline } =
when ( fileInline == Just IFMSent ) . forM_ ms $ \ case
m @ GroupMember { activeConn = Just conn @ Connection { connStatus } } ->
when ( connStatus == ConnReady || connStatus == ConnSndReady ) $ do
void . withStore' $ \ db -> createSndGroupInlineFT db m conn ft
sendMemberFileInline m conn ft sharedMsgId
_ -> pure ()
2022-04-10 13:30:58 +04:00
prepareMsg :: Maybe FileInvitation -> GroupMember -> m ( MsgContainer , Maybe ( CIQuote 'CTGroup ) )
prepareMsg fileInvitation_ membership = case quotedItemId_ of
Nothing -> pure ( MCSimple ( ExtMsgContent mc fileInvitation_ ) , Nothing )
Just quotedItemId -> do
2022-05-05 11:52:32 +01:00
CChatItem _ ChatItem { chatDir , meta = CIMeta { itemTs , itemSharedMsgId } , content = ciContent , formattedText , file } <-
2022-06-18 20:06:13 +01:00
withStore $ \ db -> getGroupChatItem db user chatId quotedItemId
2022-04-11 09:34:59 +01:00
( origQmc , qd , sent , GroupMember { memberId } ) <- quoteData ciContent chatDir membership
2022-04-10 13:30:58 +04:00
let msgRef = MsgRef { msgId = itemSharedMsgId , sentAt = itemTs , sent , memberId = Just memberId }
2022-05-06 12:04:53 +04:00
qmc = quoteContent origQmc file
2022-04-10 13:30:58 +04:00
quotedItem = CIQuote { chatDir = qd , itemId = Just quotedItemId , sharedMsgId = itemSharedMsgId , sentAt = itemTs , content = qmc , formattedText }
pure ( MCQuote QuotedMsg { msgRef , content = qmc } ( ExtMsgContent mc fileInvitation_ ) , Just quotedItem )
2022-03-16 13:20:47 +00:00
where
2022-04-11 09:34:59 +01:00
quoteData :: CIContent d -> CIDirection 'CTGroup d -> GroupMember -> m ( MsgContent , CIQDirection 'CTGroup , Bool , GroupMember )
quoteData ( CISndMsgContent qmc ) CIGroupSnd membership' = pure ( qmc , CIQGroupSnd , True , membership' )
quoteData ( CIRcvMsgContent qmc ) ( CIGroupRcv m ) _ = pure ( qmc , CIQGroupRcv $ Just m , False , m )
quoteData _ _ _ = throwChatError CEInvalidQuote
2022-02-06 16:18:01 +00:00
CTContactRequest -> pure $ chatCmdError " not supported "
2022-04-23 17:32:40 +01:00
CTContactConnection -> pure $ chatCmdError " not supported "
2022-04-10 13:30:58 +04:00
where
2022-05-06 12:04:53 +04:00
quoteContent :: forall d . MsgContent -> Maybe ( CIFile d ) -> MsgContent
quoteContent qmc ciFile_
| replaceContent = MCText qTextOrFile
| otherwise = case qmc of
2022-10-14 13:06:33 +01:00
MCImage _ image -> MCImage qTextOrFile image
MCFile _ -> MCFile qTextOrFile
_ -> qmc
2022-05-06 12:04:53 +04:00
where
-- if the message we're quoting with is one of the "large" MsgContents
-- we replace the quote's content with MCText
replaceContent = case mc of
MCText _ -> False
MCFile _ -> False
MCLink { } -> True
MCImage { } -> True
MCUnknown { } -> True
qText = msgContentText qmc
qFileName = maybe qText ( T . pack . ( fileName :: CIFile d -> String ) ) ciFile_
qTextOrFile = if T . null qText then qFileName else qText
2022-10-14 13:06:33 +01:00
unzipMaybe3 :: Maybe ( a , b , c ) -> ( Maybe a , Maybe b , Maybe c )
unzipMaybe3 ( Just ( a , b , c ) ) = ( Just a , Just b , Just c )
unzipMaybe3 _ = ( Nothing , Nothing , Nothing )
2022-04-28 08:34:21 +01:00
APIUpdateChatItem ( ChatRef cType chatId ) itemId mc -> withUser $ \ user @ User { userId } -> withChatLock $ case cType of
2022-03-23 11:37:51 +00:00
CTDirect -> do
2022-06-18 20:06:13 +01:00
( ct @ Contact { contactId , localDisplayName = c } , ci ) <- withStore $ \ db -> ( , ) <$> getContact db userId chatId <*> getDirectChatItem db userId chatId itemId
2022-03-23 11:37:51 +00:00
case ci of
CChatItem SMDSnd ChatItem { meta = CIMeta { itemSharedMsgId } , content = ciContent } -> do
case ( ciContent , itemSharedMsgId ) of
( CISndMsgContent _ , Just itemSharedMId ) -> do
2022-10-14 13:06:33 +01:00
( SndMessage { msgId } , _ ) <- sendDirectContactMessage ct ( XMsgUpdate itemSharedMId mc )
2022-06-18 20:06:13 +01:00
updCi <- withStore $ \ db -> updateDirectChatItem db userId contactId itemId ( CISndMsgContent mc ) $ Just msgId
2022-03-23 11:37:51 +00:00
setActive $ ActiveC c
pure . CRChatItemUpdated $ AChatItem SCTDirect SMDSnd ( DirectChat ct ) updCi
2022-03-28 20:35:57 +04:00
_ -> throwChatError CEInvalidChatItemUpdate
CChatItem SMDRcv _ -> throwChatError CEInvalidChatItemUpdate
2022-03-23 11:37:51 +00:00
CTGroup -> do
2022-06-18 20:06:13 +01:00
Group gInfo @ GroupInfo { groupId , localDisplayName = gName , membership } ms <- withStore $ \ db -> getGroup db user chatId
2022-03-23 11:37:51 +00:00
unless ( memberActive membership ) $ throwChatError CEGroupMemberUserRemoved
2022-06-18 20:06:13 +01:00
ci <- withStore $ \ db -> getGroupChatItem db user chatId itemId
2022-03-23 11:37:51 +00:00
case ci of
CChatItem SMDSnd ChatItem { meta = CIMeta { itemSharedMsgId } , content = ciContent } -> do
case ( ciContent , itemSharedMsgId ) of
( CISndMsgContent _ , Just itemSharedMId ) -> do
SndMessage { msgId } <- sendGroupMessage gInfo ms ( XMsgUpdate itemSharedMId mc )
2022-06-18 20:06:13 +01:00
updCi <- withStore $ \ db -> updateGroupChatItem db user groupId itemId ( CISndMsgContent mc ) msgId
2022-03-23 11:37:51 +00:00
setActive $ ActiveG gName
pure . CRChatItemUpdated $ AChatItem SCTGroup SMDSnd ( GroupChat gInfo ) updCi
2022-03-28 20:35:57 +04:00
_ -> throwChatError CEInvalidChatItemUpdate
CChatItem SMDRcv _ -> throwChatError CEInvalidChatItemUpdate
2022-03-23 11:37:51 +00:00
CTContactRequest -> pure $ chatCmdError " not supported "
2022-04-23 17:32:40 +01:00
CTContactConnection -> pure $ chatCmdError " not supported "
2022-04-28 08:34:21 +01:00
APIDeleteChatItem ( ChatRef cType chatId ) itemId mode -> withUser $ \ user @ User { userId } -> withChatLock $ case cType of
2022-03-28 20:35:57 +04:00
CTDirect -> do
2022-06-18 20:06:13 +01:00
( ct @ Contact { localDisplayName = c } , CChatItem msgDir deletedItem @ ChatItem { meta = CIMeta { itemSharedMsgId } , file } ) <- withStore $ \ db -> ( , ) <$> getContact db userId chatId <*> getDirectChatItem db userId chatId itemId
2022-03-28 20:35:57 +04:00
case ( mode , msgDir , itemSharedMsgId ) of
( CIDMInternal , _ , _ ) -> do
2022-05-11 16:18:28 +04:00
deleteCIFile user file
2022-06-18 20:06:13 +01:00
toCi <- withStore $ \ db -> deleteDirectChatItemLocal db userId ct itemId CIDMInternal
2022-03-28 20:35:57 +04:00
pure $ CRChatItemDeleted ( AChatItem SCTDirect msgDir ( DirectChat ct ) deletedItem ) toCi
( CIDMBroadcast , SMDSnd , Just itemSharedMId ) -> do
2022-05-17 11:22:09 +04:00
void $ sendDirectContactMessage ct ( XMsgDel itemSharedMId )
2022-05-11 16:18:28 +04:00
deleteCIFile user file
2022-06-18 20:06:13 +01:00
toCi <- withStore $ \ db -> deleteDirectChatItemLocal db userId ct itemId CIDMBroadcast
2022-03-28 20:35:57 +04:00
setActive $ ActiveC c
pure $ CRChatItemDeleted ( AChatItem SCTDirect msgDir ( DirectChat ct ) deletedItem ) toCi
( CIDMBroadcast , _ , _ ) -> throwChatError CEInvalidChatItemDelete
2022-05-17 11:22:09 +04:00
-- TODO for group integrity and pending messages, group items and messages are set to "deleted"; maybe a different workaround is needed
2022-03-28 20:35:57 +04:00
CTGroup -> do
2022-06-18 20:06:13 +01:00
Group gInfo @ GroupInfo { localDisplayName = gName , membership } ms <- withStore $ \ db -> getGroup db user chatId
2022-03-28 20:35:57 +04:00
unless ( memberActive membership ) $ throwChatError CEGroupMemberUserRemoved
2022-06-18 20:06:13 +01:00
CChatItem msgDir deletedItem @ ChatItem { meta = CIMeta { itemSharedMsgId } , file } <- withStore $ \ db -> getGroupChatItem db user chatId itemId
2022-03-28 20:35:57 +04:00
case ( mode , msgDir , itemSharedMsgId ) of
( CIDMInternal , _ , _ ) -> do
2022-05-11 16:18:28 +04:00
deleteCIFile user file
2022-10-01 14:31:21 +04:00
toCi <- withStore $ \ db -> deleteGroupChatItemLocal db user gInfo itemId CIDMInternal
2022-03-28 20:35:57 +04:00
pure $ CRChatItemDeleted ( AChatItem SCTGroup msgDir ( GroupChat gInfo ) deletedItem ) toCi
( CIDMBroadcast , SMDSnd , Just itemSharedMId ) -> do
2022-10-01 14:31:21 +04:00
void $ sendGroupMessage gInfo ms ( XMsgDel itemSharedMId )
2022-05-11 16:18:28 +04:00
deleteCIFile user file
2022-10-01 14:31:21 +04:00
toCi <- withStore $ \ db -> deleteGroupChatItemLocal db user gInfo itemId CIDMBroadcast
2022-03-28 20:35:57 +04:00
setActive $ ActiveG gName
pure $ CRChatItemDeleted ( AChatItem SCTGroup msgDir ( GroupChat gInfo ) deletedItem ) toCi
( CIDMBroadcast , _ , _ ) -> throwChatError CEInvalidChatItemDelete
2022-03-23 11:37:51 +00:00
CTContactRequest -> pure $ chatCmdError " not supported "
2022-04-23 17:32:40 +01:00
CTContactConnection -> pure $ chatCmdError " not supported "
2022-04-15 09:36:38 +04:00
where
2022-05-11 16:18:28 +04:00
deleteCIFile :: MsgDirectionI d => User -> Maybe ( CIFile d ) -> m ()
deleteCIFile user file =
2022-04-15 13:16:34 +01:00
forM_ file $ \ CIFile { fileId , filePath , fileStatus } -> do
2022-10-05 19:54:28 +04:00
let fileInfo = CIFileInfo { fileId , fileStatus = Just $ AFS msgDirection fileStatus , filePath }
2022-10-04 01:33:36 +04:00
deleteFile user fileInfo
2022-04-28 08:34:21 +01:00
APIChatRead ( ChatRef cType chatId ) fromToIds -> withChatLock $ case cType of
2022-06-18 20:06:13 +01:00
CTDirect -> withStore' ( \ db -> updateDirectChatItemsRead db chatId fromToIds ) $> CRCmdOk
CTGroup -> withStore' ( \ db -> updateGroupChatItemsRead db chatId fromToIds ) $> CRCmdOk
2022-02-08 17:27:43 +04:00
CTContactRequest -> pure $ chatCmdError " not supported "
2022-04-23 17:32:40 +01:00
CTContactConnection -> pure $ chatCmdError " not supported "
2022-05-05 10:37:53 +01:00
APIDeleteChat ( ChatRef cType chatId ) -> withUser $ \ user @ User { userId } -> case cType of
2022-01-31 21:53:53 +04:00
CTDirect -> do
2022-06-18 20:06:13 +01:00
ct @ Contact { localDisplayName } <- withStore $ \ db -> getContact db userId chatId
withStore' ( \ db -> getContactGroupNames db userId ct ) >>= \ case
2022-01-31 21:53:53 +04:00
[] -> do
2022-10-04 01:33:36 +04:00
filesInfo <- withStore' $ \ db -> getContactFileInfo db user ct
2022-06-18 20:06:13 +01:00
conns <- withStore $ \ db -> getContactConnections db userId ct
2022-02-06 08:21:40 +00:00
withChatLock . procCmd $ do
2022-10-04 01:33:36 +04:00
forM_ filesInfo $ \ fileInfo -> deleteFile user fileInfo
2022-09-30 16:18:43 +04:00
forM_ conns $ \ conn -> deleteAgentConnectionAsync user conn ` catchError ` \ _ -> pure ()
2022-09-14 19:45:21 +04:00
-- functions below are called in separate transactions to prevent crashes on android
2022-06-18 20:06:13 +01:00
-- (possibly, race condition on integrity check?)
withStore' $ \ db -> deleteContactConnectionsAndFiles db userId ct
withStore' $ \ db -> deleteContact db userId ct
2022-01-31 21:53:53 +04:00
unsetActive $ ActiveC localDisplayName
pure $ CRContactDeleted ct
gs -> throwChatError $ CEContactGroups ct gs
2022-04-25 10:39:28 +01:00
CTContactConnection -> withChatLock . procCmd $ do
2022-09-30 16:18:43 +04:00
conn @ PendingContactConnection { pccConnId , pccAgentConnId } <- withStore $ \ db -> getPendingContactConnection db userId chatId
deleteAgentConnectionAsync' user pccConnId pccAgentConnId
2022-06-18 20:06:13 +01:00
withStore' $ \ db -> deletePendingContactConnection db userId chatId
2022-04-25 10:39:28 +01:00
pure $ CRContactConnectionDeleted conn
2022-07-12 19:20:56 +04:00
CTGroup -> do
2022-08-04 11:12:50 +01:00
Group gInfo @ GroupInfo { membership } members <- withStore $ \ db -> getGroup db user chatId
2022-07-30 16:49:34 +04:00
let canDelete = memberRole ( membership :: GroupMember ) == GROwner || not ( memberCurrent membership )
2022-07-12 19:20:56 +04:00
unless canDelete $ throwChatError CEGroupUserRole
2022-10-04 01:33:36 +04:00
filesInfo <- withStore' $ \ db -> getGroupFileInfo db user gInfo
2022-07-12 19:20:56 +04:00
withChatLock . procCmd $ do
2022-10-04 01:33:36 +04:00
forM_ filesInfo $ \ fileInfo -> deleteFile user fileInfo
2022-07-12 19:20:56 +04:00
when ( memberActive membership ) . void $ sendGroupMessage gInfo members XGrpDel
2022-10-13 17:12:22 +04:00
deleteGroupLink' user gInfo ` catchError ` \ _ -> pure ()
2022-09-30 16:18:43 +04:00
forM_ members $ deleteMemberConnection user
2022-09-14 19:45:21 +04:00
-- functions below are called in separate transactions to prevent crashes on android
2022-08-02 14:10:03 +04:00
-- (possibly, race condition on integrity check?)
2022-08-04 11:12:50 +01:00
withStore' $ \ db -> deleteGroupConnectionsAndFiles db user gInfo members
withStore' $ \ db -> deleteGroupItemsAndMembers db user gInfo
withStore' $ \ db -> deleteGroup db user gInfo
2022-07-12 19:20:56 +04:00
pure $ CRGroupDeletedUser gInfo
2022-02-06 16:18:01 +00:00
CTContactRequest -> pure $ chatCmdError " not supported "
2022-05-17 11:22:09 +04:00
APIClearChat ( ChatRef cType chatId ) -> withUser $ \ user @ User { userId } -> case cType of
CTDirect -> do
2022-06-18 20:06:13 +01:00
ct <- withStore $ \ db -> getContact db userId chatId
2022-10-04 01:33:36 +04:00
filesInfo <- withStore' $ \ db -> getContactFileInfo db user ct
maxItemTs_ <- withStore' $ \ db -> getContactMaxItemTs db user ct
forM_ filesInfo $ \ fileInfo -> deleteFile user fileInfo
withStore' $ \ db -> deleteContactCIs db user ct
ct' <- case maxItemTs_ of
Just ts -> do
withStore' $ \ db -> updateContactTs db user ct ts
pure ( ct :: Contact ) { updatedAt = ts }
_ -> pure ct
2022-05-20 12:00:58 +04:00
pure $ CRChatCleared ( AChatInfo SCTDirect ( DirectChat ct' ) )
2022-05-17 11:22:09 +04:00
CTGroup -> do
2022-06-18 20:06:13 +01:00
gInfo <- withStore $ \ db -> getGroupInfo db user chatId
2022-10-04 01:33:36 +04:00
filesInfo <- withStore' $ \ db -> getGroupFileInfo db user gInfo
maxItemTs_ <- withStore' $ \ db -> getGroupMaxItemTs db user gInfo
forM_ filesInfo $ \ fileInfo -> deleteFile user fileInfo
withStore' $ \ db -> deleteGroupCIs db user gInfo
gInfo' <- case maxItemTs_ of
Just ts -> do
withStore' $ \ db -> updateGroupTs db user gInfo ts
pure ( gInfo :: GroupInfo ) { updatedAt = ts }
2022-08-04 11:12:50 +01:00
_ -> pure gInfo
2022-05-20 12:00:58 +04:00
pure $ CRChatCleared ( AChatInfo SCTGroup ( GroupChat gInfo' ) )
2022-05-17 11:22:09 +04:00
CTContactConnection -> pure $ chatCmdError " not supported "
CTContactRequest -> pure $ chatCmdError " not supported "
2022-02-14 14:59:11 +04:00
APIAcceptContact connReqId -> withUser $ \ user @ User { userId } -> withChatLock $ do
2022-06-18 20:06:13 +01:00
cReq <- withStore $ \ db -> getContactRequest db userId connReqId
2022-10-13 17:12:22 +04:00
-- [incognito] generate profile to send, create connection with incognito profile
incognito <- readTVarIO =<< asks incognitoMode
2022-10-14 14:57:01 +04:00
incognitoProfile <- if incognito then Just . NewIncognito <$> liftIO generateRandomProfile else pure Nothing
2022-10-13 17:12:22 +04:00
ct <- acceptContactRequest user cReq incognitoProfile
pure $ CRAcceptingContactRequest ct
2022-02-06 16:18:01 +00:00
APIRejectContact connReqId -> withUser $ \ User { userId } -> withChatLock $ do
2022-02-01 05:31:34 +00:00
cReq @ UserContactRequest { agentContactConnId = AgentConnId connId , agentInvitationId = AgentInvId invId } <-
2022-06-18 20:06:13 +01:00
withStore $ \ db ->
getContactRequest db userId connReqId
` E . finally ` liftIO ( deleteContactRequest db userId connReqId )
2022-02-01 05:31:34 +00:00
withAgent $ \ a -> rejectContact a connId invId
pure $ CRContactRequestRejected cReq
2022-05-18 07:01:32 +01:00
APISendCallInvitation contactId callType -> withUser $ \ user @ User { userId } -> do
2022-05-03 10:22:35 +01:00
-- party initiating call
2022-06-18 20:06:13 +01:00
ct <- withStore $ \ db -> getContact db userId contactId
2022-05-04 13:31:00 +01:00
calls <- asks currentCalls
withChatLock $ do
callId <- CallId <$> ( asks idsDrg >>= liftIO . ( ` randomBytes ` 16 ) )
2022-05-18 07:01:32 +01:00
dhKeyPair <- if encryptedCall callType then Just <$> liftIO C . generateKeyPair' else pure Nothing
2022-05-04 13:31:00 +01:00
let invitation = CallInvitation { callType , callDhPubKey = fst <$> dhKeyPair }
callState = CallInvitationSent { localCallType = callType , localDhPrivKey = snd <$> dhKeyPair }
2022-10-14 13:06:33 +01:00
( msg , _ ) <- sendDirectContactMessage ct ( XCallInv callId invitation )
2022-05-04 13:31:00 +01:00
ci <- saveSndChatItem user ( CDDirectSnd ct ) msg ( CISndCall CISCallPending 0 ) Nothing Nothing
2022-07-04 11:15:25 +01:00
let call' = Call { contactId , callId , chatItemId = chatItemId' ci , callState , callTs = chatItemTs' ci }
2022-05-04 13:31:00 +01:00
call_ <- atomically $ TM . lookupInsert contactId call' calls
2022-05-18 18:46:45 +01:00
forM_ call_ $ \ call -> updateCallItemStatus userId ct call WCSDisconnected Nothing
2022-05-04 13:31:00 +01:00
toView . CRNewChatItem $ AChatItem SCTDirect SMDSnd ( DirectChat ct ) ci
pure CRCmdOk
2022-09-05 15:23:38 +01:00
SendCallInvitation cName callType -> withUser $ \ user -> do
contactId <- withStore $ \ db -> getContactIdByName db user cName
2022-05-17 08:37:00 +01:00
processChatCommand $ APISendCallInvitation contactId callType
2022-05-03 10:22:35 +01:00
APIRejectCall contactId ->
-- party accepting call
withCurrentCall contactId $ \ userId ct Call { chatItemId , callState } -> case callState of
2022-05-28 12:34:40 +01:00
CallInvitationReceived { } -> do
2022-05-04 13:31:00 +01:00
let aciContent = ACIContent SMDRcv $ CIRcvCall CISCallRejected 0
2022-06-18 20:06:13 +01:00
withStore' $ \ db -> updateDirectChatItemsRead db contactId $ Just ( chatItemId , chatItemId )
2022-05-28 12:34:40 +01:00
updateDirectChatItemView userId ct chatItemId aciContent Nothing $> Nothing
2022-05-03 10:22:35 +01:00
_ -> throwChatError . CECallState $ callStateTag callState
APISendCallOffer contactId WebRTCCallOffer { callType , rtcSession } ->
-- party accepting call
withCurrentCall contactId $ \ userId ct call @ Call { callId , chatItemId , callState } -> case callState of
CallInvitationReceived { peerCallType , localDhPubKey , sharedKey } -> do
2022-05-18 07:01:32 +01:00
let callDhPubKey = if encryptedCall callType then localDhPubKey else Nothing
offer = CallOffer { callType , rtcSession , callDhPubKey }
2022-05-03 10:22:35 +01:00
callState' = CallOfferSent { localCallType = callType , peerCallType , localCallSession = rtcSession , sharedKey }
2022-05-04 13:31:00 +01:00
aciContent = ACIContent SMDRcv $ CIRcvCall CISCallAccepted 0
2022-10-14 13:06:33 +01:00
( SndMessage { msgId } , _ ) <- sendDirectContactMessage ct ( XCallOffer callId offer )
2022-06-18 20:06:13 +01:00
withStore' $ \ db -> updateDirectChatItemsRead db contactId $ Just ( chatItemId , chatItemId )
2022-05-04 13:31:00 +01:00
updateDirectChatItemView userId ct chatItemId aciContent $ Just msgId
2022-05-03 10:22:35 +01:00
pure $ Just call { callState = callState' }
_ -> throwChatError . CECallState $ callStateTag callState
APISendCallAnswer contactId rtcSession ->
-- party initiating call
withCurrentCall contactId $ \ userId ct call @ Call { callId , chatItemId , callState } -> case callState of
CallOfferReceived { localCallType , peerCallType , peerCallSession , sharedKey } -> do
let callState' = CallNegotiated { localCallType , peerCallType , localCallSession = rtcSession , peerCallSession , sharedKey }
2022-05-04 13:31:00 +01:00
aciContent = ACIContent SMDSnd $ CISndCall CISCallNegotiated 0
2022-10-14 13:06:33 +01:00
( SndMessage { msgId } , _ ) <- sendDirectContactMessage ct ( XCallAnswer callId CallAnswer { rtcSession } )
2022-05-04 13:31:00 +01:00
updateDirectChatItemView userId ct chatItemId aciContent $ Just msgId
2022-05-03 10:22:35 +01:00
pure $ Just call { callState = callState' }
_ -> throwChatError . CECallState $ callStateTag callState
APISendCallExtraInfo contactId rtcExtraInfo ->
-- any call party
withCurrentCall contactId $ \ _ ct call @ Call { callId , callState } -> case callState of
2022-05-07 06:40:46 +01:00
CallOfferSent { localCallType , peerCallType , localCallSession , sharedKey } -> do
-- TODO update the list of ice servers in localCallSession
2022-10-14 13:06:33 +01:00
void . sendDirectContactMessage ct $ XCallExtra callId CallExtraInfo { rtcExtraInfo }
2022-05-07 06:40:46 +01:00
let callState' = CallOfferSent { localCallType , peerCallType , localCallSession , sharedKey }
pure $ Just call { callState = callState' }
2022-05-03 10:22:35 +01:00
CallNegotiated { localCallType , peerCallType , localCallSession , peerCallSession , sharedKey } -> do
2022-05-07 06:40:46 +01:00
-- TODO update the list of ice servers in localCallSession
2022-10-14 13:06:33 +01:00
void . sendDirectContactMessage ct $ XCallExtra callId CallExtraInfo { rtcExtraInfo }
2022-05-03 10:22:35 +01:00
let callState' = CallNegotiated { localCallType , peerCallType , localCallSession , peerCallSession , sharedKey }
pure $ Just call { callState = callState' }
_ -> throwChatError . CECallState $ callStateTag callState
APIEndCall contactId ->
-- any call party
2022-05-04 13:31:00 +01:00
withCurrentCall contactId $ \ userId ct call @ Call { callId } -> do
2022-10-14 13:06:33 +01:00
( SndMessage { msgId } , _ ) <- sendDirectContactMessage ct ( XCallEnd callId )
2022-05-04 13:31:00 +01:00
updateCallItemStatus userId ct call WCSDisconnected $ Just msgId
2022-05-03 10:22:35 +01:00
pure Nothing
2022-07-05 15:15:15 +04:00
APIGetCallInvitations -> withUser $ \ User { userId } -> do
calls <- asks currentCalls >>= readTVarIO
let invs = mapMaybe callInvitation $ M . elems calls
2022-07-04 11:15:25 +01:00
CRCallInvitations <$> mapM ( rcvCallInvitation userId ) invs
where
callInvitation Call { contactId , callState , callTs } = case callState of
CallInvitationReceived { peerCallType , sharedKey } -> Just ( contactId , callTs , peerCallType , sharedKey )
_ -> Nothing
rcvCallInvitation userId ( contactId , callTs , peerCallType , sharedKey ) = do
contact <- withStore ( \ db -> getContact db userId contactId )
pure RcvCallInvitation { contact , callType = peerCallType , sharedKey , callTs }
2022-05-04 13:31:00 +01:00
APICallStatus contactId receivedStatus ->
withCurrentCall contactId $ \ userId ct call ->
updateCallItemStatus userId ct call receivedStatus Nothing $> Just call
2022-03-23 20:52:00 +00:00
APIUpdateProfile profile -> withUser ( ` updateProfile ` profile )
2022-08-24 19:03:43 +04:00
APISetContactAlias contactId localAlias -> withUser $ \ User { userId } -> do
ct' <- withStore $ \ db -> do
ct <- getContact db userId contactId
liftIO $ updateContactAlias db userId ct localAlias
pure $ CRContactAliasUpdated ct'
2022-09-27 20:45:46 +01:00
APISetConnectionAlias connId localAlias -> withUser $ \ User { userId } -> do
conn' <- withStore $ \ db -> do
conn <- getPendingContactConnection db userId connId
liftIO $ updateContactConnectionAlias db userId conn localAlias
pure $ CRConnectionAliasUpdated conn'
2022-04-04 19:51:49 +01:00
APIParseMarkdown text -> pure . CRApiParsedMarkdown $ parseMaybeMarkdownList text
2022-06-25 17:02:16 +01:00
APIGetNtfToken -> withUser $ \ _ -> crNtfToken <$> withAgent getNtfToken
APIRegisterToken token mode -> CRNtfTokenStatus <$> withUser ( \ _ -> withAgent $ \ a -> registerNtfToken a token mode )
2022-06-27 23:03:27 +01:00
APIVerifyToken token nonce code -> withUser $ \ _ -> withAgent ( \ a -> verifyNtfToken a token nonce code ) $> CRCmdOk
2022-04-21 20:04:22 +01:00
APIDeleteToken token -> withUser $ \ _ -> withAgent ( ` deleteNtfToken ` token ) $> CRCmdOk
2022-06-19 14:44:13 +01:00
APIGetNtfMessage nonce encNtfInfo -> withUser $ \ user -> do
( NotificationInfo { ntfConnId , ntfMsgMeta } , msgs ) <- withAgent $ \ a -> getNotificationMessage a nonce encNtfInfo
let ntfMessages = map ( \ SMP . SMPMsgMeta { msgTs , msgFlags } -> NtfMsgInfo { msgTs = systemToUTCTime msgTs , msgFlags } ) msgs
msgTs' = systemToUTCTime . ( SMP . msgTs :: SMP . NMsgMeta -> SystemTime ) <$> ntfMsgMeta
2022-07-17 15:51:17 +01:00
connEntity <- withStore ( \ db -> Just <$> getConnectionEntity db user ( AgentConnId ntfConnId ) ) ` catchError ` \ _ -> pure Nothing
2022-06-19 14:44:13 +01:00
pure CRNtfMessages { connEntity , msgTs = msgTs' , ntfMessages }
2022-06-18 20:06:13 +01:00
GetUserSMPServers -> CRUserSMPServers <$> withUser ( \ user -> withStore' ( ` getSMPServers ` user ) )
2022-03-10 15:45:40 +04:00
SetUserSMPServers smpServers -> withUser $ \ user -> withChatLock $ do
2022-06-18 20:06:13 +01:00
withStore $ \ db -> overwriteSMPServers db user smpServers
2022-05-11 16:52:08 +01:00
ChatConfig { defaultServers = InitialAgentServers { smp = defaultSMPServers } } <- asks config
2022-03-10 15:45:40 +04:00
withAgent $ \ a -> setSMPServers a ( fromMaybe defaultSMPServers ( nonEmpty smpServers ) )
pure CRCmdOk
2022-10-07 13:53:05 +04:00
APISetChatItemTTL newTTL_ -> withUser' $ \ user ->
checkStoreNotChanged $
withChatLock $ do
case newTTL_ of
Nothing -> do
withStore' $ \ db -> setChatItemTTL db user newTTL_
setExpireCIs False
Just newTTL -> do
oldTTL <- withStore' ( ` getChatItemTTL ` user )
when ( maybe True ( newTTL < ) oldTTL ) $ do
setExpireCIs False
expireChatItems user newTTL True
withStore' $ \ db -> setChatItemTTL db user newTTL_
whenM chatStarted $ setExpireCIs True
pure CRCmdOk
2022-09-28 20:47:06 +04:00
APIGetChatItemTTL -> CRChatItemTTL <$> withUser ( \ user -> withStore' ( ` getChatItemTTL ` user ) )
2022-07-28 11:12:23 +01:00
APISetNetworkConfig cfg -> withUser' $ \ _ -> withAgent ( ` setNetworkConfig ` cfg ) $> CRCmdOk
APIGetNetworkConfig -> CRNetworkConfig <$> withUser' ( \ _ -> withAgent getNetworkConfig )
2022-08-19 15:17:05 +01:00
APISetChatSettings ( ChatRef cType chatId ) chatSettings -> withUser $ \ user @ User { userId } -> case cType of
CTDirect -> do
ct <- withStore $ \ db -> do
ct <- getContact db userId chatId
liftIO $ updateContactSettings db user chatId chatSettings
pure ct
withAgent $ \ a -> toggleConnectionNtfs a ( contactConnId ct ) ( enableNtfs chatSettings )
pure CRCmdOk
CTGroup -> do
ms <- withStore $ \ db -> do
Group _ ms <- getGroup db user chatId
liftIO $ updateGroupSettings db user chatId chatSettings
pure ms
2022-08-20 14:47:24 +01:00
forM_ ( filter memberActive ms ) $ \ m -> forM_ ( memberConnId m ) $ \ connId ->
withAgent ( \ a -> toggleConnectionNtfs a connId $ enableNtfs chatSettings ) ` catchError ` ( toView . CRChatError )
2022-08-19 15:17:05 +01:00
pure CRCmdOk
_ -> pure $ chatCmdError " not supported "
2022-07-20 14:57:16 +01:00
APIContactInfo contactId -> withUser $ \ User { userId } -> do
2022-08-18 11:35:31 +04:00
-- [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 )
2022-08-24 19:03:43 +04:00
pure $ CRContactInfo ct connectionStats ( fmap fromLocalProfile incognitoProfile )
2022-08-27 19:56:03 +04:00
APIGroupMemberInfo gId gMemberId -> withUser $ \ user -> do
( g , m ) <- withStore $ \ db -> ( , ) <$> getGroupInfo db user gId <*> getGroupMember db user gId gMemberId
2022-08-18 11:35:31 +04:00
connectionStats <- mapM ( withAgent . flip getConnectionServers ) ( memberConnId m )
2022-08-27 19:56:03 +04:00
pure $ CRGroupMemberInfo g m connectionStats
2022-09-05 15:23:38 +01:00
ShowMessages ( ChatName cType name ) ntfOn -> withUser $ \ user -> do
chatId <- case cType of
CTDirect -> withStore $ \ db -> getContactIdByName db user name
CTGroup -> withStore $ \ db -> getGroupIdByName db user name
_ -> throwChatError $ CECommandError " not supported "
processChatCommand $ APISetChatSettings ( ChatRef cType chatId ) $ ChatSettings ntfOn
ContactInfo cName -> withUser $ \ user -> do
contactId <- withStore $ \ db -> getContactIdByName db user cName
2022-07-20 14:57:16 +01:00
processChatCommand $ APIContactInfo contactId
GroupMemberInfo gName mName -> withUser $ \ user -> do
( gId , mId ) <- withStore $ \ db -> getGroupIdByName db user gName >>= \ gId -> ( gId , ) <$> getGroupMemberIdByName db user gId mName
processChatCommand $ APIGroupMemberInfo gId mId
2022-01-24 16:07:17 +00:00
ChatHelp section -> pure $ CRChatHelp section
2022-02-06 16:18:01 +00:00
Welcome -> withUser $ pure . CRWelcome
AddContact -> withUser $ \ User { userId } -> withChatLock . procCmd $ do
2022-08-18 11:35:31 +04:00
-- [incognito] generate profile for connection
incognito <- readTVarIO =<< asks incognitoMode
incognitoProfile <- if incognito then Just <$> liftIO generateRandomProfile else pure Nothing
2022-08-19 15:17:05 +01:00
( connId , cReq ) <- withAgent $ \ a -> createConnection a True SCMInvitation
2022-09-27 20:45:46 +01:00
conn <- withStore' $ \ db -> createDirectConnection db userId connId cReq ConnNew incognitoProfile
2022-04-23 17:32:40 +01:00
toView $ CRNewContactConnection conn
2022-01-24 16:07:17 +00:00
pure $ CRInvitation cReq
2022-02-06 16:18:01 +00:00
Connect ( Just ( ACR SCMInvitation cReq ) ) -> withUser $ \ User { userId , profile } -> withChatLock . procCmd $ do
2022-08-18 11:35:31 +04:00
-- [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
2022-08-19 15:17:05 +01:00
connId <- withAgent $ \ a -> joinConnection a True cReq . directMessage $ XInfo profileToSend
2022-09-27 20:45:46 +01:00
conn <- withStore' $ \ db -> createDirectConnection db userId connId cReq ConnJoined incognitoProfile
2022-04-23 17:32:40 +01:00
toView $ CRNewContactConnection conn
2022-01-24 16:07:17 +00:00
pure CRSentConfirmation
2022-02-13 13:19:24 +04:00
Connect ( Just ( ACR SCMContact cReq ) ) -> withUser $ \ User { userId , profile } ->
2022-08-18 11:35:31 +04:00
-- [incognito] generate profile to send
connectViaContact userId cReq $ fromLocalProfile profile
2022-01-26 21:20:08 +00:00
Connect Nothing -> throwChatError CEInvalidConnReq
2022-03-29 08:53:30 +01:00
ConnectSimplex -> withUser $ \ User { userId , profile } ->
2022-08-18 11:35:31 +04:00
-- [incognito] generate profile to send
connectViaContact userId adminContactReq $ fromLocalProfile profile
2022-09-05 15:23:38 +01:00
DeleteContact cName -> withUser $ \ user -> do
contactId <- withStore $ \ db -> getContactIdByName db user cName
2022-04-28 08:34:21 +01:00
processChatCommand $ APIDeleteChat ( ChatRef CTDirect contactId )
2022-09-05 15:23:38 +01:00
ClearContact cName -> withUser $ \ user -> do
contactId <- withStore $ \ db -> getContactIdByName db user cName
2022-05-17 11:22:09 +04:00
processChatCommand $ APIClearChat ( ChatRef CTDirect contactId )
2022-06-18 20:06:13 +01:00
ListContacts -> withUser $ \ user -> CRContactsList <$> withStore' ( ` getUserContacts ` user )
2022-02-06 16:18:01 +00:00
CreateMyAddress -> withUser $ \ User { userId } -> withChatLock . procCmd $ do
2022-08-19 15:17:05 +01:00
( connId , cReq ) <- withAgent $ \ a -> createConnection a True SCMContact
2022-06-18 20:06:13 +01:00
withStore $ \ db -> createUserContactLink db userId connId cReq
2022-01-24 16:07:17 +00:00
pure $ CRUserContactLinkCreated cReq
2022-07-17 15:51:17 +01:00
DeleteMyAddress -> withUser $ \ user -> withChatLock $ do
2022-10-13 17:12:22 +04:00
conns <- withStore ( ` getUserAddressConnections ` user )
2022-01-24 16:07:17 +00:00
procCmd $ do
2022-09-30 16:18:43 +04:00
forM_ conns $ \ conn -> deleteAgentConnectionAsync user conn ` catchError ` \ _ -> pure ()
2022-10-13 17:12:22 +04:00
withStore' ( ` deleteUserAddress ` user )
2022-01-24 16:07:17 +00:00
pure CRUserContactLinkDeleted
2022-02-14 14:59:11 +04:00
ShowMyAddress -> withUser $ \ User { userId } ->
2022-10-13 17:12:22 +04:00
uncurry3 CRUserContactLink <$> withStore ( ` getUserAddress ` userId )
2022-06-27 19:41:25 +01:00
AddressAutoAccept onOff msgContent -> withUser $ \ User { userId } -> do
2022-10-13 17:12:22 +04:00
uncurry3 CRUserContactLinkUpdated <$> withStore ( \ db -> updateUserAddressAutoAccept db userId onOff msgContent )
2022-02-06 16:18:01 +00:00
AcceptContact cName -> withUser $ \ User { userId } -> do
2022-06-18 20:06:13 +01:00
connReqId <- withStore $ \ db -> getContactRequestIdByName db userId cName
2022-02-06 16:18:01 +00:00
processChatCommand $ APIAcceptContact connReqId
RejectContact cName -> withUser $ \ User { userId } -> do
2022-06-18 20:06:13 +01:00
connReqId <- withStore $ \ db -> getContactRequestIdByName db userId cName
2022-02-06 16:18:01 +00:00
processChatCommand $ APIRejectContact connReqId
2022-04-28 08:34:21 +01:00
SendMessage chatName msg -> withUser $ \ user -> do
chatRef <- getChatRef user chatName
2022-01-26 16:18:27 +04:00
let mc = MCText $ safeDecodeUtf8 msg
2022-05-05 14:04:03 +01:00
processChatCommand . APISendMessage chatRef $ ComposedMessage Nothing Nothing mc
2022-03-29 08:53:30 +01:00
SendMessageBroadcast msg -> withUser $ \ user -> do
2022-06-18 20:06:13 +01:00
contacts <- withStore' ( ` getUserContacts ` user )
2022-03-29 08:53:30 +01:00
withChatLock . procCmd $ do
let mc = MCText $ safeDecodeUtf8 msg
cts = filter isReady contacts
forM_ cts $ \ ct ->
2022-04-10 13:30:58 +04:00
void
( do
2022-10-14 13:06:33 +01:00
( sndMsg , _ ) <- sendDirectContactMessage ct ( XMsgNew $ MCSimple ( ExtMsgContent mc Nothing ) )
2022-04-10 13:30:58 +04:00
saveSndChatItem user ( CDDirectSnd ct ) sndMsg ( CISndMsgContent mc ) Nothing Nothing
)
2022-03-29 08:53:30 +01:00
` catchError ` ( toView . CRChatError )
CRBroadcastSent mc ( length cts ) <$> liftIO getZonedTime
2022-09-05 15:23:38 +01:00
SendMessageQuote cName ( AMsgDirection msgDir ) quotedMsg msg -> withUser $ \ user @ User { userId } -> do
contactId <- withStore $ \ db -> getContactIdByName db user cName
2022-06-18 20:06:13 +01:00
quotedItemId <- withStore $ \ db -> getDirectChatItemIdByText db userId contactId msgDir ( safeDecodeUtf8 quotedMsg )
2022-03-13 19:34:03 +00:00
let mc = MCText $ safeDecodeUtf8 msg
2022-05-05 14:04:03 +01:00
processChatCommand . APISendMessage ( ChatRef CTDirect contactId ) $ ComposedMessage Nothing ( Just quotedItemId ) mc
2022-04-28 08:34:21 +01:00
DeleteMessage chatName deletedMsg -> withUser $ \ user -> do
chatRef <- getChatRef user chatName
deletedItemId <- getSentChatItemIdByText user chatRef deletedMsg
processChatCommand $ APIDeleteChatItem chatRef deletedItemId CIDMBroadcast
EditMessage chatName editedMsg msg -> withUser $ \ user -> do
chatRef <- getChatRef user chatName
editedItemId <- getSentChatItemIdByText user chatRef editedMsg
2022-04-03 09:44:23 +01:00
let mc = MCText $ safeDecodeUtf8 msg
2022-04-28 08:34:21 +01:00
processChatCommand $ APIUpdateChatItem chatRef editedItemId mc
2022-02-06 16:18:01 +00:00
NewGroup gProfile -> withUser $ \ user -> do
2021-07-12 19:00:03 +01:00
gVar <- asks idsDrg
2022-08-27 19:56:03 +04:00
groupInfo <- withStore ( \ db -> createNewGroup db gVar user gProfile )
pure $ CRGroupCreated groupInfo
2022-07-12 19:20:56 +04:00
APIAddMember groupId contactId memRole -> withUser $ \ user @ User { userId } -> withChatLock $ do
2022-01-26 16:18:27 +04:00
-- TODO for large groups: no need to load all members to determine if contact is a member
2022-07-12 19:20:56 +04:00
( group , contact ) <- withStore $ \ db -> ( , ) <$> getGroup db user groupId <*> getContact db userId contactId
2022-10-03 09:00:47 +01:00
let Group gInfo @ GroupInfo { membership } members = group
GroupMember { memberRole = userRole } = membership
2022-07-12 19:20:56 +04:00
Contact { localDisplayName = cName } = contact
2022-08-27 19:56:03 +04:00
-- [incognito] forbid to invite contact to whom user is connected incognito
when ( contactConnIncognito contact ) $ throwChatError CEContactIncognitoCantInvite
-- [incognito] forbid to invite contacts if user joined the group using an incognito profile
when ( memberIncognito membership ) $ throwChatError CEGroupIncognitoCantInvite
2022-01-26 21:20:08 +00:00
when ( userRole < GRAdmin || userRole < memRole ) $ throwChatError CEGroupUserRole
when ( memberStatus membership == GSMemInvited ) $ throwChatError ( CEGroupNotJoined gInfo )
unless ( memberActive membership ) $ throwChatError CEGroupMemberNotActive
2022-10-03 09:00:47 +01:00
let sendInvitation = sendGrpInvitation user contact gInfo
2022-01-06 23:39:58 +04:00
case contactMember contact members of
Nothing -> do
gVar <- asks idsDrg
2022-08-19 15:17:05 +01:00
( agentConnId , cReq ) <- withAgent $ \ a -> createConnection a True SCMInvitation
2022-08-18 11:35:31 +04:00
member <- withStore $ \ db -> createNewContactMember db gVar user groupId contact memRole agentConnId cReq
2022-08-09 13:43:19 +04:00
sendInvitation member cReq
2022-10-03 09:00:47 +01:00
pure $ CRSentGroupInvitation gInfo contact member
2022-08-09 13:43:19 +04:00
Just member @ GroupMember { groupMemberId , memberStatus }
2022-01-06 23:39:58 +04:00
| memberStatus == GSMemInvited ->
2022-10-14 13:06:33 +01:00
withStore' ( \ db -> getMemberInvitation db user groupMemberId ) >>= \ case
Just cReq -> sendInvitation member cReq $> CRSentGroupInvitation gInfo contact member
Nothing -> throwChatError $ CEGroupCantResendInvitation gInfo cName
2022-01-26 21:20:08 +00:00
| otherwise -> throwChatError $ CEGroupDuplicateMember cName
2022-07-12 19:20:56 +04:00
APIJoinGroup groupId -> withUser $ \ user @ User { userId } -> do
2022-07-18 21:58:32 +04:00
ReceivedGroupInvitation { fromMember , connRequest , groupInfo = g @ GroupInfo { membership } } <- withStore $ \ db -> getGroupInvitation db user groupId
2022-02-06 08:21:40 +00:00
withChatLock . procCmd $ do
2022-08-27 19:56:03 +04:00
agentConnId <- withAgent $ \ a -> joinConnection a True connRequest . directMessage $ XGrpAcpt ( memberId ( membership :: GroupMember ) )
2022-06-18 20:06:13 +01:00
withStore' $ \ db -> do
createMemberConnection db userId fromMember agentConnId
updateGroupMemberStatus db userId fromMember GSMemAccepted
2022-08-27 19:56:03 +04:00
updateGroupMemberStatus db userId membership GSMemAccepted
2022-07-15 17:49:29 +04:00
updateCIGroupInvitationStatus user
2022-08-27 19:56:03 +04:00
pure $ CRUserAcceptedGroupSent g { membership = membership { memberStatus = GSMemAccepted } }
2022-07-15 17:49:29 +04:00
where
updateCIGroupInvitationStatus user @ User { userId } = do
AChatItem _ _ cInfo ChatItem { content , meta = CIMeta { itemId } } <- withStore $ \ db -> getChatItemByGroupId db user groupId
case ( cInfo , content ) of
( DirectChat ct , CIRcvGroupInvitation ciGroupInv memRole ) -> do
let aciContent = ACIContent SMDRcv $ CIRcvGroupInvitation ciGroupInv { status = CIGISAccepted } memRole
updateDirectChatItemView userId ct itemId aciContent Nothing
_ -> pure () -- prohibited
2022-10-03 09:00:47 +01:00
APIMemberRole groupId memberId memRole -> withUser $ \ user -> do
Group gInfo @ GroupInfo { membership } members <- withStore $ \ db -> getGroup db user groupId
if memberId == groupMemberId' membership
then changeMemberRole user gInfo members membership $ SGEUserRole memRole
else case find ( ( == memberId ) . groupMemberId' ) members of
Just m -> changeMemberRole user gInfo members m $ SGEMemberRole memberId ( fromLocalProfile $ memberProfile m ) memRole
_ -> throwChatError CEGroupMemberNotFound
where
changeMemberRole user @ User { userId } gInfo @ GroupInfo { membership } members m gEvent = do
let GroupMember { memberId = mId , memberRole = mRole , memberStatus = mStatus , memberContactId , localDisplayName = cName } = m
GroupMember { memberRole = userRole } = membership
canChangeRole = userRole >= GRAdmin && userRole >= mRole && userRole >= memRole && memberCurrent membership
unless canChangeRole $ throwChatError CEGroupUserRole
withChatLock . procCmd $ do
unless ( mRole == memRole ) $ do
withStore' $ \ db -> updateGroupMemberRole db user m memRole
case mStatus of
GSMemInvited -> do
withStore ( \ db -> ( , ) <$> mapM ( getContact db userId ) memberContactId <*> liftIO ( getMemberInvitation db user $ groupMemberId' m ) ) >>= \ case
( Just ct , Just cReq ) -> sendGrpInvitation user ct gInfo ( m :: GroupMember ) { memberRole = memRole } cReq
_ -> throwChatError $ CEGroupCantResendInvitation gInfo cName
_ -> do
msg <- sendGroupMessage gInfo members $ XGrpMemRole mId memRole
ci <- saveSndChatItem user ( CDGroupSnd gInfo ) msg ( CISndGroupEvent gEvent ) Nothing Nothing
toView . CRNewChatItem $ AChatItem SCTGroup SMDSnd ( GroupChat gInfo ) ci
pure CRMemberRoleUser { groupInfo = gInfo , member = m { memberRole = memRole } , fromRole = mRole , toRole = memRole }
2022-07-12 19:20:56 +04:00
APIRemoveMember groupId memberId -> withUser $ \ user @ User { userId } -> do
Group gInfo @ GroupInfo { membership } members <- withStore $ \ db -> getGroup db user groupId
2022-07-15 17:49:29 +04:00
case find ( ( == memberId ) . groupMemberId' ) members of
2022-07-12 19:20:56 +04:00
Nothing -> throwChatError CEGroupMemberNotFound
2022-07-20 16:56:55 +04:00
Just m @ GroupMember { memberId = mId , memberRole = mRole , memberStatus = mStatus , memberProfile } -> do
2022-01-11 08:50:44 +00:00
let userRole = memberRole ( membership :: GroupMember )
2022-07-30 16:49:34 +04:00
canRemove = userRole >= GRAdmin && userRole >= mRole && memberCurrent membership
2022-07-27 11:16:07 +04:00
unless canRemove $ throwChatError CEGroupUserRole
2022-02-06 08:21:40 +00:00
withChatLock . procCmd $ do
2022-08-04 18:39:31 +01:00
case mStatus of
GSMemInvited -> do
2022-09-30 16:18:43 +04:00
deleteMemberConnection user m
2022-08-04 18:39:31 +01:00
withStore' $ \ db -> deleteGroupMember db user m
_ -> do
msg <- sendGroupMessage gInfo members $ XGrpMemDel mId
2022-08-18 11:35:31 +04:00
ci <- saveSndChatItem user ( CDGroupSnd gInfo ) msg ( CISndGroupEvent $ SGEMemberDeleted memberId ( fromLocalProfile memberProfile ) ) Nothing Nothing
2022-08-04 18:39:31 +01:00
toView . CRNewChatItem $ AChatItem SCTGroup SMDSnd ( GroupChat gInfo ) ci
2022-09-30 16:18:43 +04:00
deleteMemberConnection user m
2022-08-04 18:39:31 +01:00
withStore' $ \ db -> updateGroupMemberStatus db userId m GSMemRemoved
2022-07-20 16:56:55 +04:00
pure $ CRUserDeletedMember gInfo m { memberStatus = GSMemRemoved }
2022-07-12 19:20:56 +04:00
APILeaveGroup groupId -> withUser $ \ user @ User { userId } -> do
Group gInfo @ GroupInfo { membership } members <- withStore $ \ db -> getGroup db user groupId
2022-02-06 08:21:40 +00:00
withChatLock . procCmd $ do
2022-07-20 16:56:55 +04:00
msg <- sendGroupMessage gInfo members XGrpLeave
ci <- saveSndChatItem user ( CDGroupSnd gInfo ) msg ( CISndGroupEvent SGEUserLeft ) Nothing Nothing
toView . CRNewChatItem $ AChatItem SCTGroup SMDSnd ( GroupChat gInfo ) ci
2022-07-19 18:21:15 +04:00
-- TODO delete direct connections that were unused
2022-10-13 17:12:22 +04:00
deleteGroupLink' user gInfo ` catchError ` \ _ -> pure ()
2022-09-30 16:18:43 +04:00
forM_ members $ deleteMemberConnection user
2022-06-18 20:06:13 +01:00
withStore' $ \ db -> updateGroupMemberStatus db userId membership GSMemLeft
2022-07-19 18:21:15 +04:00
pure $ CRLeftMemberUser gInfo { membership = membership { memberStatus = GSMemLeft } }
2022-07-12 19:20:56 +04:00
APIListMembers groupId -> CRGroupMembers <$> withUser ( \ user -> withStore ( \ db -> getGroup db user groupId ) )
2022-09-05 15:23:38 +01:00
AddMember gName cName memRole -> withUser $ \ user -> do
( groupId , contactId ) <- withStore $ \ db -> ( , ) <$> getGroupIdByName db user gName <*> getContactIdByName db user cName
2022-07-12 19:20:56 +04:00
processChatCommand $ APIAddMember groupId contactId memRole
JoinGroup gName -> withUser $ \ user -> do
groupId <- withStore $ \ db -> getGroupIdByName db user gName
processChatCommand $ APIJoinGroup groupId
MemberRole gName groupMemberName memRole -> do
( groupId , groupMemberId ) <- getGroupAndMemberId gName groupMemberName
processChatCommand $ APIMemberRole groupId groupMemberId memRole
RemoveMember gName groupMemberName -> do
( groupId , groupMemberId ) <- getGroupAndMemberId gName groupMemberName
processChatCommand $ APIRemoveMember groupId groupMemberId
LeaveGroup gName -> withUser $ \ user -> do
groupId <- withStore $ \ db -> getGroupIdByName db user gName
processChatCommand $ APILeaveGroup groupId
2022-02-06 16:18:01 +00:00
DeleteGroup gName -> withUser $ \ user -> do
2022-07-12 19:20:56 +04:00
groupId <- withStore $ \ db -> getGroupIdByName db user gName
processChatCommand $ APIDeleteChat ( ChatRef CTGroup groupId )
2022-05-17 11:22:09 +04:00
ClearGroup gName -> withUser $ \ user -> do
2022-06-18 20:06:13 +01:00
groupId <- withStore $ \ db -> getGroupIdByName db user gName
2022-05-17 11:22:09 +04:00
processChatCommand $ APIClearChat ( ChatRef CTGroup groupId )
2022-07-12 19:20:56 +04:00
ListMembers gName -> withUser $ \ user -> do
groupId <- withStore $ \ db -> getGroupIdByName db user gName
processChatCommand $ APIListMembers groupId
2022-06-18 20:06:13 +01:00
ListGroups -> CRGroupsList <$> withUser ( \ user -> withStore' ( ` getUserGroupDetails ` user ) )
2022-07-29 19:04:32 +01:00
APIUpdateGroupProfile groupId p' -> withUser $ \ user -> do
Group g ms <- withStore $ \ db -> getGroup db user groupId
let s = memberStatus $ membership g
canUpdate =
memberRole ( membership g :: GroupMember ) == GROwner
|| ( s == GSMemRemoved || s == GSMemLeft || s == GSMemGroupDeleted || s == GSMemInvited )
unless canUpdate $ throwChatError CEGroupUserRole
g' <- withStore $ \ db -> updateGroupProfile db user g p'
msg <- sendGroupMessage g' ms ( XGrpInfo p' )
ci <- saveSndChatItem user ( CDGroupSnd g' ) msg ( CISndGroupEvent $ SGEGroupUpdated p' ) Nothing Nothing
toView . CRNewChatItem $ AChatItem SCTGroup SMDSnd ( GroupChat g' ) ci
pure $ CRGroupUpdated g g' Nothing
UpdateGroupProfile gName profile -> withUser $ \ user -> do
groupId <- withStore $ \ db -> getGroupIdByName db user gName
processChatCommand $ APIUpdateGroupProfile groupId profile
2022-10-13 17:12:22 +04:00
APICreateGroupLink groupId -> withUser $ \ user -> withChatLock $ do
gInfo @ GroupInfo { membership = membership @ GroupMember { memberRole = userRole } } <- withStore $ \ db -> getGroupInfo db user groupId
when ( userRole < GRAdmin ) $ throwChatError CEGroupUserRole
when ( memberStatus membership == GSMemInvited ) $ throwChatError ( CEGroupNotJoined gInfo )
unless ( memberActive membership ) $ throwChatError CEGroupMemberNotActive
( connId , cReq ) <- withAgent $ \ a -> createConnection a True SCMContact
withStore $ \ db -> createGroupLink db user gInfo connId cReq
pure $ CRGroupLinkCreated gInfo cReq
APIDeleteGroupLink groupId -> withUser $ \ user -> withChatLock $ do
gInfo <- withStore $ \ db -> getGroupInfo db user groupId
deleteGroupLink' user gInfo
pure $ CRGroupLinkDeleted gInfo
APIGetGroupLink groupId -> withUser $ \ user -> do
gInfo <- withStore $ \ db -> getGroupInfo db user groupId
CRGroupLink gInfo <$> withStore ( \ db -> getGroupLink db user gInfo )
CreateGroupLink gName -> withUser $ \ user -> do
groupId <- withStore $ \ db -> getGroupIdByName db user gName
processChatCommand $ APICreateGroupLink groupId
DeleteGroupLink gName -> withUser $ \ user -> do
groupId <- withStore $ \ db -> getGroupIdByName db user gName
processChatCommand $ APIDeleteGroupLink groupId
ShowGroupLink gName -> withUser $ \ user -> do
groupId <- withStore $ \ db -> getGroupIdByName db user gName
processChatCommand $ APIGetGroupLink groupId
2022-03-13 19:34:03 +00:00
SendGroupMessageQuote gName cName quotedMsg msg -> withUser $ \ user -> do
2022-06-18 20:06:13 +01:00
groupId <- withStore $ \ db -> getGroupIdByName db user gName
quotedItemId <- withStore $ \ db -> getGroupChatItemIdByText db user groupId cName ( safeDecodeUtf8 quotedMsg )
2022-03-13 19:34:03 +00:00
let mc = MCText $ safeDecodeUtf8 msg
2022-05-05 14:04:03 +01:00
processChatCommand . APISendMessage ( ChatRef CTGroup groupId ) $ ComposedMessage Nothing ( Just quotedItemId ) mc
2022-04-28 08:34:21 +01:00
LastMessages ( Just chatName ) count -> withUser $ \ user -> do
chatRef <- getChatRef user chatName
2022-08-08 22:48:42 +04:00
CRLastMessages . aChatItems . chat <$> processChatCommand ( APIGetChat chatRef ( CPLast count ) Nothing )
2022-06-18 20:06:13 +01:00
LastMessages Nothing count -> withUser $ \ user -> withStore $ \ db ->
CRLastMessages <$> getAllChatItems db user ( CPLast count )
2022-04-30 19:18:46 +04:00
SendFile chatName f -> withUser $ \ user -> do
chatRef <- getChatRef user chatName
2022-05-05 14:04:03 +01:00
processChatCommand . APISendMessage chatRef $ ComposedMessage ( Just f ) Nothing ( MCFile " " )
2022-05-21 18:17:15 +04:00
SendImage chatName f -> withUser $ \ user -> do
chatRef <- getChatRef user chatName
filePath <- toFSFilePath f
unless ( " .jpg " ` isSuffixOf ` f || " .jpeg " ` isSuffixOf ` f ) $ throwChatError CEFileImageType { filePath }
fileSize <- getFileSize filePath
unless ( fileSize <= maxImageSize ) $ throwChatError CEFileImageSize { filePath }
processChatCommand . APISendMessage chatRef $ ComposedMessage ( Just f ) Nothing ( MCImage " " fixedImagePreview )
ForwardFile chatName fileId -> forwardFile chatName fileId SendFile
ForwardImage chatName fileId -> forwardFile chatName fileId SendImage
2022-05-11 16:18:28 +04:00
ReceiveFile fileId filePath_ -> withUser $ \ user ->
2022-04-10 13:30:58 +04:00
withChatLock . procCmd $ do
2022-06-18 20:06:13 +01:00
ft <- withStore $ \ db -> getRcvFileTransfer db user fileId
2022-04-29 15:56:56 +04:00
( CRRcvFileAccepted <$> acceptFileReceive user ft filePath_ ) ` catchError ` processError ft
2022-04-10 13:30:58 +04:00
where
processError ft = \ case
2022-04-29 15:56:56 +04:00
-- TODO AChatItem in Cancelled events
2022-04-10 13:30:58 +04:00
ChatErrorAgent ( SMP SMP . AUTH ) -> pure $ CRRcvFileAcceptedSndCancelled ft
ChatErrorAgent ( CONN DUPLICATE ) -> pure $ CRRcvFileAcceptedSndCancelled ft
e -> throwError e
2022-05-11 16:18:28 +04:00
CancelFile fileId -> withUser $ \ user @ User { userId } ->
withChatLock . procCmd $
2022-06-18 20:06:13 +01:00
withStore ( \ db -> getFileTransfer db user fileId ) >>= \ case
2022-05-11 16:18:28 +04:00
FTSnd ftm @ FileTransferMeta { cancelled } fts -> do
unless cancelled $ do
cancelSndFile user ftm fts
2022-06-18 20:06:13 +01:00
sharedMsgId <- withStore $ \ db -> getSharedMsgIdByFileId db userId fileId
2022-10-14 13:06:33 +01:00
withStore ( \ db -> getChatRefByFileId db user fileId ) >>= \ case
ChatRef CTDirect contactId -> do
contact <- withStore $ \ db -> getContact db userId contactId
void . sendDirectContactMessage contact $ XFileCancel sharedMsgId
ChatRef CTGroup groupId -> do
Group gInfo ms <- withStore $ \ db -> getGroup db user groupId
void . sendGroupMessage gInfo ms $ XFileCancel sharedMsgId
_ -> throwChatError $ CEFileInternal " invalid chat ref for file transfer "
2022-06-18 20:06:13 +01:00
ci <- withStore $ \ db -> getChatItemByFileId db user fileId
2022-05-11 16:18:28 +04:00
pure $ CRSndGroupFileCancelled ci ftm fts
FTRcv ftr @ RcvFileTransfer { cancelled } -> do
unless cancelled $ cancelRcvFileTransfer user ftr
pure $ CRRcvFileCancelled ftr
2021-09-04 07:32:56 +01:00
FileStatus fileId ->
2022-06-18 20:06:13 +01:00
CRFileTransferStatus <$> withUser ( \ user -> withStore $ \ db -> getFileTransferProgress db user fileId )
2022-08-18 11:35:31 +04:00
ShowProfile -> withUser $ \ User { profile } -> pure $ CRUserProfile ( fromLocalProfile profile )
2022-03-10 15:45:40 +04:00
UpdateProfile displayName fullName -> withUser $ \ user @ User { profile } -> do
2022-08-18 11:35:31 +04:00
let p = ( fromLocalProfile profile :: Profile ) { displayName = displayName , fullName = fullName }
2022-03-10 15:45:40 +04:00
updateProfile user p
UpdateProfileImage image -> withUser $ \ user @ User { profile } -> do
2022-08-18 11:35:31 +04:00
let p = ( fromLocalProfile profile :: Profile ) { image }
2022-03-10 15:45:40 +04:00
updateProfile user p
2021-07-27 08:08:05 +01:00
QuitChat -> liftIO exitSuccess
2022-02-14 17:51:50 +00:00
ShowVersion -> pure $ CRVersionInfo versionNumber
2021-07-12 19:00:03 +01:00
where
2022-10-04 17:19:00 +01:00
withChatLock action = asks chatLock >>= ( ` withLock ` action )
2022-02-04 08:02:48 +00:00
-- below code would make command responses asynchronous where they can be slow
-- in View.hs `r'` should be defined as `id` in this case
2022-02-16 16:48:28 +04:00
-- procCmd :: m ChatResponse -> m ChatResponse
2022-02-16 20:31:26 +00:00
-- procCmd action = do
-- ChatController {chatLock = l, smpAgent = a, outputQ = q, idsDrg = gVar} <- ask
-- corrId <- liftIO $ SMP.CorrId <$> randomBytes gVar 8
-- void . forkIO $
-- withAgentLock a . withLock l $
-- (atomically . writeTBQueue q) . (Just corrId,) =<< (action `catchError` (pure . CRChatError))
-- pure $ CRCmdAccepted corrId
-- use function below to make commands "synchronous"
procCmd :: m ChatResponse -> m ChatResponse
procCmd = id
2022-04-28 08:34:21 +01:00
getChatRef :: User -> ChatName -> m ChatRef
2022-09-05 15:23:38 +01:00
getChatRef user ( ChatName cType name ) =
2022-04-28 08:34:21 +01:00
ChatRef cType <$> case cType of
2022-09-05 15:23:38 +01:00
CTDirect -> withStore $ \ db -> getContactIdByName db user name
2022-06-18 20:06:13 +01:00
CTGroup -> withStore $ \ db -> getGroupIdByName db user name
2022-04-28 08:34:21 +01:00
_ -> throwChatError $ CECommandError " not supported "
2022-06-06 16:23:47 +01:00
checkChatStopped :: m ChatResponse -> m ChatResponse
checkChatStopped a = asks agentAsync >>= readTVarIO >>= maybe a ( const $ throwChatError CEChatNotStopped )
setStoreChanged :: m ()
setStoreChanged = asks chatStoreChanged >>= atomically . ( ` writeTVar ` True )
2022-08-31 18:07:34 +01:00
withStoreChanged :: m () -> m ChatResponse
withStoreChanged a = checkChatStopped $ a >> setStoreChanged $> CRCmdOk
checkStoreNotChanged :: m ChatResponse -> m ChatResponse
checkStoreNotChanged = ifM ( asks chatStoreChanged >>= readTVarIO ) ( throwChatError CEChatStoreChanged )
2022-04-28 08:34:21 +01:00
getSentChatItemIdByText :: User -> ChatRef -> ByteString -> m Int64
getSentChatItemIdByText user @ User { userId , localDisplayName } ( ChatRef cType cId ) msg = case cType of
2022-06-18 20:06:13 +01:00
CTDirect -> withStore $ \ db -> getDirectChatItemIdByText db userId cId SMDSnd ( safeDecodeUtf8 msg )
CTGroup -> withStore $ \ db -> getGroupChatItemIdByText db user cId ( Just localDisplayName ) ( safeDecodeUtf8 msg )
2022-04-28 07:26:43 +01:00
_ -> throwChatError $ CECommandError " not supported "
2022-02-13 13:19:24 +04:00
connectViaContact :: UserId -> ConnectionRequestUri 'CMContact -> Profile -> m ChatResponse
connectViaContact userId cReq profile = withChatLock $ do
let cReqHash = ConnReqUriHash . C . sha256Hash $ strEncode cReq
2022-06-18 20:06:13 +01:00
withStore' ( \ db -> getConnReqContactXContactId db userId cReqHash ) >>= \ case
2022-02-13 13:19:24 +04:00
( Just contact , _ ) -> pure $ CRContactAlreadyExists contact
( _ , xContactId_ ) -> procCmd $ do
let randomXContactId = XContactId <$> ( asks idsDrg >>= liftIO . ( ` randomBytes ` 16 ) )
xContactId <- maybe randomXContactId pure xContactId_
2022-08-18 11:35:31 +04:00
-- [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
2022-08-19 15:17:05 +01:00
connId <- withAgent $ \ a -> joinConnection a True cReq $ directMessage ( XContact profileToSend $ Just xContactId )
2022-08-18 11:35:31 +04:00
conn <- withStore' $ \ db -> createConnReqConnection db userId connId cReqHash xContactId incognitoProfile
2022-04-23 17:32:40 +01:00
toView $ CRNewContactConnection conn
2022-08-18 11:35:31 +04:00
pure $ CRSentInvitation incognitoProfile
2021-08-02 20:10:24 +01:00
contactMember :: Contact -> [ GroupMember ] -> Maybe GroupMember
contactMember Contact { contactId } =
find $ \ GroupMember { memberContactId = cId , memberStatus = s } ->
cId == Just contactId && s /= GSMemRemoved && s /= GSMemLeft
2022-10-14 13:06:33 +01:00
checkSndFile :: FilePath -> Integer -> m ( Integer , Integer , Maybe InlineFileMode )
checkSndFile f n = do
2022-04-15 09:36:38 +04:00
fsFilePath <- toFSFilePath f
unlessM ( doesFileExist fsFilePath ) . throwChatError $ CEFileNotFound f
2022-10-14 13:06:33 +01:00
ChatConfig { fileChunkSize , inlineFiles } <- asks config
fileSize <- getFileSize fsFilePath
let chunks = - ( ( - fileSize ) ` div ` fileChunkSize )
pure ( fileSize , fileChunkSize , inlineFileMode inlineFiles chunks n )
inlineFileMode InlineFilesConfig { offerChunks , sendChunks , totalSendChunks } chunks n
| chunks > offerChunks = Nothing
| chunks > sendChunks || chunks * n > totalSendChunks = Just IFMOffer
| otherwise = Just IFMSent
2022-03-10 15:45:40 +04:00
updateProfile :: User -> Profile -> m ChatResponse
2022-08-24 19:03:43 +04:00
updateProfile user @ User { profile = p @ LocalProfile { profileId , localAlias } } p' @ Profile { displayName }
2022-08-18 11:35:31 +04:00
| p' == fromLocalProfile p = pure CRUserProfileNoChange
2022-03-29 08:53:30 +01:00
| otherwise = do
2022-10-14 13:06:33 +01:00
withStore $ \ db -> updateUserProfile db user p'
let user' = ( user :: User ) { localDisplayName = displayName , profile = toLocalProfile profileId p' localAlias }
asks currentUser >>= atomically . ( ` writeTVar ` Just 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 ( fromLocalProfile p ) p'
2022-03-29 08:53:30 +01:00
isReady :: Contact -> Bool
isReady ct =
let s = connStatus $ activeConn ( ct :: Contact )
in s == ConnReady || s == ConnSndReady
2022-05-04 13:31:00 +01:00
withCurrentCall :: ContactId -> ( UserId -> Contact -> Call -> m ( Maybe Call ) ) -> m ChatResponse
2022-07-04 11:15:25 +01:00
withCurrentCall ctId action = withUser $ \ user @ User { userId } -> do
2022-06-18 20:06:13 +01:00
ct <- withStore $ \ db -> getContact db userId ctId
2022-05-04 13:31:00 +01:00
calls <- asks currentCalls
2022-05-03 10:22:35 +01:00
withChatLock $
2022-05-04 13:31:00 +01:00
atomically ( TM . lookup ctId calls ) >>= \ case
2022-05-03 10:22:35 +01:00
Nothing -> throwChatError CENoCurrentCall
Just call @ Call { contactId }
| ctId == contactId -> do
2022-10-14 13:06:33 +01:00
call_ <- action userId ct call
case call_ of
Just call' -> do
unless ( isRcvInvitation call' ) $ withStore' $ \ db -> deleteCalls db user ctId
atomically $ TM . insert ctId call' calls
_ -> do
withStore' $ \ db -> deleteCalls db user ctId
atomically $ TM . delete ctId calls
pure CRCmdOk
2022-05-03 10:22:35 +01:00
| otherwise -> throwChatError $ CECallContact contactId
2022-05-21 18:17:15 +04:00
forwardFile :: ChatName -> FileTransferId -> ( ChatName -> FilePath -> ChatCommand ) -> m ChatResponse
forwardFile chatName fileId sendCommand = withUser $ \ user -> do
2022-06-18 20:06:13 +01:00
withStore ( \ db -> getFileTransfer db user fileId ) >>= \ case
2022-05-21 18:17:15 +04:00
FTRcv RcvFileTransfer { fileStatus = RFSComplete RcvFileInfo { filePath } } -> forward filePath
FTSnd { fileTransferMeta = FileTransferMeta { filePath } } -> forward filePath
_ -> throwChatError CEFileNotReceived { fileId }
where
forward = processChatCommand . sendCommand chatName
2022-07-12 19:20:56 +04:00
getGroupAndMemberId :: GroupName -> ContactName -> m ( GroupId , GroupMemberId )
getGroupAndMemberId gName groupMemberName = withUser $ \ user -> do
withStore $ \ db -> do
groupId <- getGroupIdByName db user gName
groupMemberId <- getGroupMemberIdByName db user groupId groupMemberName
pure ( groupId , groupMemberId )
2022-10-13 17:12:22 +04:00
sendGrpInvitation :: ChatMonad m => User -> Contact -> GroupInfo -> GroupMember -> ConnReqInvitation -> m ()
sendGrpInvitation user ct @ Contact { localDisplayName } GroupInfo { groupId , groupProfile , membership } GroupMember { groupMemberId , memberId , memberRole = memRole } cReq = do
let GroupMember { memberRole = userRole , memberId = userMemberId } = membership
groupInv = GroupInvitation ( MemberIdRole userMemberId userRole ) ( MemberIdRole memberId memRole ) cReq groupProfile
2022-10-14 13:06:33 +01:00
( msg , _ ) <- sendDirectContactMessage ct $ XGrpInv groupInv
2022-10-13 17:12:22 +04:00
let content = CISndGroupInvitation ( CIGroupInvitation { groupId , groupMemberId , localDisplayName , groupProfile , status = CIGISPending } ) memRole
ci <- saveSndChatItem user ( CDDirectSnd ct ) msg content Nothing Nothing
toView . CRNewChatItem $ AChatItem SCTDirect SMDSnd ( DirectChat ct ) ci
setActive $ ActiveG localDisplayName
2022-04-10 13:30:58 +04:00
2022-09-28 20:47:06 +04:00
setExpireCIs :: ( MonadUnliftIO m , MonadReader ChatController m ) => Bool -> m ()
setExpireCIs b = do
expire <- asks expireCIs
atomically $ writeTVar expire b
2022-10-04 01:33:36 +04:00
deleteFile :: forall m . ChatMonad m => User -> CIFileInfo -> m ()
2022-10-05 19:54:28 +04:00
deleteFile user CIFileInfo { filePath , fileId , fileStatus } =
2022-10-06 14:00:02 +04:00
( cancel' >> delete ) ` catchError ` ( toView . CRChatError )
2022-10-04 01:33:36 +04:00
where
2022-10-05 19:54:28 +04:00
cancel' = forM_ fileStatus $ \ ( AFS dir status ) ->
unless ( ciFileEnded status ) $
case dir of
SMDSnd -> do
( ftm @ FileTransferMeta { cancelled } , fts ) <- withStore ( \ db -> getSndFileTransfer db user fileId )
unless cancelled $ cancelSndFile user ftm fts
SMDRcv -> do
ft @ RcvFileTransfer { cancelled } <- withStore ( \ db -> getRcvFileTransfer db user fileId )
unless cancelled $ cancelRcvFileTransfer user ft
2022-10-04 01:33:36 +04:00
delete = withFilesFolder $ \ filesFolder ->
forM_ filePath $ \ fPath -> do
let fsFilePath = filesFolder <> " / " <> fPath
removeFile fsFilePath ` E . catch ` \ ( _ :: E . SomeException ) ->
removePathForcibly fsFilePath ` E . catch ` \ ( _ :: E . SomeException ) -> pure ()
-- perform an action only if filesFolder is set (i.e. on mobile devices)
withFilesFolder :: ( FilePath -> m () ) -> m ()
withFilesFolder action = asks filesFolder >>= readTVarIO >>= mapM_ action
2022-09-28 20:47:06 +04:00
2022-05-04 13:31:00 +01:00
updateCallItemStatus :: ChatMonad m => UserId -> Contact -> Call -> WebRTCCallStatus -> Maybe MessageId -> m ()
updateCallItemStatus userId ct Call { chatItemId } receivedStatus msgId_ = do
aciContent_ <- callStatusItemContent userId ct chatItemId receivedStatus
forM_ aciContent_ $ \ aciContent -> updateDirectChatItemView userId ct chatItemId aciContent msgId_
updateDirectChatItemView :: ChatMonad m => UserId -> Contact -> ChatItemId -> ACIContent -> Maybe MessageId -> m ()
updateDirectChatItemView userId ct @ Contact { contactId } chatItemId ( ACIContent msgDir ciContent ) msgId_ = do
2022-06-18 20:06:13 +01:00
updCi <- withStore $ \ db -> updateDirectChatItem db userId contactId chatItemId ciContent msgId_
2022-05-04 13:31:00 +01:00
toView . CRChatItemUpdated $ AChatItem SCTDirect msgDir ( DirectChat ct ) updCi
callStatusItemContent :: ChatMonad m => UserId -> Contact -> ChatItemId -> WebRTCCallStatus -> m ( Maybe ACIContent )
callStatusItemContent userId Contact { contactId } chatItemId receivedStatus = do
CChatItem msgDir ChatItem { meta = CIMeta { updatedAt } , content } <-
2022-06-18 20:06:13 +01:00
withStore $ \ db -> getDirectChatItem db userId contactId chatItemId
2022-05-04 13:31:00 +01:00
ts <- liftIO getCurrentTime
let callDuration :: Int = nominalDiffTimeToSeconds ( ts ` diffUTCTime ` updatedAt ) ` div' ` 1
callStatus = case content of
CISndCall st _ -> Just st
CIRcvCall st _ -> Just st
_ -> Nothing
newState_ = case ( callStatus , receivedStatus ) of
( Just CISCallProgress , WCSConnected ) -> Nothing -- if call in-progress received connected -> no change
( Just CISCallProgress , WCSDisconnected ) -> Just ( CISCallEnded , callDuration ) -- calculate in-progress duration
( Just CISCallProgress , WCSFailed ) -> Just ( CISCallEnded , callDuration ) -- whether call disconnected or failed
2022-05-20 07:43:44 +01:00
( Just CISCallPending , WCSDisconnected ) -> Just ( CISCallMissed , 0 )
2022-05-04 13:31:00 +01:00
( Just CISCallEnded , _ ) -> Nothing -- if call already ended or failed -> no change
( Just CISCallError , _ ) -> Nothing
2022-05-24 19:34:27 +01:00
( Just _ , WCSConnecting ) -> Just ( CISCallNegotiated , 0 )
2022-05-04 13:31:00 +01:00
( Just _ , WCSConnected ) -> Just ( CISCallProgress , 0 ) -- if call ended that was never connected, duration = 0
( Just _ , WCSDisconnected ) -> Just ( CISCallEnded , 0 )
( Just _ , WCSFailed ) -> Just ( CISCallError , 0 )
( Nothing , _ ) -> Nothing -- some other content - we should never get here, but no exception is thrown
pure $ aciContent msgDir <$> newState_
where
aciContent :: forall d . SMsgDirection d -> ( CICallStatus , Int ) -> ACIContent
aciContent msgDir ( callStatus' , duration ) = case msgDir of
SMDSnd -> ACIContent SMDSnd $ CISndCall callStatus' duration
SMDRcv -> ACIContent SMDRcv $ CIRcvCall callStatus' duration
2022-04-15 09:36:38 +04:00
-- mobile clients use file paths relative to app directory (e.g. for the reason ios app directory changes on updates),
-- so we have to differentiate between the file path stored in db and communicated with frontend, and the file path
-- used during file transfer for actual operations with file system
toFSFilePath :: ChatMonad m => FilePath -> m FilePath
2022-04-15 13:16:34 +01:00
toFSFilePath f =
maybe f ( <> " / " <> f ) <$> ( readTVarIO =<< asks filesFolder )
2022-04-15 09:36:38 +04:00
2022-04-29 15:56:56 +04:00
acceptFileReceive :: forall m . ChatMonad m => User -> RcvFileTransfer -> Maybe FilePath -> m AChatItem
2022-10-14 13:06:33 +01:00
acceptFileReceive user @ User { userId } RcvFileTransfer { fileId , fileInvitation = FileInvitation { fileName = fName , fileConnReq , fileInline , fileSize } , fileStatus , grpMemberId } filePath_ = do
2022-05-11 16:18:28 +04:00
unless ( fileStatus == RFSNew ) $ case fileStatus of
RFSCancelled _ -> throwChatError $ CEFileCancelled fName
_ -> throwChatError $ CEFileAlreadyReceiving fName
2022-04-10 13:30:58 +04:00
case fileConnReq of
2022-05-11 16:18:28 +04:00
-- direct file protocol
2022-09-20 14:46:30 +01:00
Just connReq -> do
agentConnId <- withAgent $ \ a -> joinConnection a True connReq . directMessage $ XFileAcpt fName
2022-10-14 13:06:33 +01:00
filePath <- getRcvFilePath fileId filePath_ fName
2022-09-20 14:46:30 +01:00
withStore $ \ db -> acceptRcvFileTransfer db user fileId agentConnId ConnJoined filePath
-- group & direct file protocol
Nothing -> do
chatRef <- withStore $ \ db -> getChatRefByFileId db user fileId
case ( chatRef , grpMemberId ) of
( ChatRef CTDirect contactId , Nothing ) -> do
ct <- withStore $ \ db -> getContact db userId contactId
( msg , ci ) <- acceptFile
void $ sendDirectContactMessage ct msg
pure ci
( ChatRef CTGroup groupId , Just memId ) -> do
GroupMember { activeConn } <- withStore $ \ db -> getGroupMember db user groupId memId
2022-04-10 13:30:58 +04:00
case activeConn of
2022-05-11 16:18:28 +04:00
Just conn -> do
2022-09-20 14:46:30 +01:00
( msg , ci ) <- acceptFile
void $ sendDirectMessage conn msg $ GroupId groupId
2022-05-11 16:18:28 +04:00
pure ci
_ -> throwChatError $ CEFileInternal " member connection not active "
2022-09-20 14:46:30 +01:00
_ -> throwChatError $ CEFileInternal " invalid chat ref for file transfer "
2022-04-10 13:30:58 +04:00
where
2022-10-14 13:06:33 +01:00
acceptFile :: m ( ChatMsgEvent 'Json , AChatItem )
2022-09-20 14:46:30 +01:00
acceptFile = do
sharedMsgId <- withStore $ \ db -> getSharedMsgIdByFileId db userId fileId
2022-10-14 13:06:33 +01:00
filePath <- getRcvFilePath fileId filePath_ fName
ChatConfig { fileChunkSize , inlineFiles } <- asks config
if
| fileInline == Just IFMOffer && fileSize <= fileChunkSize * receiveChunks inlineFiles -> do
-- accepting inline
ci <- withStore $ \ db -> acceptRcvInlineFT db user fileId filePath
pure ( XFileAcptInv sharedMsgId Nothing fName , ci )
| fileInline == Just IFMSent -> throwChatError $ CEFileAlreadyReceiving fName
| otherwise -> do
-- accepting via a new connection
( agentConnId , fileInvConnReq ) <- withAgent $ \ a -> createConnection a True SCMInvitation
ci <- withStore $ \ db -> acceptRcvFileTransfer db user fileId agentConnId ConnNew filePath
pure ( XFileAcptInv sharedMsgId ( Just fileInvConnReq ) fName , ci )
getRcvFilePath :: forall m . ChatMonad m => FileTransferId -> Maybe FilePath -> String -> m FilePath
getRcvFilePath fileId fPath_ fn = case fPath_ of
Nothing ->
asks filesFolder >>= readTVarIO >>= \ case
Nothing -> do
dir <- ( ` combine ` " Downloads " ) <$> getHomeDirectory
ifM ( doesDirectoryExist dir ) ( pure dir ) getTemporaryDirectory
>>= ( ` uniqueCombine ` fn )
>>= createEmptyFile
Just filesFolder ->
filesFolder ` uniqueCombine ` fn
>>= createEmptyFile
>>= pure <$> takeFileName
Just fPath ->
ifM
( doesDirectoryExist fPath )
( fPath ` uniqueCombine ` fn >>= createEmptyFile )
$ ifM
( doesFileExist fPath )
( throwChatError $ CEFileAlreadyExists fPath )
( createEmptyFile fPath )
where
createEmptyFile :: FilePath -> m FilePath
createEmptyFile fPath = emptyFile fPath ` E . catch ` ( throwChatError . CEFileWrite fPath . ( show :: E . SomeException -> String ) )
emptyFile :: FilePath -> m FilePath
emptyFile fPath = do
h <- getFileHandle fileId fPath rcvFiles AppendMode
liftIO $ B . hPut h " " >> hFlush h
pure fPath
uniqueCombine :: FilePath -> String -> m FilePath
uniqueCombine filePath fileName = tryCombine ( 0 :: Int )
2021-09-04 07:32:56 +01:00
where
2022-10-14 13:06:33 +01:00
tryCombine n =
let ( name , ext ) = splitExtensions fileName
suffix = if n == 0 then " " else " _ " <> show n
f = filePath ` combine ` ( name <> suffix <> ext )
in ifM ( doesFileExist f ) ( tryCombine $ n + 1 ) ( pure f )
2021-06-25 18:18:24 +01:00
2022-10-14 14:57:01 +04:00
acceptContactRequest :: ChatMonad m => User -> UserContactRequest -> Maybe IncognitoProfile -> m Contact
acceptContactRequest user @ User { userId } UserContactRequest { agentInvitationId = AgentInvId invId , localDisplayName = cName , profileId , profile = p , userContactLinkId , xContactId } incognitoProfile = do
let profileToSend = profileToSendOnAccept user incognitoProfile
acId <- withAgent $ \ a -> acceptContact a True invId . directMessage $ XInfo profileToSend
withStore' $ \ db -> createAcceptedContact db userId acId cName profileId p userContactLinkId xContactId incognitoProfile
acceptContactRequestAsync :: ChatMonad m => User -> UserContactRequest -> Maybe IncognitoProfile -> m Contact
acceptContactRequestAsync user @ User { userId } UserContactRequest { agentInvitationId = AgentInvId invId , localDisplayName = cName , profileId , profile = p , userContactLinkId , xContactId } incognitoProfile = do
let profileToSend = profileToSendOnAccept user incognitoProfile
( cmdId , acId ) <- agentAcceptContactAsync user True invId $ XInfo profileToSend
withStore' $ \ db -> do
ct @ Contact { activeConn = Connection { connId } } <- createAcceptedContact db userId acId cName profileId p userContactLinkId xContactId incognitoProfile
setCommandConnId db user cmdId connId
pure ct
profileToSendOnAccept :: User -> Maybe IncognitoProfile -> Profile
profileToSendOnAccept User { profile } = \ case
Just ( NewIncognito p ) -> p
Just ( ExistingIncognito lp ) -> fromLocalProfile lp
Nothing -> fromLocalProfile profile
2022-02-14 14:59:11 +04:00
2022-10-13 17:12:22 +04:00
deleteGroupLink' :: ChatMonad m => User -> GroupInfo -> m ()
deleteGroupLink' user gInfo = do
conn <- withStore $ \ db -> getGroupLinkConnection db user gInfo
deleteAgentConnectionAsync user conn ` catchError ` \ _ -> pure ()
withStore' $ \ db -> deleteGroupLink db user gInfo
2022-07-02 10:13:06 +01:00
agentSubscriber :: ( MonadUnliftIO m , MonadReader ChatController m ) => m ()
agentSubscriber = do
2021-07-06 19:07:03 +01:00
q <- asks $ subQ . smpAgent
2021-08-05 20:51:48 +01:00
l <- asks chatLock
2021-06-25 18:18:24 +01:00
forever $ do
2022-09-14 19:45:21 +04:00
( corrId , connId , msg ) <- atomically $ readTBQueue q
2022-02-06 16:18:01 +00:00
u <- readTVarIO =<< asks currentUser
2021-08-05 20:51:48 +01:00
withLock l . void . runExceptT $
2022-09-14 19:45:21 +04:00
processAgentMessage u corrId connId msg ` catchError ` ( toView . CRChatError )
2022-02-06 16:18:01 +00:00
2022-07-17 15:51:17 +01:00
type AgentBatchSubscribe m = AgentClient -> [ ConnId ] -> ExceptT AgentErrorType m ( Map ConnId ( Either AgentErrorType () ) )
subscribeUserConnections :: forall m . ChatMonad m => AgentBatchSubscribe m -> User -> m ()
subscribeUserConnections agentBatchSubscribe user = do
-- get user connections
2022-02-25 16:29:36 +04:00
ce <- asks $ subscriptionEvents . config
2022-07-17 15:51:17 +01:00
( ctConns , cts ) <- getContactConns
( ucConns , ucs ) <- getUserContactLinkConns
( gs , mConns , ms ) <- getGroupMemberConns
( sftConns , sfts ) <- getSndFileTransferConns
( rftConns , rfts ) <- getRcvFileTransferConns
( pcConns , pcs ) <- getPendingContactConns
-- subscribe using batched commands
rs <- withAgent ( ` agentBatchSubscribe ` concat [ ctConns , ucConns , mConns , sftConns , rftConns , pcConns ] )
-- send connection events to view
contactSubsToView rs cts
contactLinkSubsToView rs ucs
groupSubsToView rs gs ms ce
sndFileSubsToView rs sfts
rcvFileSubsToView rs rfts
pendingConnSubsToView rs pcs
2021-07-25 20:23:52 +01:00
where
2022-07-17 15:51:17 +01:00
getContactConns :: m ( [ ConnId ] , Map ConnId Contact )
getContactConns = do
cts <- withStore_ getUserContacts
let connIds = map contactConnId cts
pure ( connIds , M . fromList $ zip connIds cts )
getUserContactLinkConns :: m ( [ ConnId ] , Map ConnId UserContact )
getUserContactLinkConns = do
( cs , ucs ) <- unzip <$> withStore_ getUserContactLinks
let connIds = map aConnId cs
pure ( connIds , M . fromList $ zip connIds ucs )
getGroupMemberConns :: m ( [ Group ] , [ ConnId ] , Map ConnId GroupMember )
getGroupMemberConns = do
gs <- withStore_ getUserGroups
let mPairs = concatMap ( \ ( Group _ ms ) -> mapMaybe ( \ m -> ( , m ) <$> memberConnId m ) ms ) gs
pure ( gs , map fst mPairs , M . fromList mPairs )
getSndFileTransferConns :: m ( [ ConnId ] , Map ConnId SndFileTransfer )
getSndFileTransferConns = do
sfts <- withStore_ getLiveSndFileTransfers
let connIds = map sndFileTransferConnId sfts
pure ( connIds , M . fromList $ zip connIds sfts )
getRcvFileTransferConns :: m ( [ ConnId ] , Map ConnId RcvFileTransfer )
getRcvFileTransferConns = do
rfts <- withStore_ getLiveRcvFileTransfers
let rftPairs = mapMaybe ( \ ft -> ( , ft ) <$> liveRcvFileTransferConnId ft ) rfts
pure ( map fst rftPairs , M . fromList rftPairs )
getPendingContactConns :: m ( [ ConnId ] , Map ConnId PendingContactConnection )
getPendingContactConns = do
pcs <- withStore_ getPendingContactConnections
let connIds = map aConnId' pcs
pure ( connIds , M . fromList $ zip connIds pcs )
contactSubsToView :: Map ConnId ( Either AgentErrorType () ) -> Map ConnId Contact -> m ()
contactSubsToView rs = toView . CRContactSubSummary . map ( uncurry ContactSubStatus ) . resultsFor rs
contactLinkSubsToView :: Map ConnId ( Either AgentErrorType () ) -> Map ConnId UserContact -> m ()
2022-10-13 17:12:22 +04:00
contactLinkSubsToView rs = toView . CRUserContactSubSummary . map ( uncurry UserContactSubStatus ) . resultsFor rs
2022-07-17 15:51:17 +01:00
groupSubsToView :: Map ConnId ( Either AgentErrorType () ) -> [ Group ] -> Map ConnId GroupMember -> Bool -> m ()
groupSubsToView rs gs ms ce = do
mapM_ groupSub $
2022-08-18 11:35:31 +04:00
sortOn ( \ ( Group GroupInfo { localDisplayName = g } _ ) -> g ) gs
2022-07-17 15:51:17 +01:00
toView . CRMemberSubSummary $ map ( uncurry MemberSubStatus ) mRs
where
mRs = resultsFor rs ms
groupSub :: Group -> m ()
groupSub ( Group g @ GroupInfo { membership , groupId = gId } members ) = do
when ce $ mapM_ ( toView . uncurry ( CRMemberSubError g ) ) mErrors
toView groupEvent
where
mErrors :: [ ( GroupMember , ChatError ) ]
mErrors =
2022-07-20 16:56:55 +04:00
sortOn ( \ ( GroupMember { localDisplayName = n } , _ ) -> n )
2022-07-17 15:51:17 +01:00
. filterErrors
$ filter ( \ ( GroupMember { groupId } , _ ) -> groupId == gId ) mRs
groupEvent :: ChatResponse
groupEvent
| memberStatus membership == GSMemInvited = CRGroupInvitation g
| all ( \ GroupMember { activeConn } -> isNothing activeConn ) members =
2022-10-14 13:06:33 +01:00
if memberActive membership
then CRGroupEmpty g
else CRGroupRemoved g
2022-07-17 15:51:17 +01:00
| otherwise = CRGroupSubscribed g
sndFileSubsToView :: Map ConnId ( Either AgentErrorType () ) -> Map ConnId SndFileTransfer -> m ()
sndFileSubsToView rs sfts = do
let sftRs = resultsFor rs sfts
forM_ sftRs $ \ ( ft @ SndFileTransfer { fileId , fileStatus } , err_ ) -> do
forM_ err_ $ toView . CRSndFileSubError ft
void . forkIO $ do
threadDelay 1000000
l <- asks chatLock
2022-10-04 17:19:00 +01:00
when ( fileStatus == FSConnected ) . unlessM ( isFileActive fileId sndFiles ) . withLock l $
sendFileChunk user ft
2022-07-17 15:51:17 +01:00
rcvFileSubsToView :: Map ConnId ( Either AgentErrorType () ) -> Map ConnId RcvFileTransfer -> m ()
rcvFileSubsToView rs = mapM_ ( toView . uncurry CRRcvFileSubError ) . filterErrors . resultsFor rs
pendingConnSubsToView :: Map ConnId ( Either AgentErrorType () ) -> Map ConnId PendingContactConnection -> m ()
pendingConnSubsToView rs = toView . CRPendingSubSummary . map ( uncurry PendingSubStatus ) . resultsFor rs
withStore_ :: ( DB . Connection -> User -> IO [ a ] ) -> m [ a ]
withStore_ a = withStore' ( ` a ` user ) ` catchError ` \ _ -> pure []
filterErrors :: [ ( a , Maybe ChatError ) ] -> [ ( a , ChatError ) ]
filterErrors = mapMaybe ( \ ( a , e_ ) -> ( a , ) <$> e_ )
resultsFor :: Map ConnId ( Either AgentErrorType () ) -> Map ConnId a -> [ ( a , Maybe ChatError ) ]
resultsFor rs = M . foldrWithKey' addResult []
2021-09-04 07:32:56 +01:00
where
2022-07-17 15:51:17 +01:00
addResult :: ConnId -> a -> [ ( a , Maybe ChatError ) ] -> [ ( a , Maybe ChatError ) ]
addResult connId = ( : ) . ( , err )
2021-09-04 07:32:56 +01:00
where
2022-07-17 15:51:17 +01:00
err = case M . lookup connId rs of
Just ( Left e ) -> Just $ ChatErrorAgent e
Just _ -> Nothing
_ -> Just . ChatError . CEAgentNoSubResult $ AgentConnId connId
2021-07-25 20:23:52 +01:00
2022-09-28 20:47:06 +04:00
expireChatItems :: forall m . ChatMonad m => User -> Int64 -> Bool -> m ()
2022-10-04 01:33:36 +04:00
expireChatItems user ttl sync = do
2022-09-28 20:47:06 +04:00
currentTs <- liftIO getCurrentTime
let expirationDate = addUTCTime ( - 1 * fromIntegral ttl ) currentTs
2022-10-05 19:54:28 +04:00
-- this is to keep group messages created during last 12 hours even if they're expired according to item_ts
createdAtCutoff = addUTCTime ( - 43200 :: NominalDiffTime ) currentTs
2022-09-28 20:47:06 +04:00
expire <- asks expireCIs
2022-10-05 19:54:28 +04:00
contacts <- withStore' ( ` getUserContacts ` user )
2022-10-06 14:00:02 +04:00
loop expire contacts $ processContact expirationDate
2022-10-05 19:54:28 +04:00
groups <- withStore' ( ` getUserGroupDetails ` user )
2022-10-06 14:00:02 +04:00
loop expire groups $ processGroup expirationDate createdAtCutoff
2022-09-28 20:47:06 +04:00
where
2022-10-06 14:00:02 +04:00
loop :: TVar Bool -> [ a ] -> ( a -> m () ) -> m ()
loop _ [] _ = pure ()
loop expire ( a : as ) process = continue expire $ do
process a ` catchError ` ( toView . CRChatError )
loop expire as process
continue :: TVar Bool -> m () -> m ()
continue expire = if sync then id else \ a -> whenM ( readTVarIO expire ) $ threadDelay 100000 >> a
processContact :: UTCTime -> Contact -> m ()
processContact expirationDate ct = do
2022-10-05 19:54:28 +04:00
filesInfo <- withStore' $ \ db -> getContactExpiredFileInfo db user ct expirationDate
maxItemTs_ <- withStore' $ \ db -> getContactMaxItemTs db user ct
forM_ filesInfo $ \ fileInfo -> deleteFile user fileInfo
withStore' $ \ db -> deleteContactExpiredCIs db user ct expirationDate
withStore' $ \ db -> do
ciCount_ <- getContactCICount db user ct
case ( maxItemTs_ , ciCount_ ) of
( Just ts , Just count ) -> when ( count == 0 ) $ updateContactTs db user ct ts
_ -> pure ()
2022-10-06 14:00:02 +04:00
processGroup :: UTCTime -> UTCTime -> GroupInfo -> m ()
processGroup expirationDate createdAtCutoff gInfo = do
2022-10-05 19:54:28 +04:00
filesInfo <- withStore' $ \ db -> getGroupExpiredFileInfo db user gInfo expirationDate createdAtCutoff
maxItemTs_ <- withStore' $ \ db -> getGroupMaxItemTs db user gInfo
forM_ filesInfo $ \ fileInfo -> deleteFile user fileInfo
withStore' $ \ db -> deleteGroupExpiredCIs db user gInfo expirationDate createdAtCutoff
withStore' $ \ db -> do
ciCount_ <- getGroupCICount db user gInfo
case ( maxItemTs_ , ciCount_ ) of
( Just ts , Just count ) -> when ( count == 0 ) $ updateGroupTs db user gInfo ts
_ -> pure ()
2022-09-28 20:47:06 +04:00
2022-09-14 19:45:21 +04:00
processAgentMessage :: forall m . ChatMonad m => Maybe User -> ConnId -> ACorrId -> ACommand 'Agent -> m ()
processAgentMessage Nothing _ _ _ = throwChatError CENoActiveUser
processAgentMessage ( Just User { userId } ) _ " " agentMessage = case agentMessage of
2022-08-13 14:18:12 +01:00
CONNECT p h -> hostEvent $ CRHostConnected p h
DISCONNECT p h -> hostEvent $ CRHostDisconnected p h
2022-04-25 09:17:12 +01:00
DOWN srv conns -> serverEvent srv conns CRContactsDisconnected " disconnected "
UP srv conns -> serverEvent srv conns CRContactsSubscribed " connected "
2022-06-26 15:04:44 +01:00
SUSPENDED -> toView CRChatSuspended
2022-04-25 09:17:12 +01:00
_ -> pure ()
where
2022-08-13 14:18:12 +01:00
hostEvent = whenM ( asks $ hostEvents . config ) . toView
2022-08-13 11:53:53 +01:00
serverEvent srv @ ( SMPServer host _ _ ) conns event str = do
2022-06-18 20:06:13 +01:00
cs <- withStore' $ \ db -> getConnectionsContacts db userId conns
2022-04-25 09:17:12 +01:00
toView $ event srv cs
2022-08-13 11:53:53 +01:00
showToast ( " server " <> str ) ( safeDecodeUtf8 $ strEncode host )
2022-09-14 19:45:21 +04:00
processAgentMessage ( Just user @ User { userId , profile } ) corrId agentConnId agentMessage =
2022-07-17 15:51:17 +01:00
( withStore ( \ db -> getConnectionEntity db user $ AgentConnId agentConnId ) >>= updateConnStatus ) >>= \ case
2022-01-26 16:18:27 +04:00
RcvDirectMsgConnection conn contact_ ->
processDirectMessage agentMessage conn contact_
RcvGroupMsgConnection conn gInfo m ->
processGroupMessage agentMessage conn gInfo m
2021-09-04 07:32:56 +01:00
RcvFileConnection conn ft ->
processRcvFileConn agentMessage conn ft
SndFileConnection conn ft ->
processSndFileConn agentMessage conn ft
2021-12-08 13:09:51 +00:00
UserContactConnection conn uc ->
processUserContactRequest agentMessage conn uc
2021-07-24 18:11:04 +01:00
where
2022-02-02 11:31:01 +00:00
updateConnStatus :: ConnectionEntity -> m ConnectionEntity
updateConnStatus acEntity = case agentMsgConnStatus agentMessage of
Just connStatus -> do
let conn = ( entityConnection acEntity ) { connStatus }
2022-06-18 20:06:13 +01:00
withStore' $ \ db -> updateConnectionStatus db conn connStatus
2022-02-02 17:01:12 +00:00
pure $ updateEntityConnStatus acEntity connStatus
2022-02-02 11:31:01 +00:00
Nothing -> pure acEntity
2022-01-26 16:18:27 +04:00
isMember :: MemberId -> GroupInfo -> [ GroupMember ] -> Bool
isMember memId GroupInfo { membership } members =
2022-01-11 08:50:44 +00:00
sameMemberId memId membership || isJust ( find ( sameMemberId memId ) members )
2021-07-24 18:11:04 +01:00
agentMsgConnStatus :: ACommand 'Agent -> Maybe ConnStatus
agentMsgConnStatus = \ case
2021-12-08 13:09:51 +00:00
CONF { } -> Just ConnRequested
2021-07-24 18:11:04 +01:00
INFO _ -> Just ConnSndReady
CON -> Just ConnReady
_ -> Nothing
processDirectMessage :: ACommand 'Agent -> Connection -> Maybe Contact -> m ()
2022-08-18 11:35:31 +04:00
processDirectMessage agentMsg conn @ Connection { connId , viaUserContactLink , customUserProfileId } = \ case
2021-07-24 18:11:04 +01:00
Nothing -> case agentMsg of
2022-07-20 14:57:16 +01:00
CONF confId _ connInfo -> do
2022-08-18 11:35:31 +04:00
-- [incognito] send saved profile
incognitoProfile <- forM customUserProfileId $ \ profileId -> withStore ( \ db -> getProfileById db userId profileId )
2022-08-24 19:03:43 +04:00
let profileToSend = fromLocalProfile $ fromMaybe profile incognitoProfile
2021-07-24 18:11:04 +01:00
saveConnInfo conn connInfo
2022-09-14 19:45:21 +04:00
-- [async agent commands] no continuation needed, but command should be asynchronous for stability
allowAgentConnectionAsync user conn confId $ XInfo profileToSend
2021-07-24 18:11:04 +01:00
INFO connInfo ->
saveConnInfo conn connInfo
2022-06-07 14:14:54 +01:00
MSG meta _msgFlags msgBody -> do
2022-09-14 19:45:21 +04:00
cmdId <- createAckCmd conn
_ <- saveRcvMSG conn ( ConnectionId connId ) meta msgBody cmdId
withAckMessage agentConnId cmdId meta $ pure ()
2021-12-29 23:11:55 +04:00
SENT msgId ->
2022-03-23 11:37:51 +00:00
-- ? updateDirectChatItemStatus
2021-12-29 23:11:55 +04:00
sentMsgDeliveryEvent conn msgId
2022-09-14 19:45:21 +04:00
OK ->
-- [async agent commands] continuation on receiving OK
withCompletedCommand conn agentMsg $ \ CommandData { cmdFunction , cmdId } ->
when ( cmdFunction == CFAckMessage ) $ ackMsgDeliveryEvent conn cmdId
2022-07-02 12:35:04 +04:00
MERR _ err -> toView . CRChatError $ ChatErrorAgent err -- ? updateDirectChatItemStatus
2022-09-16 19:30:02 +04:00
ERR err -> do
toView . CRChatError $ ChatErrorAgent err
when ( corrId /= " " ) $ withCompletedCommand conn agentMsg $ \ _cmdData -> pure ()
2022-01-12 11:54:40 +00:00
-- TODO add debugging output
2021-08-14 21:04:51 +01:00
_ -> pure ()
2022-03-13 19:34:03 +00:00
Just ct @ Contact { localDisplayName = c , contactId } -> case agentMsg of
2022-09-14 19:45:21 +04:00
INV ( ACR _ cReq ) ->
-- [async agent commands] XGrpMemIntro continuation on receiving INV
withCompletedCommand conn agentMsg $ \ _ ->
case cReq of
directConnReq @ ( CRInvitationUri _ _ ) -> do
contData <- withStore' $ \ db -> do
setConnConnReqInv db user connId cReq
getXGrpMemIntroContDirect db user ct
forM_ contData $ \ ( hostConnId , xGrpMemIntroCont ) ->
sendXGrpMemIntro hostConnId directConnReq xGrpMemIntroCont
CRContactUri _ -> throwChatError $ CECommandError " unexpected ConnectionRequestUri type "
2022-06-07 14:14:54 +01:00
MSG msgMeta _msgFlags msgBody -> do
2022-09-14 19:45:21 +04:00
cmdId <- createAckCmd conn
2022-10-14 13:06:33 +01:00
msg @ RcvMessage { chatMsgEvent = ACME _ event } <- saveRcvMSG conn ( ConnectionId connId ) msgMeta msgBody cmdId
2022-09-14 19:45:21 +04:00
withAckMessage agentConnId cmdId msgMeta $
2022-10-14 13:06:33 +01:00
case event of
2022-03-13 19:34:03 +00:00
XMsgNew mc -> newContentMessage ct mc msg msgMeta
2022-03-23 11:37:51 +00:00
XMsgUpdate sharedMsgId mContent -> messageUpdate ct sharedMsgId mContent msg msgMeta
2022-03-28 20:35:57 +04:00
XMsgDel sharedMsgId -> messageDelete ct sharedMsgId msg msgMeta
2022-04-10 13:30:58 +04:00
-- TODO discontinue XFile
XFile fInv -> processFileInvitation' ct fInv msg msgMeta
2022-05-11 16:18:28 +04:00
XFileCancel sharedMsgId -> xFileCancel ct sharedMsgId msgMeta
2022-10-14 13:06:33 +01:00
XFileAcptInv sharedMsgId fileConnReq_ fName -> xFileAcptInv ct sharedMsgId fileConnReq_ fName msgMeta
2021-12-29 23:11:55 +04:00
XInfo p -> xInfo ct p
2022-07-14 22:04:23 +04:00
XGrpInv gInv -> processGroupInvitation ct gInv msg msgMeta
2021-12-29 23:11:55 +04:00
XInfoProbe probe -> xInfoProbe ct probe
XInfoProbeCheck probeHash -> xInfoProbeCheck ct probeHash
XInfoProbeOk probe -> xInfoProbeOk ct probe
2022-05-03 10:22:35 +01:00
XCallInv callId invitation -> xCallInv ct callId invitation msg msgMeta
XCallOffer callId offer -> xCallOffer ct callId offer msg msgMeta
XCallAnswer callId answer -> xCallAnswer ct callId answer msg msgMeta
XCallExtra callId extraInfo -> xCallExtra ct callId extraInfo msg msgMeta
XCallEnd callId -> xCallEnd ct callId msg msgMeta
2022-10-14 13:06:33 +01:00
BFileChunk sharedMsgId chunk -> bFileChunk ct sharedMsgId chunk msgMeta
_ -> messageError $ " unsupported message: " <> T . pack ( show event )
2022-07-20 14:57:16 +01:00
CONF confId _ connInfo -> do
2021-07-24 10:26:28 +01:00
-- confirming direct connection with a member
2022-10-14 13:06:33 +01:00
ChatMessage { chatMsgEvent } <- parseChatMessage connInfo
2021-07-24 10:26:28 +01:00
case chatMsgEvent of
XGrpMemInfo _memId _memProfile -> do
-- TODO check member ID
-- TODO update member profile
2022-09-14 19:45:21 +04:00
-- [async agent commands] no continuation needed, but command should be asynchronous for stability
allowAgentConnectionAsync user conn confId XOk
2021-12-08 13:09:51 +00:00
_ -> messageError " CONF from member must have x.grp.mem.info "
2021-07-24 10:26:28 +01:00
INFO connInfo -> do
2022-10-14 13:06:33 +01:00
ChatMessage { chatMsgEvent } <- parseChatMessage connInfo
2021-07-24 10:26:28 +01:00
case chatMsgEvent of
XGrpMemInfo _memId _memProfile -> do
-- TODO check member ID
-- TODO update member profile
pure ()
2021-12-08 13:09:51 +00:00
XInfo _profile -> do
-- TODO update contact profile
pure ()
2021-07-24 10:26:28 +01:00
XOk -> pure ()
2021-12-13 12:05:57 +00:00
_ -> messageError " INFO for existing contact must have x.grp.mem.info, x.info or x.ok "
2021-07-24 18:11:04 +01:00
CON ->
2022-06-18 20:06:13 +01:00
withStore' ( \ db -> getViaGroupMember db user ct ) >>= \ case
2021-07-24 10:26:28 +01:00
Nothing -> do
2022-08-18 11:35:31 +04:00
-- [incognito] print incognito profile used for this contact
incognitoProfile <- forM customUserProfileId $ \ profileId -> withStore ( \ db -> getProfileById db userId profileId )
2022-08-24 19:03:43 +04:00
toView $ CRContactConnected ct ( fmap fromLocalProfile incognitoProfile )
2021-07-24 10:26:28 +01:00
setActive $ ActiveC c
showToast ( c <> " > " ) " connected "
2022-10-13 17:12:22 +04:00
forM_ viaUserContactLink $ \ userContactLinkId ->
2022-06-27 19:41:25 +01:00
withStore' ( \ db -> getUserContactLinkById db userId userContactLinkId ) >>= \ case
2022-10-13 17:12:22 +04:00
Just ( _ , True , mc_ , groupId_ ) -> do
forM_ mc_ $ \ mc -> do
2022-10-14 13:06:33 +01:00
( msg , _ ) <- sendDirectContactMessage ct ( XMsgNew $ MCSimple ( ExtMsgContent mc Nothing ) )
2022-10-13 17:12:22 +04:00
ci <- saveSndChatItem user ( CDDirectSnd ct ) msg ( CISndMsgContent mc ) Nothing Nothing
toView . CRNewChatItem $ AChatItem SCTDirect SMDSnd ( DirectChat ct ) ci
forM_ groupId_ $ \ groupId -> do
gInfo <- withStore $ \ db -> getGroupInfo db user groupId
gVar <- asks idsDrg
-- TODO async and continuation?
( grpAgentConnId , cReq ) <- withAgent $ \ a -> createConnection a True SCMInvitation
member <- withStore $ \ db -> createNewContactMember db gVar user groupId ct GRMember grpAgentConnId cReq
sendGrpInvitation user ct gInfo member cReq
toView $ CRSentGroupInvitation gInfo ct member
2022-06-27 19:41:25 +01:00
_ -> pure ()
2022-08-27 19:56:03 +04:00
Just ( gInfo @ GroupInfo { membership } , m @ GroupMember { activeConn } ) -> do
2022-02-14 18:49:42 +04:00
when ( maybe False ( ( == ConnReady ) . connStatus ) activeConn ) $ do
2022-01-26 16:18:27 +04:00
notifyMemberConnected gInfo m
2022-08-27 19:56:03 +04:00
let connectedIncognito = contactConnIncognito ct || memberIncognito membership
when ( memberCategory m == GCPreMember ) $ probeMatchingContacts ct connectedIncognito
2022-02-07 15:19:34 +04:00
SENT msgId -> do
2021-12-29 23:11:55 +04:00
sentMsgDeliveryEvent conn msgId
2022-10-14 13:06:33 +01:00
checkSndInlineFTComplete conn msgId
2022-06-18 20:06:13 +01:00
withStore' ( \ db -> getDirectChatItemByAgentMsgId db userId contactId connId msgId ) >>= \ case
2022-05-04 13:31:00 +01:00
Just ( CChatItem SMDSnd ci ) -> do
2022-06-18 20:06:13 +01:00
chatItem <- withStore $ \ db -> updateDirectChatItemStatus db userId contactId ( chatItemId' ci ) CISSndSent
2022-03-23 11:37:51 +00:00
toView $ CRChatItemStatusUpdated ( AChatItem SCTDirect SMDSnd ( DirectChat ct ) chatItem )
2022-05-04 13:31:00 +01:00
_ -> pure ()
2022-09-14 19:45:21 +04:00
OK ->
-- [async agent commands] continuation on receiving OK
withCompletedCommand conn agentMsg $ \ CommandData { cmdFunction , cmdId } ->
when ( cmdFunction == CFAckMessage ) $ ackMsgDeliveryEvent conn cmdId
2021-07-06 19:07:03 +01:00
END -> do
2022-01-26 16:18:27 +04:00
toView $ CRContactAnotherClient ct
2021-08-14 21:04:51 +01:00
showToast ( c <> " > " ) " connected to another client "
unsetActive $ ActiveC c
2022-01-12 11:54:40 +00:00
-- TODO print errors
2022-02-07 15:19:34 +04:00
MERR msgId err -> do
2022-06-18 20:06:13 +01:00
chatItemId_ <- withStore' $ \ db -> getChatItemIdByAgentMsgId db connId msgId
2022-08-18 11:35:31 +04:00
forM_ chatItemId_ $ \ chatItemId -> do
chatItem <- withStore $ \ db -> updateDirectChatItemStatus db userId contactId chatItemId ( agentErrToItemStatus err )
toView $ CRChatItemStatusUpdated ( AChatItem SCTDirect SMDSnd ( DirectChat ct ) chatItem )
2022-09-16 19:30:02 +04:00
ERR err -> do
toView . CRChatError $ ChatErrorAgent err
when ( corrId /= " " ) $ withCompletedCommand conn agentMsg $ \ _cmdData -> pure ()
2022-01-12 11:54:40 +00:00
-- TODO add debugging output
2021-08-14 21:04:51 +01:00
_ -> pure ()
2021-07-24 10:26:28 +01:00
2022-01-26 16:18:27 +04:00
processGroupMessage :: ACommand 'Agent -> Connection -> GroupInfo -> GroupMember -> m ()
2022-09-14 19:45:21 +04:00
processGroupMessage agentMsg conn @ Connection { connId } gInfo @ GroupInfo { groupId , localDisplayName = gName , membership , chatSettings } m = case agentMsg of
INV ( ACR _ cReq ) ->
-- [async agent commands] XGrpMemIntro continuation on receiving INV
withCompletedCommand conn agentMsg $ \ _ ->
case cReq of
groupConnReq @ ( CRInvitationUri _ _ ) -> do
contData <- withStore' $ \ db -> do
setConnConnReqInv db user connId cReq
getXGrpMemIntroContGroup db user m
forM_ contData $ \ ( hostConnId , directConnReq ) -> do
let GroupMember { groupMemberId , memberId } = m
sendXGrpMemIntro hostConnId directConnReq XGrpMemIntroCont { groupId , groupMemberId , memberId , groupConnReq }
CRContactUri _ -> throwChatError $ CECommandError " unexpected ConnectionRequestUri type "
2022-07-20 14:57:16 +01:00
CONF confId _ connInfo -> do
2022-10-14 13:06:33 +01:00
ChatMessage { chatMsgEvent } <- parseChatMessage connInfo
2021-07-24 18:11:04 +01:00
case memberCategory m of
GCInviteeMember ->
case chatMsgEvent of
2022-08-27 19:56:03 +04:00
XGrpAcpt memId
2022-01-11 08:50:44 +00:00
| sameMemberId memId m -> do
2022-10-14 13:06:33 +01:00
withStore $ \ db -> liftIO $ updateGroupMemberStatus db userId m GSMemAccepted
-- [async agent commands] no continuation needed, but command should be asynchronous for stability
allowAgentConnectionAsync user conn confId XOk
2021-07-24 18:11:04 +01:00
| otherwise -> messageError " x.grp.acpt: memberId is different from expected "
2021-12-08 13:09:51 +00:00
_ -> messageError " CONF from invited member must have x.grp.acpt "
2021-07-24 18:11:04 +01:00
_ ->
case chatMsgEvent of
XGrpMemInfo memId _memProfile
2022-01-11 08:50:44 +00:00
| sameMemberId memId m -> do
2022-10-14 13:06:33 +01:00
-- TODO update member profile
-- [async agent commands] no continuation needed, but command should be asynchronous for stability
allowAgentConnectionAsync user conn confId $ XGrpMemInfo ( memberId ( membership :: GroupMember ) ) ( fromLocalProfile $ memberProfile membership )
2021-07-24 18:11:04 +01:00
| otherwise -> messageError " x.grp.mem.info: memberId is different from expected "
2021-12-08 13:09:51 +00:00
_ -> messageError " CONF from member must have x.grp.mem.info "
2021-07-24 18:11:04 +01:00
INFO connInfo -> do
2022-10-14 13:06:33 +01:00
ChatMessage { chatMsgEvent } <- parseChatMessage connInfo
2021-07-24 18:11:04 +01:00
case chatMsgEvent of
XGrpMemInfo memId _memProfile
2022-01-11 08:50:44 +00:00
| sameMemberId memId m -> do
2022-10-14 13:06:33 +01:00
-- TODO update member profile
pure ()
2021-07-24 18:11:04 +01:00
| otherwise -> messageError " x.grp.mem.info: memberId is different from expected "
XOk -> pure ()
_ -> messageError " INFO from member must have x.grp.mem.info "
pure ()
CON -> do
2022-06-18 20:06:13 +01:00
members <- withStore' $ \ db -> getGroupMembers db user gInfo
withStore' $ \ db -> do
updateGroupMemberStatus db userId m GSMemConnected
2021-07-27 08:08:05 +01:00
unless ( memberActive membership ) $
2022-06-18 20:06:13 +01:00
updateGroupMemberStatus db userId membership GSMemConnected
2022-01-24 16:07:17 +00:00
sendPendingGroupMessages m conn
2022-09-26 18:09:45 +01:00
withAgent $ \ a -> toggleConnectionNtfs a ( aConnId conn ) $ enableNtfs chatSettings
2021-07-24 18:11:04 +01:00
case memberCategory m of
GCHostMember -> do
2022-08-27 19:56:03 +04:00
memberConnectedChatItem gInfo m
toView $ CRUserJoinedGroup gInfo { membership = membership { memberStatus = GSMemConnected } } m { memberStatus = GSMemConnected }
2021-07-24 18:11:04 +01:00
setActive $ ActiveG gName
showToast ( " # " <> gName ) " you are connected to group "
GCInviteeMember -> do
2022-08-27 19:56:03 +04:00
memberConnectedChatItem gInfo m
toView $ CRJoinedGroupMember gInfo m { memberStatus = GSMemConnected }
2021-07-24 18:11:04 +01:00
setActive $ ActiveG gName
showToast ( " # " <> gName ) $ " member " <> localDisplayName ( m :: GroupMember ) <> " is connected "
2022-06-18 20:06:13 +01:00
intros <- withStore' $ \ db -> createIntroductions db members m
2022-02-25 21:59:35 +04:00
void . sendGroupMessage gInfo members . XGrpMemNew $ memberInfo m
2022-01-24 16:07:17 +00:00
forM_ intros $ \ intro @ GroupMemberIntro { introId } -> do
2022-02-25 21:59:35 +04:00
void $ sendDirectMessage conn ( XGrpMemIntro . memberInfo $ reMember intro ) ( GroupId groupId )
2022-06-18 20:06:13 +01:00
withStore' $ \ db -> updateIntroStatus db introId GMIntroSent
2021-07-24 18:11:04 +01:00
_ -> do
-- TODO send probe and decide whether to use existing contact connection or the new contact connection
-- TODO notify member who forwarded introduction - question - where it is stored? There is via_contact but probably there should be via_member in group_members table
2022-06-18 20:06:13 +01:00
withStore' ( \ db -> getViaGroupContact db user m ) >>= \ case
2021-07-24 18:11:04 +01:00
Nothing -> do
2022-01-26 16:18:27 +04:00
notifyMemberConnected gInfo m
2021-07-24 18:11:04 +01:00
messageError " implementation error: connected member does not have contact "
2022-02-14 18:49:42 +04:00
Just ct @ Contact { activeConn = Connection { connStatus } } ->
when ( connStatus == ConnReady ) $ do
2022-01-26 16:18:27 +04:00
notifyMemberConnected gInfo m
2022-08-27 19:56:03 +04:00
let connectedIncognito = contactConnIncognito ct || memberIncognito membership
when ( memberCategory m == GCPreMember ) $ probeMatchingContacts ct connectedIncognito
2022-06-07 14:14:54 +01:00
MSG msgMeta _msgFlags msgBody -> do
2022-09-14 19:45:21 +04:00
cmdId <- createAckCmd conn
2022-10-14 13:06:33 +01:00
msg @ RcvMessage { chatMsgEvent = ACME _ event } <- saveRcvMSG conn ( GroupId groupId ) msgMeta msgBody cmdId
2022-09-14 19:45:21 +04:00
withAckMessage agentConnId cmdId msgMeta $
2022-10-14 13:06:33 +01:00
case event of
2022-03-13 19:34:03 +00:00
XMsgNew mc -> newGroupContentMessage gInfo m mc msg msgMeta
2022-10-01 14:31:21 +04:00
XMsgUpdate sharedMsgId mContent -> groupMessageUpdate gInfo m sharedMsgId mContent msg msgMeta
2022-03-28 20:35:57 +04:00
XMsgDel sharedMsgId -> groupMessageDelete gInfo m sharedMsgId msg
2022-04-10 13:30:58 +04:00
-- TODO discontinue XFile
XFile fInv -> processGroupFileInvitation' gInfo m fInv msg msgMeta
2022-05-11 16:18:28 +04:00
XFileCancel sharedMsgId -> xFileCancelGroup gInfo m sharedMsgId msgMeta
2022-10-14 13:06:33 +01:00
XFileAcptInv sharedMsgId fileConnReq_ fName -> xFileAcptInvGroup gInfo m sharedMsgId fileConnReq_ fName msgMeta
2022-07-20 16:56:55 +04:00
XGrpMemNew memInfo -> xGrpMemNew gInfo m memInfo msg msgMeta
2022-09-14 19:45:21 +04:00
XGrpMemIntro memInfo -> xGrpMemIntro gInfo m memInfo
2022-01-26 16:18:27 +04:00
XGrpMemInv memId introInv -> xGrpMemInv gInfo m memId introInv
XGrpMemFwd memInfo introInv -> xGrpMemFwd gInfo m memInfo introInv
2022-10-03 09:00:47 +01:00
XGrpMemRole memId memRole -> xGrpMemRole gInfo m memId memRole msg msgMeta
2022-07-20 16:56:55 +04:00
XGrpMemDel memId -> xGrpMemDel gInfo m memId msg msgMeta
XGrpLeave -> xGrpLeave gInfo m msg msgMeta
XGrpDel -> xGrpDel gInfo m msg msgMeta
2022-07-29 19:04:32 +01:00
XGrpInfo p' -> xGrpInfo gInfo m p' msg msgMeta
2022-10-14 13:06:33 +01:00
BFileChunk sharedMsgId chunk -> bFileChunkGroup gInfo sharedMsgId chunk msgMeta
_ -> messageError $ " unsupported message: " <> T . pack ( show event )
SENT msgId -> do
2021-12-29 23:11:55 +04:00
sentMsgDeliveryEvent conn msgId
2022-10-14 13:06:33 +01:00
checkSndInlineFTComplete conn msgId
2022-09-14 19:45:21 +04:00
OK ->
-- [async agent commands] continuation on receiving OK
withCompletedCommand conn agentMsg $ \ CommandData { cmdFunction , cmdId } ->
when ( cmdFunction == CFAckMessage ) $ ackMsgDeliveryEvent conn cmdId
2022-07-02 12:35:04 +04:00
MERR _ err -> toView . CRChatError $ ChatErrorAgent err
2022-09-16 19:30:02 +04:00
ERR err -> do
toView . CRChatError $ ChatErrorAgent err
when ( corrId /= " " ) $ withCompletedCommand conn agentMsg $ \ _cmdData -> pure ()
2022-01-12 11:54:40 +00:00
-- TODO add debugging output
2021-08-14 21:04:51 +01:00
_ -> pure ()
2021-07-24 10:26:28 +01:00
2021-09-04 07:32:56 +01:00
processSndFileConn :: ACommand 'Agent -> Connection -> SndFileTransfer -> m ()
processSndFileConn agentMsg conn ft @ SndFileTransfer { fileId , fileName , fileStatus } =
case agentMsg of
2022-05-11 16:18:28 +04:00
-- SMP CONF for SndFileConnection happens for direct file protocol
-- when recipient of the file "joins" connection created by the sender
2022-07-20 14:57:16 +01:00
CONF confId _ connInfo -> do
2022-10-14 13:06:33 +01:00
ChatMessage { chatMsgEvent } <- parseChatMessage connInfo
2021-09-04 07:32:56 +01:00
case chatMsgEvent of
2021-12-29 23:11:55 +04:00
-- TODO save XFileAcpt message
2021-09-04 07:32:56 +01:00
XFileAcpt name
| name == fileName -> do
2022-10-14 13:06:33 +01:00
withStore' $ \ db -> updateSndFileStatus db ft FSAccepted
-- [async agent commands] no continuation needed, but command should be asynchronous for stability
allowAgentConnectionAsync user conn confId XOk
2021-09-04 07:32:56 +01:00
| otherwise -> messageError " x.file.acpt: fileName is different from expected "
2021-12-08 13:09:51 +00:00
_ -> messageError " CONF from file connection must have x.file.acpt "
2021-09-04 07:32:56 +01:00
CON -> do
2022-06-18 20:06:13 +01:00
ci <- withStore $ \ db -> do
liftIO $ updateSndFileStatus db ft FSConnected
updateDirectCIFileStatus db user fileId CIFSSndTransfer
2022-05-05 10:37:53 +01:00
toView $ CRSndFileStart ci ft
sendFileChunk user ft
2021-09-04 07:32:56 +01:00
SENT msgId -> do
2022-06-18 20:06:13 +01:00
withStore' $ \ db -> updateSndFileChunkSent db ft msgId
2022-05-05 10:37:53 +01:00
unless ( fileStatus == FSCancelled ) $ sendFileChunk user ft
2021-09-04 07:32:56 +01:00
MERR _ err -> do
2022-09-30 16:18:43 +04:00
cancelSndFileTransfer user ft
2021-09-04 07:32:56 +01:00
case err of
2022-05-05 10:37:53 +01:00
SMP SMP . AUTH -> unless ( fileStatus == FSCancelled ) $ do
2022-06-18 20:06:13 +01:00
ci <- withStore $ \ db -> getChatItemByFileId db user fileId
2022-05-05 10:37:53 +01:00
toView $ CRSndFileRcvCancelled ci ft
2022-01-26 21:20:08 +00:00
_ -> throwChatError $ CEFileSend fileId err
2022-09-14 19:45:21 +04:00
MSG meta _ _ -> do
cmdId <- createAckCmd conn
withAckMessage agentConnId cmdId meta $ pure ()
OK ->
-- [async agent commands] continuation on receiving OK
withCompletedCommand conn agentMsg $ \ _cmdData -> pure ()
2022-09-16 19:30:02 +04:00
ERR err -> do
toView . CRChatError $ ChatErrorAgent err
when ( corrId /= " " ) $ withCompletedCommand conn agentMsg $ \ _cmdData -> pure ()
2022-01-12 11:54:40 +00:00
-- TODO add debugging output
2021-09-04 07:32:56 +01:00
_ -> pure ()
processRcvFileConn :: ACommand 'Agent -> Connection -> RcvFileTransfer -> m ()
2022-10-14 13:06:33 +01:00
processRcvFileConn agentMsg conn ft =
2021-09-04 07:32:56 +01:00
case agentMsg of
2022-05-11 16:18:28 +04:00
-- SMP CONF for RcvFileConnection happens for group file protocol
-- when sender of the file "joins" connection created by the recipient
-- (sender doesn't create connections for all group members)
2022-07-20 14:57:16 +01:00
CONF confId _ connInfo -> do
2022-10-14 13:06:33 +01:00
ChatMessage { chatMsgEvent } <- parseChatMessage connInfo
2022-04-05 10:01:08 +04:00
case chatMsgEvent of
2022-09-14 19:45:21 +04:00
XOk -> allowAgentConnectionAsync user conn confId XOk -- [async agent commands] no continuation needed, but command should be asynchronous for stability
2022-04-05 10:01:08 +04:00
_ -> pure ()
2022-10-14 13:06:33 +01:00
CON -> startReceivingFile ft
MSG meta _ msgBody -> do
2022-09-14 19:45:21 +04:00
cmdId <- createAckCmd conn
2022-10-14 13:06:33 +01:00
withAckMessage agentConnId cmdId meta $
parseFileChunk msgBody >>= receiveFileChunk ft ( Just conn ) meta
2022-09-14 19:45:21 +04:00
OK ->
-- [async agent commands] continuation on receiving OK
withCompletedCommand conn agentMsg $ \ _cmdData -> pure ()
2022-07-02 12:35:04 +04:00
MERR _ err -> toView . CRChatError $ ChatErrorAgent err
2022-09-16 19:30:02 +04:00
ERR err -> do
toView . CRChatError $ ChatErrorAgent err
when ( corrId /= " " ) $ withCompletedCommand conn agentMsg $ \ _cmdData -> pure ()
2022-01-12 11:54:40 +00:00
-- TODO add debugging output
2021-09-04 07:32:56 +01:00
_ -> pure ()
2022-10-14 13:06:33 +01:00
startReceivingFile :: RcvFileTransfer -> m ()
startReceivingFile ft @ RcvFileTransfer { fileId } = do
ci <- withStore $ \ db -> do
liftIO $ updateRcvFileStatus db ft FSConnected
liftIO $ updateCIFileStatus db user fileId CIFSRcvTransfer
getChatItemByFileId db user fileId
toView $ CRRcvFileStart ci
receiveFileChunk :: RcvFileTransfer -> Maybe Connection -> MsgMeta -> FileChunk -> m ()
receiveFileChunk ft @ RcvFileTransfer { fileId , chunkSize , cancelled } conn_ MsgMeta { recipient = ( msgId , _ ) , integrity } = \ case
FileChunkCancel ->
unless cancelled $ do
cancelRcvFileTransfer user ft
toView ( CRRcvFileSndCancelled ft )
FileChunk { chunkNo , chunkBytes = chunk } -> do
case integrity of
MsgOk -> pure ()
MsgError MsgDuplicate -> pure () -- TODO remove once agent removes duplicates
MsgError e ->
badRcvFileChunk ft $ " invalid file chunk number " <> show chunkNo <> " : " <> show e
withStore' ( \ db -> createRcvFileChunk db ft chunkNo msgId ) >>= \ case
RcvChunkOk ->
if B . length chunk /= fromInteger chunkSize
then badRcvFileChunk ft " incorrect chunk size "
else appendFileChunk ft chunkNo chunk
RcvChunkFinal ->
if B . length chunk > fromInteger chunkSize
then badRcvFileChunk ft " incorrect chunk size "
else do
appendFileChunk ft chunkNo chunk
ci <- withStore $ \ db -> do
liftIO $ do
updateRcvFileStatus db ft FSComplete
updateCIFileStatus db user fileId CIFSRcvComplete
deleteRcvFileChunks db ft
getChatItemByFileId db user fileId
toView $ CRRcvFileComplete ci
closeFileHandle fileId rcvFiles
mapM_ ( deleteAgentConnectionAsync user ) conn_
RcvChunkDuplicate -> pure ()
RcvChunkError -> badRcvFileChunk ft $ " incorrect chunk number " <> show chunkNo
2021-12-08 13:09:51 +00:00
processUserContactRequest :: ACommand 'Agent -> Connection -> UserContact -> m ()
2022-09-16 19:30:02 +04:00
processUserContactRequest agentMsg conn UserContact { userContactLinkId } = case agentMsg of
2022-07-20 14:57:16 +01:00
REQ invId _ connInfo -> do
2022-10-14 13:06:33 +01:00
ChatMessage { chatMsgEvent } <- parseChatMessage connInfo
2021-12-08 13:09:51 +00:00
case chatMsgEvent of
2022-02-13 13:19:24 +04:00
XContact p xContactId_ -> profileContactRequest invId p xContactId_
XInfo p -> profileContactRequest invId p Nothing
2021-12-08 13:09:51 +00:00
-- TODO show/log error, other events in contact request
_ -> pure ()
2022-07-02 12:35:04 +04:00
MERR _ err -> toView . CRChatError $ ChatErrorAgent err
2022-09-16 19:30:02 +04:00
ERR err -> do
toView . CRChatError $ ChatErrorAgent err
when ( corrId /= " " ) $ withCompletedCommand conn agentMsg $ \ _cmdData -> pure ()
2022-01-12 11:54:40 +00:00
-- TODO add debugging output
2021-12-08 13:09:51 +00:00
_ -> pure ()
where
2022-02-13 13:19:24 +04:00
profileContactRequest :: InvitationId -> Profile -> Maybe XContactId -> m ()
profileContactRequest invId p xContactId_ = do
2022-06-18 20:06:13 +01:00
withStore ( \ db -> createOrUpdateContactRequest db userId userContactLinkId invId p xContactId_ ) >>= \ case
2022-05-14 00:57:24 +04:00
CORContact contact -> toView $ CRContactRequestAlreadyAccepted contact
CORRequest cReq @ UserContactRequest { localDisplayName } -> do
2022-10-13 17:12:22 +04:00
withStore' ( \ db -> getUserContactLinkById db userId userContactLinkId ) >>= \ case
Just ( _ , autoAccept , _ , groupId_ ) ->
if autoAccept
then case groupId_ of
Nothing -> do
-- [incognito] generate profile to send, create connection with incognito profile
-- TODO allow to configure incognito setting on auto accept instead of checking incognito mode
incognito <- readTVarIO =<< asks incognitoMode
2022-10-14 14:57:01 +04:00
incognitoProfile <- if incognito then Just . NewIncognito <$> liftIO generateRandomProfile else pure Nothing
ct <- acceptContactRequestAsync user cReq incognitoProfile
2022-10-13 17:12:22 +04:00
toView $ CRAcceptingContactRequest ct
Just groupId -> do
2022-10-14 14:57:01 +04:00
gInfo @ GroupInfo { membership = membership @ GroupMember { memberProfile } } <- withStore $ \ db -> getGroupInfo db user groupId
let profileMode = if memberIncognito membership then Just $ ExistingIncognito memberProfile else Nothing
ct <- acceptContactRequestAsync user cReq profileMode
2022-10-13 17:12:22 +04:00
toView $ CRAcceptingGroupJoinRequest gInfo ct
else do
toView $ CRReceivedContactRequest cReq
showToast ( localDisplayName <> " > " ) " wants to connect to you "
_ -> pure ()
2021-12-08 13:09:51 +00:00
2022-09-14 19:45:21 +04:00
withCompletedCommand :: Connection -> ACommand 'Agent -> ( CommandData -> m () ) -> m ()
withCompletedCommand Connection { connId } agentMsg action = do
let agentMsgTag = aCommandTag agentMsg
cmdData_ <- withStore' $ \ db -> getCommandDataByCorrId db user corrId
case cmdData_ of
Just cmdData @ CommandData { cmdId , cmdConnId = Just cmdConnId' , cmdFunction }
2022-09-16 19:41:53 +04:00
| connId == cmdConnId' && ( agentMsgTag == commandExpectedResponse cmdFunction || agentMsgTag == ERR_ ) -> do
2022-10-14 13:06:33 +01:00
withStore' $ \ db -> deleteCommand db user cmdId
action cmdData
2022-09-16 19:30:02 +04:00
| otherwise -> err cmdId $ " not matching connection id or unexpected response, corrId = " <> show corrId
Just CommandData { cmdId , cmdConnId = Nothing } -> err cmdId $ " no command connection id, corrId = " <> show corrId
Nothing -> throwChatError . CEAgentCommandError $ " command not found, corrId = " <> show corrId
where
err cmdId msg = do
withStore' $ \ db -> updateCommandStatus db user cmdId CSError
throwChatError . CEAgentCommandError $ msg
2022-09-14 19:45:21 +04:00
createAckCmd :: Connection -> m CommandId
createAckCmd Connection { connId } = do
withStore' $ \ db -> createCommand db user ( Just connId ) CFAckMessage
withAckMessage :: ConnId -> CommandId -> MsgMeta -> m () -> m ()
withAckMessage cId cmdId MsgMeta { recipient = ( msgId , _ ) } action =
-- [async agent commands] command should be asynchronous, continuation is ackMsgDeliveryEvent
action ` E . finally ` withAgent ( \ a -> ackMessageAsync a ( aCorrId cmdId ) cId msgId ` catchError ` \ _ -> pure () )
ackMsgDeliveryEvent :: Connection -> CommandId -> m ()
ackMsgDeliveryEvent Connection { connId } ackCmdId =
withStore' $ \ db -> createRcvMsgDeliveryEvent db connId ackCmdId MDSRcvAcknowledged
2021-12-29 23:11:55 +04:00
sentMsgDeliveryEvent :: Connection -> AgentMsgId -> m ()
sentMsgDeliveryEvent Connection { connId } msgId =
2022-06-18 20:06:13 +01:00
withStore $ \ db -> createSndMsgDeliveryEvent db connId msgId MDSSndSent
2021-12-29 23:11:55 +04:00
2022-02-07 15:19:34 +04:00
agentErrToItemStatus :: AgentErrorType -> CIStatus 'MDSnd
agentErrToItemStatus ( SMP AUTH ) = CISSndErrorAuth
agentErrToItemStatus err = CISSndError err
2021-09-04 07:32:56 +01:00
badRcvFileChunk :: RcvFileTransfer -> String -> m ()
2022-05-11 16:18:28 +04:00
badRcvFileChunk ft @ RcvFileTransfer { cancelled } err =
unless cancelled $ do
cancelRcvFileTransfer user ft
throwChatError $ CEFileRcvChunk err
2021-09-04 07:32:56 +01:00
2022-08-27 19:56:03 +04:00
memberConnectedChatItem :: GroupInfo -> GroupMember -> m ()
memberConnectedChatItem gInfo m = do
2022-07-20 16:56:55 +04:00
createdAt <- liftIO getCurrentTime
2022-08-27 19:56:03 +04:00
let content = CIRcvGroupEvent RGEMemberConnected
2022-07-20 16:56:55 +04:00
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
ci <- liftIO $ mkChatItem cd ciId content Nothing Nothing Nothing createdAt createdAt
toView $ CRNewChatItem $ AChatItem SCTGroup SMDRcv ( GroupChat gInfo ) ci
2022-01-26 16:18:27 +04:00
notifyMemberConnected :: GroupInfo -> GroupMember -> m ()
notifyMemberConnected gInfo m @ GroupMember { localDisplayName = c } = do
2022-08-27 19:56:03 +04:00
memberConnectedChatItem gInfo m
2022-01-26 16:18:27 +04:00
toView $ CRConnectedToGroupMember gInfo m
2022-01-27 22:01:15 +00:00
let g = groupName' gInfo
2022-01-26 16:18:27 +04:00
setActive $ ActiveG g
showToast ( " # " <> g ) $ " member " <> c <> " is connected "
2021-07-24 10:26:28 +01:00
2022-08-27 19:56:03 +04:00
probeMatchingContacts :: Contact -> Bool -> m ()
probeMatchingContacts ct connectedIncognito = do
2021-07-27 08:08:05 +01:00
gVar <- asks idsDrg
2022-06-18 20:06:13 +01:00
( probe , probeId ) <- withStore $ \ db -> createSentProbe db gVar userId ct
2022-02-14 18:49:42 +04:00
void . sendDirectContactMessage ct $ XInfoProbe probe
2022-08-27 19:56:03 +04:00
if connectedIncognito
2022-08-30 12:49:07 +01:00
then withStore' $ \ db -> deleteSentProbe db userId probeId
2022-08-27 19:56:03 +04:00
else do
cs <- withStore' $ \ db -> getMatchingContacts db userId ct
let probeHash = ProbeHash $ C . sha256Hash ( unProbe probe )
forM_ cs $ \ c -> sendProbeHash c probeHash probeId ` catchError ` const ( pure () )
2021-07-27 08:08:05 +01:00
where
2022-01-24 16:07:17 +00:00
sendProbeHash :: Contact -> ProbeHash -> Int64 -> m ()
2021-07-27 08:08:05 +01:00
sendProbeHash c probeHash probeId = do
2022-02-14 18:49:42 +04:00
void . sendDirectContactMessage c $ XInfoProbeCheck probeHash
2022-06-18 20:06:13 +01:00
withStore' $ \ db -> createSentProbeHash db userId probeId c
2021-07-27 08:08:05 +01:00
2021-07-24 10:26:28 +01:00
messageWarning :: Text -> m ()
2022-01-24 16:07:17 +00:00
messageWarning = toView . CRMessageError " warning "
2021-07-24 10:26:28 +01:00
messageError :: Text -> m ()
2022-01-24 16:07:17 +00:00
messageError = toView . CRMessageError " error "
2021-07-24 10:26:28 +01:00
2022-03-16 13:20:47 +00:00
newContentMessage :: Contact -> MsgContainer -> RcvMessage -> MsgMeta -> m ()
2022-09-05 15:23:38 +01:00
newContentMessage ct @ Contact { localDisplayName = c , chatSettings } mc msg msgMeta = do
2022-05-28 19:13:07 +01:00
checkIntegrityCreateItem ( CDDirectRcv ct ) msgMeta
2022-04-10 13:30:58 +04:00
let ( ExtMsgContent content fileInvitation_ ) = mcExtMsgContent mc
2022-10-14 13:06:33 +01:00
ciFile_ <- processFileInvitation fileInvitation_ $ \ db -> createRcvFileTransfer db userId ct
2022-04-10 13:30:58 +04:00
ci @ ChatItem { formattedText } <- saveRcvChatItem user ( CDDirectRcv ct ) msg msgMeta ( CIRcvMsgContent content ) ciFile_
2022-01-26 16:18:27 +04:00
toView . CRNewChatItem $ AChatItem SCTDirect SMDRcv ( DirectChat ct ) ci
2022-09-05 15:23:38 +01:00
when ( enableNtfs chatSettings ) $ showMsgToast ( c <> " > " ) content formattedText
2022-01-11 08:50:44 +00:00
setActive $ ActiveC c
2022-10-14 13:06:33 +01:00
processFileInvitation :: Maybe FileInvitation -> ( DB . Connection -> FileInvitation -> Maybe InlineFileMode -> Integer -> IO RcvFileTransfer ) -> m ( Maybe ( CIFile 'MDRcv ) )
processFileInvitation fInv_ createRcvFT = forM fInv_ $ \ fInv @ FileInvitation { fileName , fileSize } -> do
chSize <- asks $ fileChunkSize . config
inline <- receiveInlineMode fInv chSize
ft @ RcvFileTransfer { fileId } <- withStore' $ \ db -> createRcvFT db fInv inline chSize
( filePath , fileStatus ) <- case inline of
Just IFMSent -> do
fPath <- getRcvFilePath fileId Nothing fileName
withStore' $ \ db -> startRcvInlineFT db user ft fPath
pure ( Just fPath , CIFSRcvAccepted )
_ -> pure ( Nothing , CIFSRcvInvitation )
pure CIFile { fileId , fileName , fileSize , filePath , fileStatus }
2022-04-10 13:30:58 +04:00
2022-03-23 11:37:51 +00:00
messageUpdate :: Contact -> SharedMsgId -> MsgContent -> RcvMessage -> MsgMeta -> m ()
2022-05-17 11:22:09 +04:00
messageUpdate ct @ Contact { contactId , localDisplayName = c } sharedMsgId mc msg @ RcvMessage { msgId } msgMeta = do
2022-05-28 19:13:07 +01:00
checkIntegrityCreateItem ( CDDirectRcv ct ) msgMeta
2022-05-17 11:22:09 +04:00
updateRcvChatItem ` catchError ` \ e ->
case e of
( ChatErrorStore ( SEChatItemSharedMsgIdNotFound _ ) ) -> do
-- This patches initial sharedMsgId into chat item when locally deleted chat item
-- received an update from the sender, so that it can be referenced later (e.g. by broadcast delete).
-- Chat item and update message which created it will have different sharedMsgId in this case...
2022-09-05 15:23:38 +01:00
ci <- saveRcvChatItem' user ( CDDirectRcv ct ) msg ( Just sharedMsgId ) msgMeta ( CIRcvMsgContent mc ) Nothing
2022-05-17 11:22:09 +04:00
toView . CRChatItemUpdated $ AChatItem SCTDirect SMDRcv ( DirectChat ct ) ci
setActive $ ActiveC c
_ -> throwError e
where
updateRcvChatItem = do
2022-06-18 20:06:13 +01:00
CChatItem msgDir ChatItem { meta = CIMeta { itemId } } <- withStore $ \ db -> getDirectChatItemBySharedMsgId db userId contactId sharedMsgId
2022-05-17 11:22:09 +04:00
case msgDir of
SMDRcv -> updateDirectChatItemView userId ct itemId ( ACIContent SMDRcv $ CIRcvMsgContent mc ) $ Just msgId
SMDSnd -> messageError " x.msg.update: contact attempted invalid message update "
2022-03-28 20:35:57 +04:00
messageDelete :: Contact -> SharedMsgId -> RcvMessage -> MsgMeta -> m ()
messageDelete ct @ Contact { contactId } sharedMsgId RcvMessage { msgId } msgMeta = do
2022-05-28 19:13:07 +01:00
checkIntegrityCreateItem ( CDDirectRcv ct ) msgMeta
2022-05-17 11:22:09 +04:00
deleteRcvChatItem ` catchError ` \ e ->
case e of
( ChatErrorStore ( SEChatItemSharedMsgIdNotFound sMsgId ) ) -> toView $ CRChatItemDeletedNotFound ct sMsgId
_ -> throwError e
where
deleteRcvChatItem = do
2022-06-18 20:06:13 +01:00
CChatItem msgDir deletedItem @ ChatItem { meta = CIMeta { itemId } } <- withStore $ \ db -> getDirectChatItemBySharedMsgId db userId contactId sharedMsgId
2022-05-17 11:22:09 +04:00
case msgDir of
SMDRcv -> do
2022-06-18 20:06:13 +01:00
toCi <- withStore $ \ db -> deleteDirectChatItemRcvBroadcast db userId ct itemId msgId
2022-05-17 11:22:09 +04:00
toView $ CRChatItemDeleted ( AChatItem SCTDirect SMDRcv ( DirectChat ct ) deletedItem ) toCi
SMDSnd -> messageError " x.msg.del: contact attempted invalid message delete "
2022-03-23 11:37:51 +00:00
2022-03-16 13:20:47 +00:00
newGroupContentMessage :: GroupInfo -> GroupMember -> MsgContainer -> RcvMessage -> MsgMeta -> m ()
2022-09-05 15:23:38 +01:00
newGroupContentMessage gInfo @ GroupInfo { chatSettings } m @ GroupMember { localDisplayName = c } mc msg msgMeta = do
2022-10-14 13:06:33 +01:00
let ( ExtMsgContent content fInv_ ) = mcExtMsgContent mc
ciFile_ <- processFileInvitation fInv_ $ \ db -> createRcvGroupFileTransfer db userId m
2022-04-10 13:30:58 +04:00
ci @ ChatItem { formattedText } <- saveRcvChatItem user ( CDGroupRcv gInfo m ) msg msgMeta ( CIRcvMsgContent content ) ciFile_
2022-05-28 19:13:07 +01:00
groupMsgToView gInfo m ci msgMeta
2022-01-27 22:01:15 +00:00
let g = groupName' gInfo
2022-09-05 15:23:38 +01:00
when ( enableNtfs chatSettings ) $ showMsgToast ( " # " <> g <> " " <> c <> " > " ) content formattedText
2022-01-26 16:18:27 +04:00
setActive $ ActiveG g
2021-07-07 22:46:38 +01:00
2022-10-01 14:31:21 +04:00
groupMessageUpdate :: GroupInfo -> GroupMember -> SharedMsgId -> MsgContent -> RcvMessage -> MsgMeta -> m ()
groupMessageUpdate gInfo @ GroupInfo { groupId , localDisplayName = g } m @ GroupMember { groupMemberId , memberId } sharedMsgId mc msg @ RcvMessage { msgId } msgMeta =
updateRcvChatItem ` catchError ` \ e ->
case e of
( ChatErrorStore ( SEChatItemSharedMsgIdNotFound _ ) ) -> do
-- This patches initial sharedMsgId into chat item when locally deleted chat item
-- received an update from the sender, so that it can be referenced later (e.g. by broadcast delete).
-- Chat item and update message which created it will have different sharedMsgId in this case...
ci <- saveRcvChatItem' user ( CDGroupRcv gInfo m ) msg ( Just sharedMsgId ) msgMeta ( CIRcvMsgContent mc ) Nothing
toView . CRChatItemUpdated $ AChatItem SCTGroup SMDRcv ( GroupChat gInfo ) ci
setActive $ ActiveG g
_ -> throwError e
where
updateRcvChatItem = do
CChatItem msgDir ChatItem { chatDir , meta = CIMeta { itemId } } <- withStore $ \ db -> getGroupChatItemBySharedMsgId db user groupId groupMemberId sharedMsgId
case ( msgDir , chatDir ) of
( SMDRcv , CIGroupRcv m' ) ->
if sameMemberId memberId m'
then do
updCi <- withStore $ \ db -> updateGroupChatItem db user groupId itemId ( CIRcvMsgContent mc ) msgId
toView . CRChatItemUpdated $ AChatItem SCTGroup SMDRcv ( GroupChat gInfo ) updCi
setActive $ ActiveG g
else messageError " x.msg.update: group member attempted to update a message of another member " -- shouldn't happen now that query includes group member id
( SMDSnd , _ ) -> messageError " x.msg.update: group member attempted invalid message update "
2022-03-28 20:35:57 +04:00
groupMessageDelete :: GroupInfo -> GroupMember -> SharedMsgId -> RcvMessage -> m ()
2022-10-01 14:31:21 +04:00
groupMessageDelete gInfo @ GroupInfo { groupId } GroupMember { groupMemberId , memberId } sharedMsgId RcvMessage { msgId } = do
CChatItem msgDir deletedItem @ ChatItem { chatDir , meta = CIMeta { itemId } } <- withStore $ \ db -> getGroupChatItemBySharedMsgId db user groupId groupMemberId sharedMsgId
2022-03-28 20:35:57 +04:00
case ( msgDir , chatDir ) of
( SMDRcv , CIGroupRcv m ) ->
if sameMemberId memberId m
then do
2022-06-18 20:06:13 +01:00
toCi <- withStore $ \ db -> deleteGroupChatItemRcvBroadcast db user gInfo itemId msgId
2022-03-28 20:35:57 +04:00
toView $ CRChatItemDeleted ( AChatItem SCTGroup SMDRcv ( GroupChat gInfo ) deletedItem ) toCi
2022-10-01 14:31:21 +04:00
else messageError " x.msg.del: group member attempted to delete a message of another member " -- shouldn't happen now that query includes group member id
2022-03-28 20:35:57 +04:00
( SMDSnd , _ ) -> messageError " x.msg.del: group member attempted invalid message delete "
2022-03-23 11:37:51 +00:00
2022-04-10 13:30:58 +04:00
-- TODO remove once XFile is discontinued
processFileInvitation' :: Contact -> FileInvitation -> RcvMessage -> MsgMeta -> m ()
processFileInvitation' ct @ Contact { localDisplayName = c } fInv @ FileInvitation { fileName , fileSize } msg msgMeta = do
2022-05-28 19:13:07 +01:00
checkIntegrityCreateItem ( CDDirectRcv ct ) msgMeta
2021-09-04 07:32:56 +01:00
chSize <- asks $ fileChunkSize . config
2022-10-14 13:06:33 +01:00
inline <- receiveInlineMode fInv chSize
RcvFileTransfer { fileId } <- withStore' $ \ db -> createRcvFileTransfer db userId ct fInv inline chSize
2022-04-10 13:30:58 +04:00
let ciFile = Just $ CIFile { fileId , fileName , fileSize , filePath = Nothing , fileStatus = CIFSRcvInvitation }
2022-04-30 19:18:46 +04:00
ci <- saveRcvChatItem user ( CDDirectRcv ct ) msg msgMeta ( CIRcvMsgContent $ MCFile " " ) ciFile
2022-01-26 16:18:27 +04:00
toView . CRNewChatItem $ AChatItem SCTDirect SMDRcv ( DirectChat ct ) ci
2022-01-12 06:55:04 +00:00
showToast ( c <> " > " ) " wants to send a file "
2021-09-04 07:32:56 +01:00
setActive $ ActiveC c
2022-04-10 13:30:58 +04:00
-- TODO remove once XFile is discontinued
processGroupFileInvitation' :: GroupInfo -> GroupMember -> FileInvitation -> RcvMessage -> MsgMeta -> m ()
processGroupFileInvitation' gInfo m @ GroupMember { localDisplayName = c } fInv @ FileInvitation { fileName , fileSize } msg msgMeta = do
2021-09-05 14:08:29 +01:00
chSize <- asks $ fileChunkSize . config
2022-10-14 13:06:33 +01:00
inline <- receiveInlineMode fInv chSize
RcvFileTransfer { fileId } <- withStore' $ \ db -> createRcvGroupFileTransfer db userId m fInv inline chSize
2022-04-10 13:30:58 +04:00
let ciFile = Just $ CIFile { fileId , fileName , fileSize , filePath = Nothing , fileStatus = CIFSRcvInvitation }
2022-04-30 19:18:46 +04:00
ci <- saveRcvChatItem user ( CDGroupRcv gInfo m ) msg msgMeta ( CIRcvMsgContent $ MCFile " " ) ciFile
2022-05-28 19:13:07 +01:00
groupMsgToView gInfo m ci msgMeta
2022-01-27 22:01:15 +00:00
let g = groupName' gInfo
2022-01-26 16:18:27 +04:00
showToast ( " # " <> g <> " " <> c <> " > " ) " wants to send a file "
setActive $ ActiveG g
2021-09-05 14:08:29 +01:00
2022-10-14 13:06:33 +01:00
receiveInlineMode :: FileInvitation -> Integer -> m ( Maybe InlineFileMode )
receiveInlineMode FileInvitation { fileSize , fileInline } chSize = case fileInline of
inline @ ( Just _ ) -> do
rcvChunks <- asks $ receiveChunks . inlineFiles . config
pure $ if fileSize <= rcvChunks * chSize then inline else Nothing
_ -> pure Nothing
2022-05-11 16:18:28 +04:00
xFileCancel :: Contact -> SharedMsgId -> MsgMeta -> m ()
2022-05-28 19:13:07 +01:00
xFileCancel ct @ Contact { contactId } sharedMsgId msgMeta = do
checkIntegrityCreateItem ( CDDirectRcv ct ) msgMeta
2022-06-18 20:06:13 +01:00
fileId <- withStore $ \ db -> getFileIdBySharedMsgId db userId contactId sharedMsgId
ft @ RcvFileTransfer { cancelled } <- withStore ( \ db -> getRcvFileTransfer db user fileId )
2022-05-11 16:18:28 +04:00
unless cancelled $ do
cancelRcvFileTransfer user ft
toView $ CRRcvFileSndCancelled ft
2022-10-14 13:06:33 +01:00
xFileAcptInv :: Contact -> SharedMsgId -> Maybe ConnReqInvitation -> String -> MsgMeta -> m ()
xFileAcptInv ct sharedMsgId fileConnReq_ fName msgMeta = do
2022-09-20 14:46:30 +01:00
checkIntegrityCreateItem ( CDDirectRcv ct ) msgMeta
fileId <- withStore $ \ db -> getDirectFileIdBySharedMsgId db user ct sharedMsgId
2022-10-14 13:06:33 +01:00
ft @ FileTransferMeta { fileName , fileSize , fileInline , cancelled } <- withStore ( \ db -> getFileTransferMeta db user fileId )
2022-09-20 14:46:30 +01:00
-- [async agent commands] no continuation needed, but command should be asynchronous for stability
if fName == fileName
2022-10-14 13:06:33 +01:00
then unless cancelled $ case fileConnReq_ of
-- receiving via a separate connection
Just fileConnReq -> do
connIds <- joinAgentConnectionAsync user True fileConnReq $ directMessage XOk
withStore' $ \ db -> createSndDirectFTConnection db user fileId connIds
-- receiving inline
_ -> do
event <- withStore $ \ db -> do
ci <- updateDirectCIFileStatus db user fileId CIFSSndTransfer
sft <- liftIO $ createSndDirectInlineFT db ct ft
pure $ CRSndFileStart ci sft
toView event
ifM
( allowSendInline fileSize fileInline )
( sendDirectFileInline ct ft sharedMsgId )
( messageError " x.file.acpt.inv: fileSize is bigger than allowed to send inline " )
2022-09-20 14:46:30 +01:00
else messageError " x.file.acpt.inv: fileName is different from expected "
2022-10-14 13:06:33 +01:00
checkSndInlineFTComplete :: Connection -> AgentMsgId -> m ()
checkSndInlineFTComplete conn agentMsgId = do
ft_ <- withStore' $ \ db -> getSndInlineFTViaMsgDelivery db user conn agentMsgId
forM_ ft_ $ \ ft @ SndFileTransfer { fileId } -> do
ci <- withStore $ \ db -> do
liftIO $ updateSndFileStatus db ft FSComplete
liftIO $ deleteSndFileChunks db ft
updateDirectCIFileStatus db user fileId CIFSSndComplete
toView $ CRSndFileComplete ci ft
allowSendInline :: Integer -> Maybe InlineFileMode -> m Bool
allowSendInline fileSize = \ case
Just IFMOffer -> do
ChatConfig { fileChunkSize , inlineFiles } <- asks config
pure $ fileSize <= fileChunkSize * offerChunks inlineFiles
_ -> pure False
bFileChunk :: Contact -> SharedMsgId -> FileChunk -> MsgMeta -> m ()
bFileChunk ct sharedMsgId chunk meta = do
ft <- withStore $ \ db -> getDirectFileIdBySharedMsgId db user ct sharedMsgId >>= getRcvFileTransfer db user
receiveInlineChunk ft chunk meta
bFileChunkGroup :: GroupInfo -> SharedMsgId -> FileChunk -> MsgMeta -> m ()
bFileChunkGroup GroupInfo { groupId } sharedMsgId chunk meta = do
ft <- withStore $ \ db -> getGroupFileIdBySharedMsgId db userId groupId sharedMsgId >>= getRcvFileTransfer db user
receiveInlineChunk ft chunk meta
receiveInlineChunk :: RcvFileTransfer -> FileChunk -> MsgMeta -> m ()
receiveInlineChunk ft chunk meta = do
case chunk of
FileChunk { chunkNo } -> when ( chunkNo == 1 ) $ startReceivingFile ft
_ -> pure ()
receiveFileChunk ft Nothing meta chunk
2022-05-11 16:18:28 +04:00
xFileCancelGroup :: GroupInfo -> GroupMember -> SharedMsgId -> MsgMeta -> m ()
2022-10-01 14:31:21 +04:00
xFileCancelGroup g @ GroupInfo { groupId } mem @ GroupMember { groupMemberId , memberId } sharedMsgId msgMeta = do
2022-05-28 19:13:07 +01:00
checkIntegrityCreateItem ( CDGroupRcv g mem ) msgMeta
2022-06-18 20:06:13 +01:00
fileId <- withStore $ \ db -> getGroupFileIdBySharedMsgId db userId groupId sharedMsgId
2022-10-01 14:31:21 +04:00
CChatItem msgDir ChatItem { chatDir } <- withStore $ \ db -> getGroupChatItemBySharedMsgId db user groupId groupMemberId sharedMsgId
2022-05-11 16:18:28 +04:00
case ( msgDir , chatDir ) of
( SMDRcv , CIGroupRcv m ) -> do
if sameMemberId memberId m
then do
2022-06-18 20:06:13 +01:00
ft @ RcvFileTransfer { cancelled } <- withStore ( \ db -> getRcvFileTransfer db user fileId )
2022-05-11 16:18:28 +04:00
unless cancelled $ do
cancelRcvFileTransfer user ft
toView $ CRRcvFileSndCancelled ft
2022-10-01 14:31:21 +04:00
else messageError " x.file.cancel: group member attempted to cancel file of another member " -- shouldn't happen now that query includes group member id
2022-05-11 16:18:28 +04:00
( SMDSnd , _ ) -> messageError " x.file.cancel: group member attempted invalid file cancel "
2022-04-05 10:01:08 +04:00
2022-10-14 13:06:33 +01:00
xFileAcptInvGroup :: GroupInfo -> GroupMember -> SharedMsgId -> Maybe ConnReqInvitation -> String -> MsgMeta -> m ()
xFileAcptInvGroup g @ GroupInfo { groupId } m @ GroupMember { activeConn } sharedMsgId fileConnReq_ fName msgMeta = do
2022-05-28 19:13:07 +01:00
checkIntegrityCreateItem ( CDGroupRcv g m ) msgMeta
2022-06-18 20:06:13 +01:00
fileId <- withStore $ \ db -> getGroupFileIdBySharedMsgId db userId groupId sharedMsgId
2022-10-14 13:06:33 +01:00
-- TODO check that it's not already accpeted
ft @ FileTransferMeta { fileName , fileSize , fileInline , cancelled } <- withStore ( \ db -> getFileTransferMeta db user fileId )
2022-09-20 14:46:30 +01:00
if fName == fileName
2022-10-14 13:06:33 +01:00
then unless cancelled $ case ( fileConnReq_ , activeConn ) of
( Just fileConnReq , _ ) -> do
-- receiving via a separate connection
-- [async agent commands] no continuation needed, but command should be asynchronous for stability
connIds <- joinAgentConnectionAsync user True fileConnReq $ directMessage XOk
withStore' $ \ db -> createSndGroupFileTransferConnection db user fileId connIds m
( _ , Just conn ) -> do
-- receiving inline
event <- withStore $ \ db -> do
ci <- updateDirectCIFileStatus db user fileId CIFSSndTransfer
sft <- liftIO $ createSndGroupInlineFT db m conn ft
pure $ CRSndFileStart ci sft
toView event
ifM
( allowSendInline fileSize fileInline )
( sendMemberFileInline m conn ft sharedMsgId )
( messageError " x.file.acpt.inv: fileSize is bigger than allowed to send inline " )
_ -> messageError " x.file.acpt.inv: member connection is not active "
2022-09-20 14:46:30 +01:00
else messageError " x.file.acpt.inv: fileName is different from expected "
2022-04-05 10:01:08 +04:00
2022-05-28 19:13:07 +01:00
groupMsgToView :: GroupInfo -> GroupMember -> ChatItem 'CTGroup 'MDRcv -> MsgMeta -> m ()
groupMsgToView gInfo m ci msgMeta = do
checkIntegrityCreateItem ( CDGroupRcv gInfo m ) msgMeta
2022-05-03 10:22:35 +01:00
toView . CRNewChatItem $ AChatItem SCTGroup SMDRcv ( GroupChat gInfo ) ci
2022-02-22 14:05:45 +00:00
2022-07-14 22:04:23 +04:00
processGroupInvitation :: Contact -> GroupInvitation -> RcvMessage -> MsgMeta -> m ()
2022-08-27 19:56:03 +04:00
processGroupInvitation ct @ Contact { localDisplayName = c , activeConn = Connection { customUserProfileId } } inv @ GroupInvitation { fromMember = ( MemberIdRole fromMemId fromRole ) , invitedMember = ( MemberIdRole memId memRole ) } msg msgMeta = do
2022-07-14 22:04:23 +04:00
checkIntegrityCreateItem ( CDDirectRcv ct ) msgMeta
2022-10-01 20:30:47 +01:00
when ( fromRole < GRMember || fromRole < memRole ) $ throwChatError ( CEGroupContactRole c )
2022-01-26 21:20:08 +00:00
when ( fromMemId == memId ) $ throwChatError CEGroupDuplicateMemberId
2022-08-27 19:56:03 +04:00
-- [incognito] if direct connection with host is incognito, create membership using the same incognito profile
gInfo @ GroupInfo { groupId , localDisplayName , groupProfile , membership = GroupMember { groupMemberId } } <- withStore $ \ db -> createGroupInvitation db user ct inv customUserProfileId
let content = CIRcvGroupInvitation ( CIGroupInvitation { groupId , groupMemberId , localDisplayName , groupProfile , status = CIGISPending } ) memRole
2022-07-14 22:04:23 +04:00
ci <- saveRcvChatItem user ( CDDirectRcv ct ) msg msgMeta content Nothing
2022-07-15 17:49:29 +04:00
withStore' $ \ db -> setGroupInvitationChatItemId db user groupId ( chatItemId' ci )
2022-07-14 22:04:23 +04:00
toView . CRNewChatItem $ AChatItem SCTDirect SMDRcv ( DirectChat ct ) ci
2022-08-27 19:56:03 +04:00
toView $ CRReceivedGroupInvitation gInfo ct memRole
2022-07-14 22:04:23 +04:00
showToast ( " # " <> localDisplayName <> " " <> c <> " > " ) " invited you to join the group "
2021-07-12 19:00:03 +01:00
2022-05-28 19:13:07 +01:00
checkIntegrityCreateItem :: forall c . ChatTypeI c => ChatDirection c 'MDRcv -> MsgMeta -> m ()
checkIntegrityCreateItem cd MsgMeta { integrity , broker = ( _ , brokerTs ) } = case integrity of
2022-02-02 11:43:52 +00:00
MsgOk -> pure ()
2022-05-28 19:13:07 +01:00
MsgError e -> case e of
MsgSkipped { } -> createIntegrityErrorItem e
_ -> toView $ CRMsgIntegrityError e
where
createIntegrityErrorItem e = do
createdAt <- liftIO getCurrentTime
let content = CIRcvIntegrityError e
2022-06-18 20:06:13 +01:00
ciId <- withStore' $ \ db -> createNewChatItemNoMsg db user cd content brokerTs createdAt
2022-05-28 19:13:07 +01:00
ci <- liftIO $ mkChatItem cd ciId content Nothing Nothing Nothing brokerTs createdAt
toView $ CRNewChatItem $ AChatItem ( chatTypeI @ c ) SMDRcv ( toChatInfo cd ) ci
2022-02-02 11:43:52 +00:00
2021-08-22 15:56:36 +01:00
xInfo :: Contact -> Profile -> m ()
2022-08-18 11:35:31 +04:00
xInfo c @ Contact { profile = p } p' = unless ( fromLocalProfile p == p' ) $ do
2022-06-18 20:06:13 +01:00
c' <- withStore $ \ db -> updateContactProfile db userId c p'
2022-01-24 16:07:17 +00:00
toView $ CRContactUpdated c c'
2021-08-22 15:56:36 +01:00
2022-01-11 08:50:44 +00:00
xInfoProbe :: Contact -> Probe -> m ()
2022-08-18 11:35:31 +04:00
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
2021-07-27 08:08:05 +01:00
2022-01-11 08:50:44 +00:00
xInfoProbeCheck :: Contact -> ProbeHash -> m ()
2022-08-18 11:35:31 +04:00
xInfoProbeCheck c1 probeHash =
-- [incognito] unless connected incognito
unless ( contactConnIncognito c1 ) $ do
r <- withStore' $ \ db -> matchReceivedProbeHash db userId c1 probeHash
forM_ r . uncurry $ probeMatch c1
2021-07-27 08:08:05 +01:00
2022-01-11 08:50:44 +00:00
probeMatch :: Contact -> Contact -> Probe -> m ()
2021-07-27 08:08:05 +01:00
probeMatch c1 @ Contact { profile = p1 } c2 @ Contact { profile = p2 } probe =
2022-08-18 11:35:31 +04:00
when ( fromLocalProfile p1 == fromLocalProfile p2 ) $ do
2022-02-14 18:49:42 +04:00
void . sendDirectContactMessage c1 $ XInfoProbeOk probe
2021-07-27 08:08:05 +01:00
mergeContacts c1 c2
2022-01-11 08:50:44 +00:00
xInfoProbeOk :: Contact -> Probe -> m ()
2021-07-27 08:08:05 +01:00
xInfoProbeOk c1 probe = do
2022-06-18 20:06:13 +01:00
r <- withStore' $ \ db -> matchSentProbe db userId c1 probe
2021-07-27 08:08:05 +01:00
forM_ r $ \ c2 -> mergeContacts c1 c2
2022-05-03 10:22:35 +01:00
-- to party accepting call
xCallInv :: Contact -> CallId -> CallInvitation -> RcvMessage -> MsgMeta -> m ()
2022-05-18 18:46:45 +01:00
xCallInv ct @ Contact { contactId } callId CallInvitation { callType , callDhPubKey } msg msgMeta = do
2022-05-28 19:13:07 +01:00
checkIntegrityCreateItem ( CDDirectRcv ct ) msgMeta
2022-05-18 07:01:32 +01:00
dhKeyPair <- if encryptedCall callType then Just <$> liftIO C . generateKeyPair' else pure Nothing
2022-05-04 13:31:00 +01:00
ci <- saveCallItem CISCallPending
let sharedKey = C . Key . C . dhBytes' <$> ( C . dh' <$> callDhPubKey <*> ( snd <$> dhKeyPair ) )
callState = CallInvitationReceived { peerCallType = callType , localDhPubKey = fst <$> dhKeyPair , sharedKey }
2022-07-04 11:15:25 +01:00
call' = Call { contactId , callId , chatItemId = chatItemId' ci , callState , callTs = chatItemTs' ci }
2022-05-04 13:31:00 +01:00
calls <- asks currentCalls
2022-07-04 11:15:25 +01:00
-- theoretically, the new call invitation for the current contact can mark the in-progress call as ended
2022-05-04 13:31:00 +01:00
-- (and replace it in ChatController)
-- practically, this should not happen
2022-07-04 11:15:25 +01:00
withStore' $ \ db -> createCall db user call' $ chatItemTs' ci
2022-05-04 13:31:00 +01:00
call_ <- atomically ( TM . lookupInsert contactId call' calls )
2022-05-18 18:46:45 +01:00
forM_ call_ $ \ call -> updateCallItemStatus userId ct call WCSDisconnected Nothing
2022-07-04 11:15:25 +01:00
toView . CRCallInvitation $ RcvCallInvitation { contact = ct , callType , sharedKey , callTs = chatItemTs' ci }
2022-05-03 10:22:35 +01:00
toView . CRNewChatItem $ AChatItem SCTDirect SMDRcv ( DirectChat ct ) ci
where
saveCallItem status = saveRcvChatItem user ( CDDirectRcv ct ) msg msgMeta ( CIRcvCall status 0 ) Nothing
-- to party initiating call
xCallOffer :: Contact -> CallId -> CallOffer -> RcvMessage -> MsgMeta -> m ()
xCallOffer ct callId CallOffer { callType , rtcSession , callDhPubKey } msg msgMeta = do
msgCurrentCall ct callId " x.call.offer " msg msgMeta $
\ call -> case callState call of
CallInvitationSent { localCallType , localDhPrivKey } -> do
let sharedKey = C . Key . C . dhBytes' <$> ( C . dh' <$> callDhPubKey <*> localDhPrivKey )
callState' = CallOfferReceived { localCallType , peerCallType = callType , peerCallSession = rtcSession , sharedKey }
2022-05-18 07:01:32 +01:00
askConfirmation = encryptedCall localCallType && not ( encryptedCall callType )
toView CRCallOffer { contact = ct , callType , offer = rtcSession , sharedKey , askConfirmation }
2022-05-03 10:22:35 +01:00
pure ( Just call { callState = callState' } , Just . ACIContent SMDSnd $ CISndCall CISCallAccepted 0 )
_ -> do
msgCallStateError " x.call.offer " call
pure ( Just call , Nothing )
-- to party accepting call
xCallAnswer :: Contact -> CallId -> CallAnswer -> RcvMessage -> MsgMeta -> m ()
xCallAnswer ct callId CallAnswer { rtcSession } msg msgMeta = do
msgCurrentCall ct callId " x.call.answer " msg msgMeta $
\ call -> case callState call of
CallOfferSent { localCallType , peerCallType , localCallSession , sharedKey } -> do
let callState' = CallNegotiated { localCallType , peerCallType , localCallSession , peerCallSession = rtcSession , sharedKey }
toView $ CRCallAnswer ct rtcSession
pure ( Just call { callState = callState' } , Just . ACIContent SMDRcv $ CIRcvCall CISCallNegotiated 0 )
_ -> do
msgCallStateError " x.call.answer " call
pure ( Just call , Nothing )
-- to any call party
xCallExtra :: Contact -> CallId -> CallExtraInfo -> RcvMessage -> MsgMeta -> m ()
xCallExtra ct callId CallExtraInfo { rtcExtraInfo } msg msgMeta = do
msgCurrentCall ct callId " x.call.extra " msg msgMeta $
\ call -> case callState call of
2022-05-07 06:40:46 +01:00
CallOfferReceived { localCallType , peerCallType , peerCallSession , sharedKey } -> do
-- TODO update the list of ice servers in peerCallSession
let callState' = CallOfferReceived { localCallType , peerCallType , peerCallSession , sharedKey }
toView $ CRCallExtraInfo ct rtcExtraInfo
pure ( Just call { callState = callState' } , Nothing )
2022-05-03 10:22:35 +01:00
CallNegotiated { localCallType , peerCallType , localCallSession , peerCallSession , sharedKey } -> do
2022-05-07 06:40:46 +01:00
-- TODO update the list of ice servers in peerCallSession
2022-05-03 10:22:35 +01:00
let callState' = CallNegotiated { localCallType , peerCallType , localCallSession , peerCallSession , sharedKey }
toView $ CRCallExtraInfo ct rtcExtraInfo
pure ( Just call { callState = callState' } , Nothing )
_ -> do
2022-05-04 13:31:00 +01:00
msgCallStateError " x.call.extra " call
2022-05-03 10:22:35 +01:00
pure ( Just call , Nothing )
-- to any call party
xCallEnd :: Contact -> CallId -> RcvMessage -> MsgMeta -> m ()
2022-05-07 06:40:46 +01:00
xCallEnd ct callId msg msgMeta =
2022-05-04 13:31:00 +01:00
msgCurrentCall ct callId " x.call.end " msg msgMeta $ \ Call { chatItemId } -> do
toView $ CRCallEnded ct
2022-05-07 06:40:46 +01:00
( Nothing , ) <$> callStatusItemContent userId ct chatItemId WCSDisconnected
2022-05-03 10:22:35 +01:00
msgCurrentCall :: Contact -> CallId -> Text -> RcvMessage -> MsgMeta -> ( Call -> m ( Maybe Call , Maybe ACIContent ) ) -> m ()
msgCurrentCall ct @ Contact { contactId = ctId' } callId' eventName RcvMessage { msgId } msgMeta action = do
2022-05-28 19:13:07 +01:00
checkIntegrityCreateItem ( CDDirectRcv ct ) msgMeta
2022-05-04 13:31:00 +01:00
calls <- asks currentCalls
atomically ( TM . lookup ctId' calls ) >>= \ case
2022-05-03 10:22:35 +01:00
Nothing -> messageError $ eventName <> " : no current call "
Just call @ Call { contactId , callId , chatItemId }
| contactId /= ctId' || callId /= callId' -> messageError $ eventName <> " : wrong contact or callId "
| otherwise -> do
2022-10-14 13:06:33 +01:00
( call_ , aciContent_ ) <- action call
case call_ of
Just call' -> do
unless ( isRcvInvitation call' ) $ withStore' $ \ db -> deleteCalls db user ctId'
atomically $ TM . insert ctId' call' calls
_ -> do
withStore' $ \ db -> deleteCalls db user ctId'
atomically $ TM . delete ctId' calls
forM_ aciContent_ $ \ aciContent ->
updateDirectChatItemView userId ct chatItemId aciContent $ Just msgId
2022-05-03 10:22:35 +01:00
msgCallStateError :: Text -> Call -> m ()
msgCallStateError eventName Call { callState } =
messageError $ eventName <> " : wrong call state " <> T . pack ( show $ callStateTag callState )
2021-07-27 08:08:05 +01:00
mergeContacts :: Contact -> Contact -> m ()
mergeContacts to from = do
2022-06-18 20:06:13 +01:00
withStore' $ \ db -> mergeContactRecords db userId to from
2022-01-24 16:07:17 +00:00
toView $ CRContactsMerged to from
2021-07-27 08:08:05 +01:00
2021-07-06 19:07:03 +01:00
saveConnInfo :: Connection -> ConnInfo -> m ()
saveConnInfo activeConn connInfo = do
2022-10-14 13:06:33 +01:00
ChatMessage { chatMsgEvent } <- parseChatMessage connInfo
2021-07-06 19:07:03 +01:00
case chatMsgEvent of
2022-02-08 13:04:17 +04:00
XInfo p -> do
2022-06-18 20:06:13 +01:00
ct <- withStore $ \ db -> createDirectContact db userId activeConn p
2022-02-08 13:04:17 +04:00
toView $ CRContactConnecting ct
2021-07-24 18:11:04 +01:00
-- TODO show/log error, other events in SMP confirmation
_ -> pure ()
2022-07-20 16:56:55 +04:00
xGrpMemNew :: GroupInfo -> GroupMember -> MemberInfo -> RcvMessage -> MsgMeta -> m ()
2022-10-01 20:30:47 +01:00
xGrpMemNew gInfo m memInfo @ ( MemberInfo memId memRole memberProfile ) msg msgMeta = do
checkHostRole m memRole
2022-06-18 20:06:13 +01:00
members <- withStore' $ \ db -> getGroupMembers db user gInfo
2022-01-26 16:18:27 +04:00
unless ( sameMemberId memId $ membership gInfo ) $
if isMember memId gInfo members
2021-07-24 18:11:04 +01:00
then messageError " x.grp.mem.new error: member already exists "
else do
2022-07-20 16:56:55 +04:00
newMember @ GroupMember { groupMemberId } <- withStore $ \ db -> createNewGroupMember db user gInfo memInfo GCPostMember GSMemAnnounced
ci <- saveRcvChatItem user ( CDGroupRcv gInfo m ) msg msgMeta ( CIRcvGroupEvent $ RGEMemberAdded groupMemberId memberProfile ) Nothing
groupMsgToView gInfo m ci msgMeta
2022-01-26 16:18:27 +04:00
toView $ CRJoinedGroupMemberConnecting gInfo m newMember
2021-07-24 18:11:04 +01:00
2022-09-14 19:45:21 +04:00
xGrpMemIntro :: GroupInfo -> GroupMember -> MemberInfo -> m ()
2022-10-01 20:30:47 +01:00
xGrpMemIntro gInfo @ GroupInfo { membership , chatSettings = ChatSettings { enableNtfs } } m @ GroupMember { memberRole , localDisplayName = c } memInfo @ ( MemberInfo memId _ _ ) = do
2021-07-24 18:11:04 +01:00
case memberCategory m of
GCHostMember -> do
2022-06-18 20:06:13 +01:00
members <- withStore' $ \ db -> getGroupMembers db user gInfo
2022-01-26 16:18:27 +04:00
if isMember memId gInfo members
2021-07-24 18:11:04 +01:00
then messageWarning " x.grp.mem.intro ignored: member already exists "
else do
2022-10-01 20:30:47 +01:00
when ( memberRole < GRMember ) $ throwChatError ( CEGroupContactRole c )
2022-09-14 19:45:21 +04:00
-- [async agent commands] commands should be asynchronous, continuation is to send XGrpMemInv - have to remember one has completed and process on second
2022-09-26 18:09:45 +01:00
groupConnIds <- createAgentConnectionAsync user enableNtfs SCMInvitation
directConnIds <- createAgentConnectionAsync user enableNtfs SCMInvitation
2022-08-27 19:56:03 +04:00
-- [incognito] direct connection with member has to be established using the same incognito profile [that was known to host and used for group membership]
let customUserProfileId = if memberIncognito membership then Just ( localProfileId $ memberProfile membership ) else Nothing
2022-09-14 19:45:21 +04:00
void $ withStore $ \ db -> createIntroReMember db user gInfo m memInfo groupConnIds directConnIds customUserProfileId
2021-07-24 18:11:04 +01:00
_ -> messageError " x.grp.mem.intro can be only sent by host member "
2022-09-14 19:45:21 +04:00
sendXGrpMemIntro :: Int64 -> ConnReqInvitation -> XGrpMemIntroCont -> m ()
sendXGrpMemIntro hostConnId directConnReq XGrpMemIntroCont { groupId , groupMemberId , memberId , groupConnReq } = do
hostConn <- withStore $ \ db -> getConnectionById db user hostConnId
let msg = XGrpMemInv memberId IntroInvitation { groupConnReq , directConnReq }
void $ sendDirectMessage hostConn msg ( GroupId groupId )
withStore' $ \ db -> updateGroupMemberStatusById db userId groupMemberId GSMemIntroInvited
2022-01-26 16:18:27 +04:00
xGrpMemInv :: GroupInfo -> GroupMember -> MemberId -> IntroInvitation -> m ()
xGrpMemInv gInfo m memId introInv = do
2021-07-24 18:11:04 +01:00
case memberCategory m of
GCInviteeMember -> do
2022-06-18 20:06:13 +01:00
members <- withStore' $ \ db -> getGroupMembers db user gInfo
2022-01-26 16:18:27 +04:00
case find ( sameMemberId memId ) members of
2022-03-28 20:35:57 +04:00
Nothing -> messageError " x.grp.mem.inv error: referenced member does not exist "
2021-07-24 18:11:04 +01:00
Just reMember -> do
2022-06-18 20:06:13 +01:00
GroupMemberIntro { introId } <- withStore $ \ db -> saveIntroInvitation db reMember m introInv
2022-02-25 21:59:35 +04:00
void $ sendXGrpMemInv gInfo reMember ( XGrpMemFwd ( memberInfo m ) introInv ) introId
2021-07-24 18:11:04 +01:00
_ -> messageError " x.grp.mem.inv can be only sent by invitee member "
2022-01-26 16:18:27 +04:00
xGrpMemFwd :: GroupInfo -> GroupMember -> MemberInfo -> IntroInvitation -> m ()
2022-10-01 20:30:47 +01:00
xGrpMemFwd gInfo @ GroupInfo { membership , chatSettings = ChatSettings { enableNtfs } } m memInfo @ ( MemberInfo memId memRole _ ) introInv @ IntroInvitation { groupConnReq , directConnReq } = do
checkHostRole m memRole
2022-06-18 20:06:13 +01:00
members <- withStore' $ \ db -> getGroupMembers db user gInfo
2022-01-26 16:18:27 +04:00
toMember <- case find ( sameMemberId memId ) members of
2021-07-24 18:11:04 +01:00
-- TODO if the missed messages are correctly sent as soon as there is connection before anything else is sent
-- the situation when member does not exist is an error
-- member receiving x.grp.mem.fwd should have also received x.grp.mem.new prior to that.
-- For now, this branch compensates for the lack of delayed message delivery.
2022-06-18 20:06:13 +01:00
Nothing -> withStore $ \ db -> createNewGroupMember db user gInfo memInfo GCPostMember GSMemAnnounced
2021-07-24 18:11:04 +01:00
Just m' -> pure m'
2022-06-18 20:06:13 +01:00
withStore' $ \ db -> saveMemberInvitation db toMember introInv
2022-08-18 11:35:31 +04:00
-- [incognito] send membership incognito profile, create direct connection as incognito
let msg = XGrpMemInfo ( memberId ( membership :: GroupMember ) ) ( fromLocalProfile $ memberProfile membership )
2022-09-14 19:45:21 +04:00
-- [async agent commands] no continuation needed, but commands should be asynchronous for stability
2022-09-26 18:09:45 +01:00
groupConnIds <- joinAgentConnectionAsync user enableNtfs groupConnReq $ directMessage msg
directConnIds <- joinAgentConnectionAsync user enableNtfs directConnReq $ directMessage msg
2022-08-27 19:56:03 +04:00
let customUserProfileId = if memberIncognito membership then Just ( localProfileId $ memberProfile membership ) else Nothing
2022-09-14 19:45:21 +04:00
withStore' $ \ db -> createIntroToMemberContact db user m toMember groupConnIds directConnIds customUserProfileId
2021-07-06 19:07:03 +01:00
2022-10-03 09:00:47 +01:00
xGrpMemRole :: GroupInfo -> GroupMember -> MemberId -> GroupMemberRole -> RcvMessage -> MsgMeta -> m ()
xGrpMemRole gInfo @ GroupInfo { membership } m @ GroupMember { memberRole = senderRole } memId memRole msg msgMeta
| memberId ( membership :: GroupMember ) == memId =
2022-10-14 13:06:33 +01:00
let gInfo' = gInfo { membership = membership { memberRole = memRole } }
in changeMemberRole gInfo' membership $ RGEUserRole memRole
2022-10-03 09:00:47 +01:00
| otherwise = do
2022-10-14 13:06:33 +01:00
members <- withStore' $ \ db -> getGroupMembers db user gInfo
case find ( sameMemberId memId ) members of
Just member -> changeMemberRole gInfo member $ RGEMemberRole ( groupMemberId' member ) ( fromLocalProfile $ memberProfile member ) memRole
_ -> messageError " x.grp.mem.role with unknown member ID "
2022-10-03 09:00:47 +01:00
where
changeMemberRole gInfo' member @ GroupMember { memberRole = fromRole } gEvent
| senderRole < GRAdmin || senderRole < fromRole = messageError " x.grp.mem.role with insufficient member permissions "
| otherwise = do
2022-10-14 13:06:33 +01:00
withStore' $ \ db -> updateGroupMemberRole db user member memRole
ci <- saveRcvChatItem user ( CDGroupRcv gInfo m ) msg msgMeta ( CIRcvGroupEvent gEvent ) Nothing
groupMsgToView gInfo m ci msgMeta
toView CRMemberRole { groupInfo = gInfo' , byMember = m , member = member { memberRole = memRole } , fromRole , toRole = memRole }
2022-10-03 09:00:47 +01:00
2022-10-01 20:30:47 +01:00
checkHostRole :: GroupMember -> GroupMemberRole -> m ()
checkHostRole GroupMember { memberRole , localDisplayName } memRole =
when ( memberRole < GRMember || memberRole < memRole ) $ throwChatError ( CEGroupContactRole localDisplayName )
2022-07-20 16:56:55 +04:00
xGrpMemDel :: GroupInfo -> GroupMember -> MemberId -> RcvMessage -> MsgMeta -> m ()
2022-10-03 09:00:47 +01:00
xGrpMemDel gInfo @ GroupInfo { membership } m @ GroupMember { memberRole = senderRole } memId msg msgMeta = do
2022-06-18 20:06:13 +01:00
members <- withStore' $ \ db -> getGroupMembers db user gInfo
2022-01-11 08:50:44 +00:00
if memberId ( membership :: GroupMember ) == memId
2022-10-03 09:00:47 +01:00
then checkRole membership $ do
2022-10-13 17:12:22 +04:00
deleteGroupLink' user gInfo ` catchError ` \ _ -> pure ()
2022-09-30 16:18:43 +04:00
forM_ members $ deleteMemberConnection user
2022-10-03 09:00:47 +01:00
deleteMember membership RGEUserDeleted
2022-07-20 16:56:55 +04:00
toView $ CRDeletedMemberUser gInfo { membership = membership { memberStatus = GSMemRemoved } } m
2022-01-11 08:50:44 +00:00
else case find ( sameMemberId memId ) members of
2021-08-02 20:10:24 +01:00
Nothing -> messageError " x.grp.mem.del with unknown member ID "
2022-10-03 09:00:47 +01:00
Just member @ GroupMember { groupMemberId , memberProfile } ->
checkRole member $ do
deleteMemberConnection user member
deleteMember member $ RGEMemberDeleted groupMemberId ( fromLocalProfile memberProfile )
toView $ CRDeletedMember gInfo m member { memberStatus = GSMemRemoved }
where
checkRole GroupMember { memberRole } a
| senderRole < GRAdmin || senderRole < memberRole =
2022-10-14 13:06:33 +01:00
messageError " x.grp.mem.del with insufficient member permissions "
2022-10-03 09:00:47 +01:00
| otherwise = a
deleteMember member gEvent = do
withStore' $ \ db -> updateGroupMemberStatus db userId member GSMemRemoved
ci <- saveRcvChatItem user ( CDGroupRcv gInfo m ) msg msgMeta ( CIRcvGroupEvent gEvent ) Nothing
groupMsgToView gInfo m ci msgMeta
2021-08-02 20:10:24 +01:00
2022-01-11 08:50:44 +00:00
sameMemberId :: MemberId -> GroupMember -> Bool
sameMemberId memId GroupMember { memberId } = memId == memberId
2022-07-20 16:56:55 +04:00
xGrpLeave :: GroupInfo -> GroupMember -> RcvMessage -> MsgMeta -> m ()
xGrpLeave gInfo m msg msgMeta = do
2022-09-30 16:18:43 +04:00
deleteMemberConnection user m
2022-06-18 20:06:13 +01:00
withStore' $ \ db -> updateGroupMemberStatus db userId m GSMemLeft
2022-07-20 16:56:55 +04:00
ci <- saveRcvChatItem user ( CDGroupRcv gInfo m ) msg msgMeta ( CIRcvGroupEvent RGEMemberLeft ) Nothing
groupMsgToView gInfo m ci msgMeta
toView $ CRLeftMember gInfo m { memberStatus = GSMemLeft }
2021-08-02 20:10:24 +01:00
2022-07-20 16:56:55 +04:00
xGrpDel :: GroupInfo -> GroupMember -> RcvMessage -> MsgMeta -> m ()
xGrpDel gInfo @ GroupInfo { membership } m @ GroupMember { memberRole } msg msgMeta = do
2022-01-26 21:20:08 +00:00
when ( memberRole /= GROwner ) $ throwChatError CEGroupUserRole
2022-06-18 20:06:13 +01:00
ms <- withStore' $ \ db -> do
members <- getGroupMembers db user gInfo
2022-07-20 16:56:55 +04:00
updateGroupMemberStatus db userId membership GSMemGroupDeleted
2021-08-02 20:10:24 +01:00
pure members
2022-09-30 16:18:43 +04:00
forM_ ms $ deleteMemberConnection user
2022-07-21 11:01:04 +04:00
ci <- saveRcvChatItem user ( CDGroupRcv gInfo m ) msg msgMeta ( CIRcvGroupEvent RGEGroupDeleted ) Nothing
2022-07-20 16:56:55 +04:00
groupMsgToView gInfo m ci msgMeta
toView $ CRGroupDeleted gInfo { membership = membership { memberStatus = GSMemGroupDeleted } } m
2021-08-02 20:10:24 +01:00
2022-07-29 19:04:32 +01:00
xGrpInfo :: GroupInfo -> GroupMember -> GroupProfile -> RcvMessage -> MsgMeta -> m ()
xGrpInfo g m @ GroupMember { memberRole } p' msg msgMeta
| memberRole < GROwner = messageError " x.grp.info with insufficient member permissions "
| otherwise = do
2022-10-14 13:06:33 +01:00
g' <- withStore $ \ db -> updateGroupProfile db user g p'
ci <- saveRcvChatItem user ( CDGroupRcv g' m ) msg msgMeta ( CIRcvGroupEvent $ RGEGroupUpdated p' ) Nothing
groupMsgToView g' m ci msgMeta
toView . CRGroupUpdated g g' $ Just m
sendDirectFileInline :: ChatMonad m => Contact -> FileTransferMeta -> SharedMsgId -> m ()
sendDirectFileInline ct ft sharedMsgId = do
msgDeliveryId <- sendFileInline_ ft sharedMsgId $ sendDirectContactMessage ct
withStore' $ \ db -> updateSndDirectFTDelivery db ct ft msgDeliveryId
sendMemberFileInline :: ChatMonad m => GroupMember -> Connection -> FileTransferMeta -> SharedMsgId -> m ()
sendMemberFileInline m @ GroupMember { groupId } conn ft sharedMsgId = do
msgDeliveryId <- sendFileInline_ ft sharedMsgId $ \ msg -> sendDirectMessage conn msg $ GroupId groupId
withStore' $ \ db -> updateSndGroupFTDelivery db m conn ft msgDeliveryId
sendFileInline_ :: ChatMonad m => FileTransferMeta -> SharedMsgId -> ( ChatMsgEvent 'Binary -> m ( SndMessage , Int64 ) ) -> m Int64
sendFileInline_ FileTransferMeta { filePath , chunkSize } sharedMsgId sendMsg =
sendChunks 1 =<< liftIO . B . readFile =<< toFSFilePath filePath
where
sendChunks chunkNo bytes = do
let ( chunk , rest ) = B . splitAt chSize bytes
( _ , msgDeliveryId ) <- sendMsg $ BFileChunk sharedMsgId $ FileChunk chunkNo chunk
if B . null rest
then pure msgDeliveryId
else sendChunks ( chunkNo + 1 ) rest
chSize = fromIntegral chunkSize
parseChatMessage :: ChatMonad m => ByteString -> m ( ChatMessage 'Json )
parseChatMessage = liftEither . first ( ChatError . CEInvalidChatMessage ) . strDecode
2022-07-29 19:04:32 +01:00
2022-10-14 13:06:33 +01:00
parseAChatMessage :: ChatMonad m => ByteString -> m AChatMessage
parseAChatMessage = liftEither . first ( ChatError . CEInvalidChatMessage ) . strDecode
2021-12-29 23:11:55 +04:00
2022-05-05 10:37:53 +01:00
sendFileChunk :: ChatMonad m => User -> SndFileTransfer -> m ()
2022-09-30 16:18:43 +04:00
sendFileChunk user ft @ SndFileTransfer { fileId , fileStatus , connId , agentConnId } =
2021-09-04 07:32:56 +01:00
unless ( fileStatus == FSComplete || fileStatus == FSCancelled ) $
2022-06-18 20:06:13 +01:00
withStore' ( ` createSndFileChunk ` ft ) >>= \ case
2021-09-04 07:32:56 +01:00
Just chunkNo -> sendFileChunkNo ft chunkNo
Nothing -> do
2022-06-18 20:06:13 +01:00
ci <- withStore $ \ db -> do
liftIO $ updateSndFileStatus db ft FSComplete
liftIO $ deleteSndFileChunks db ft
updateDirectCIFileStatus db user fileId CIFSSndComplete
2022-05-05 10:37:53 +01:00
toView $ CRSndFileComplete ci ft
2021-09-04 07:32:56 +01:00
closeFileHandle fileId sndFiles
2022-09-30 16:18:43 +04:00
deleteAgentConnectionAsync' user connId agentConnId
2021-09-04 07:32:56 +01:00
sendFileChunkNo :: ChatMonad m => SndFileTransfer -> Integer -> m ()
2022-01-26 16:18:27 +04:00
sendFileChunkNo ft @ SndFileTransfer { agentConnId = AgentConnId acId } chunkNo = do
2022-01-11 12:41:38 +00:00
chunkBytes <- readFileChunk ft chunkNo
2022-06-07 14:14:54 +01:00
msgId <- withAgent $ \ a -> sendMessage a acId SMP . noMsgFlags $ smpEncode FileChunk { chunkNo , chunkBytes }
2022-06-18 20:06:13 +01:00
withStore' $ \ db -> updateSndFileChunkMsg db ft chunkNo msgId
2021-09-04 07:32:56 +01:00
readFileChunk :: ChatMonad m => SndFileTransfer -> Integer -> m ByteString
2022-04-15 09:36:38 +04:00
readFileChunk SndFileTransfer { fileId , filePath , chunkSize } chunkNo = do
fsFilePath <- toFSFilePath filePath
read_ fsFilePath ` E . catch ` ( throwChatError . CEFileRead filePath . ( show :: E . SomeException -> String ) )
2021-09-04 07:32:56 +01:00
where
2022-04-15 09:36:38 +04:00
read_ fsFilePath = do
h <- getFileHandle fileId fsFilePath sndFiles ReadMode
2021-09-04 07:32:56 +01:00
pos <- hTell h
let pos' = ( chunkNo - 1 ) * chunkSize
when ( pos /= pos' ) $ hSeek h AbsoluteSeek pos'
liftIO . B . hGet h $ fromInteger chunkSize
2022-01-11 12:41:38 +00:00
parseFileChunk :: ChatMonad m => ByteString -> m FileChunk
2022-10-14 13:06:33 +01:00
parseFileChunk = liftEither . first ( ChatError . CEFileRcvChunk ) . smpDecode
2021-09-04 07:32:56 +01:00
appendFileChunk :: ChatMonad m => RcvFileTransfer -> Integer -> ByteString -> m ()
appendFileChunk ft @ RcvFileTransfer { fileId , fileStatus } chunkNo chunk =
case fileStatus of
2022-05-12 17:37:09 +04:00
RFSConnected RcvFileInfo { filePath } -> append_ filePath
-- sometimes update of file transfer status to FSConnected
-- doesn't complete in time before MSG with first file chunk
RFSAccepted RcvFileInfo { filePath } -> append_ filePath
2021-09-04 07:32:56 +01:00
RFSCancelled _ -> pure ()
2022-01-26 21:20:08 +00:00
_ -> throwChatError $ CEFileInternal " receiving file transfer not in progress "
2021-09-04 07:32:56 +01:00
where
2022-05-12 17:37:09 +04:00
append_ filePath = do
fsFilePath <- toFSFilePath filePath
h <- getFileHandle fileId fsFilePath rcvFiles AppendMode
2021-09-04 07:32:56 +01:00
E . try ( liftIO $ B . hPut h chunk >> hFlush h ) >>= \ case
2022-05-12 17:37:09 +04:00
Left ( e :: E . SomeException ) -> throwChatError . CEFileWrite fsFilePath $ show e
2022-06-18 20:06:13 +01:00
Right () -> withStore' $ \ db -> updatedRcvFileChunkStored db ft chunkNo
2021-09-04 07:32:56 +01:00
getFileHandle :: ChatMonad m => Int64 -> FilePath -> ( ChatController -> TVar ( Map Int64 Handle ) ) -> IOMode -> m Handle
getFileHandle fileId filePath files ioMode = do
fs <- asks files
h_ <- M . lookup fileId <$> readTVarIO fs
maybe ( newHandle fs ) pure h_
where
newHandle fs = do
-- TODO handle errors
h <- liftIO ( openFile filePath ioMode )
atomically . modifyTVar fs $ M . insert fileId h
pure h
isFileActive :: ChatMonad m => Int64 -> ( ChatController -> TVar ( Map Int64 Handle ) ) -> m Bool
isFileActive fileId files = do
fs <- asks files
isJust . M . lookup fileId <$> readTVarIO fs
2022-05-11 16:18:28 +04:00
cancelRcvFileTransfer :: ChatMonad m => User -> RcvFileTransfer -> m ()
2022-10-14 13:06:33 +01:00
cancelRcvFileTransfer user ft @ RcvFileTransfer { fileId , fileStatus , rcvFileInline } = do
2021-09-04 07:32:56 +01:00
closeFileHandle fileId rcvFiles
2022-06-18 20:06:13 +01:00
withStore' $ \ db -> do
updateFileCancelled db user fileId CIFSRcvCancelled
updateRcvFileStatus db ft FSCancelled
deleteRcvFileChunks db ft
2022-10-14 13:06:33 +01:00
when ( isNothing rcvFileInline ) $ case fileStatus of
2022-09-30 16:18:43 +04:00
RFSAccepted RcvFileInfo { connId , agentConnId } ->
deleteAgentConnectionAsync' user connId agentConnId
RFSConnected RcvFileInfo { connId , agentConnId } ->
deleteAgentConnectionAsync' user connId agentConnId
2021-09-04 07:32:56 +01:00
_ -> pure ()
2022-05-11 16:18:28 +04:00
cancelSndFile :: ChatMonad m => User -> FileTransferMeta -> [ SndFileTransfer ] -> m ()
cancelSndFile user FileTransferMeta { fileId } fts = do
2022-06-18 20:06:13 +01:00
withStore' $ \ db -> updateFileCancelled db user fileId CIFSSndCancelled
2022-09-30 16:18:43 +04:00
forM_ fts $ \ ft' -> cancelSndFileTransfer user ft'
2022-05-11 16:18:28 +04:00
2022-09-30 16:18:43 +04:00
cancelSndFileTransfer :: ChatMonad m => User -> SndFileTransfer -> m ()
cancelSndFileTransfer user ft @ SndFileTransfer { connId , agentConnId = agentConnId @ ( AgentConnId acId ) , fileStatus } =
2021-09-04 07:32:56 +01:00
unless ( fileStatus == FSCancelled || fileStatus == FSComplete ) $ do
2022-06-18 20:06:13 +01:00
withStore' $ \ db -> do
updateSndFileStatus db ft FSCancelled
deleteSndFileChunks db ft
2022-09-30 16:18:43 +04:00
withAgent $ \ a -> void ( sendMessage a acId SMP . noMsgFlags $ smpEncode FileChunkCancel ) ` catchError ` \ _ -> pure ()
deleteAgentConnectionAsync' user connId agentConnId
2021-09-04 07:32:56 +01:00
closeFileHandle :: ChatMonad m => Int64 -> ( ChatController -> TVar ( Map Int64 Handle ) ) -> m ()
closeFileHandle fileId files = do
fs <- asks files
h_ <- atomically . stateTVar fs $ \ m -> ( M . lookup fileId m , M . delete fileId m )
mapM_ hClose h_ ` E . catch ` \ ( _ :: E . SomeException ) -> pure ()
2022-01-26 21:20:08 +00:00
throwChatError :: ChatMonad m => ChatErrorType -> m a
throwChatError = throwError . ChatError
2021-08-02 20:10:24 +01:00
2022-09-30 16:18:43 +04:00
deleteMemberConnection :: ChatMonad m => User -> GroupMember -> m ()
deleteMemberConnection user GroupMember { activeConn } = do
forM_ activeConn $ \ conn -> do
deleteAgentConnectionAsync user conn ` catchError ` \ _ -> pure ()
withStore' $ \ db -> updateConnectionStatus db conn ConnDeleted
2022-10-01 15:19:41 +01:00
-- withStore $ \db -> deleteGroupMemberConnection db userId m
2021-08-02 20:10:24 +01:00
2022-10-14 13:06:33 +01:00
sendDirectContactMessage :: ( MsgEncodingI e , ChatMonad m ) => Contact -> ChatMsgEvent e -> m ( SndMessage , Int64 )
2022-02-25 21:59:35 +04:00
sendDirectContactMessage ct @ Contact { activeConn = conn @ Connection { connId , connStatus } } chatMsgEvent = do
2022-02-14 18:49:42 +04:00
if connStatus == ConnReady || connStatus == ConnSndReady
2022-02-25 21:59:35 +04:00
then sendDirectMessage conn chatMsgEvent ( ConnectionId connId )
2022-02-14 18:49:42 +04:00
else throwChatError $ CEContactNotReady ct
2022-10-14 13:06:33 +01:00
sendDirectMessage :: ( MsgEncodingI e , ChatMonad m ) => Connection -> ChatMsgEvent e -> ConnOrGroupId -> m ( SndMessage , Int64 )
2022-02-25 21:59:35 +04:00
sendDirectMessage conn chatMsgEvent connOrGroupId = do
2022-03-13 19:34:03 +00:00
msg @ SndMessage { msgId , msgBody } <- createSndMessage chatMsgEvent connOrGroupId
2022-10-14 13:06:33 +01:00
( msg , ) <$> deliverMessage conn ( toCMEventTag chatMsgEvent ) msgBody msgId
2022-01-24 16:07:17 +00:00
2022-10-14 13:06:33 +01:00
createSndMessage :: ( MsgEncodingI e , ChatMonad m ) => ChatMsgEvent e -> ConnOrGroupId -> m SndMessage
2022-02-25 21:59:35 +04:00
createSndMessage chatMsgEvent connOrGroupId = do
2022-03-13 19:34:03 +00:00
gVar <- asks idsDrg
2022-06-18 20:06:13 +01:00
withStore $ \ db -> createNewSndMessage db gVar connOrGroupId $ \ sharedMsgId ->
2022-03-13 19:34:03 +00:00
let msgBody = strEncode ChatMessage { msgId = Just sharedMsgId , chatMsgEvent }
2022-03-16 13:20:47 +00:00
in NewMessage { chatMsgEvent , msgBody }
2021-07-16 07:40:55 +01:00
2022-10-14 13:06:33 +01:00
directMessage :: MsgEncodingI e => ChatMsgEvent e -> ByteString
2022-03-13 19:34:03 +00:00
directMessage chatMsgEvent = strEncode ChatMessage { msgId = Nothing , chatMsgEvent }
2021-07-16 07:40:55 +01:00
2022-10-14 13:06:33 +01:00
deliverMessage :: ChatMonad m => Connection -> CMEventTag e -> MsgBody -> MessageId -> m Int64
2022-06-07 14:14:54 +01:00
deliverMessage conn @ Connection { connId } cmEventTag msgBody msgId = do
let msgFlags = MsgFlags { notification = hasNotification cmEventTag }
agentMsgId <- withAgent $ \ a -> sendMessage a ( aConnId conn ) msgFlags msgBody
2021-12-29 23:11:55 +04:00
let sndMsgDelivery = SndMsgDelivery { connId , agentMsgId }
2022-06-18 20:06:13 +01:00
withStore' $ \ db -> createSndMsgDelivery db sndMsgDelivery msgId
2021-12-29 23:11:55 +04:00
2022-10-14 13:06:33 +01:00
sendGroupMessage :: ( MsgEncodingI e , ChatMonad m ) => GroupInfo -> [ GroupMember ] -> ChatMsgEvent e -> m SndMessage
2022-02-25 21:59:35 +04:00
sendGroupMessage GroupInfo { groupId } members chatMsgEvent =
sendGroupMessage' members chatMsgEvent groupId Nothing $ pure ()
2022-01-24 16:07:17 +00:00
2022-10-14 13:06:33 +01:00
sendXGrpMemInv :: ( MsgEncodingI e , ChatMonad m ) => GroupInfo -> GroupMember -> ChatMsgEvent e -> Int64 -> m SndMessage
2022-02-25 21:59:35 +04:00
sendXGrpMemInv GroupInfo { groupId } reMember chatMsgEvent introId =
sendGroupMessage' [ reMember ] chatMsgEvent groupId ( Just introId ) $
2022-06-18 20:06:13 +01:00
withStore' $ \ db -> updateIntroStatus db introId GMIntroInvForwarded
2022-01-24 16:07:17 +00:00
2022-10-14 13:06:33 +01:00
sendGroupMessage' :: ( MsgEncodingI e , ChatMonad m ) => [ GroupMember ] -> ChatMsgEvent e -> Int64 -> Maybe Int64 -> m () -> m SndMessage
2022-02-25 21:59:35 +04:00
sendGroupMessage' members chatMsgEvent groupId introId_ postDeliver = do
2022-03-13 19:34:03 +00:00
msg @ SndMessage { msgId , msgBody } <- createSndMessage chatMsgEvent ( GroupId groupId )
2022-02-10 17:03:36 +04:00
-- TODO collect failed deliveries into a single error
forM_ ( filter memberCurrent members ) $ \ m @ GroupMember { groupMemberId } ->
2022-01-24 16:07:17 +00:00
case memberConn m of
2022-06-18 20:06:13 +01:00
Nothing -> withStore' $ \ db -> createPendingGroupMessage db groupMemberId msgId introId_
2022-06-07 14:14:54 +01:00
Just conn @ Connection { connStatus }
| connStatus == ConnSndReady || connStatus == ConnReady -> do
2022-10-14 13:06:33 +01:00
let tag = toCMEventTag chatMsgEvent
( deliverMessage conn tag msgBody msgId >> postDeliver ) ` catchError ` const ( pure () )
2022-06-07 14:14:54 +01:00
| connStatus == ConnDeleted -> pure ()
2022-06-18 20:06:13 +01:00
| otherwise -> withStore' $ \ db -> createPendingGroupMessage db groupMemberId msgId introId_
2022-03-13 19:34:03 +00:00
pure msg
2022-01-24 16:07:17 +00:00
sendPendingGroupMessages :: ChatMonad m => GroupMember -> Connection -> m ()
sendPendingGroupMessages GroupMember { groupMemberId , localDisplayName } conn = do
2022-06-18 20:06:13 +01:00
pendingMessages <- withStore' $ \ db -> getPendingGroupMessages db groupMemberId
2022-01-24 16:07:17 +00:00
-- TODO ensure order - pending messages interleave with user input messages
2022-10-14 13:06:33 +01:00
forM_ pendingMessages $ \ PendingGroupMessage { msgId , cmEventTag = ACMEventTag _ tag , msgBody , introId_ } -> do
void $ deliverMessage conn tag msgBody msgId
2022-06-18 20:06:13 +01:00
withStore' $ \ db -> deletePendingGroupMessage db groupMemberId msgId
2022-10-14 13:06:33 +01:00
case tag of
XGrpMemFwd_ -> case introId_ of
Just introId -> withStore' $ \ db -> updateIntroStatus db introId GMIntroInvForwarded
_ -> throwChatError $ CEGroupMemberIntroNotFound localDisplayName
_ -> pure ()
2022-01-24 16:07:17 +00:00
2022-09-14 19:45:21 +04:00
saveRcvMSG :: ChatMonad m => Connection -> ConnOrGroupId -> MsgMeta -> MsgBody -> CommandId -> m RcvMessage
saveRcvMSG Connection { connId } connOrGroupId agentMsgMeta msgBody agentAckCmdId = do
2022-10-14 13:06:33 +01:00
ACMsg _ ChatMessage { msgId = sharedMsgId_ , chatMsgEvent } <- parseAChatMessage msgBody
2022-01-24 16:07:17 +00:00
let agentMsgId = fst $ recipient agentMsgMeta
2022-03-16 13:20:47 +00:00
newMsg = NewMessage { chatMsgEvent , msgBody }
2022-09-14 19:45:21 +04:00
rcvMsgDelivery = RcvMsgDelivery { connId , agentMsgId , agentMsgMeta , agentAckCmdId }
2022-06-18 20:06:13 +01:00
withStore' $ \ db -> createNewMessageAndRcvMsgDelivery db connOrGroupId newMsg sharedMsgId_ rcvMsgDelivery
2022-01-26 16:18:27 +04:00
2022-04-10 13:30:58 +04:00
saveSndChatItem :: ChatMonad m => User -> ChatDirection c 'MDSnd -> SndMessage -> CIContent 'MDSnd -> Maybe ( CIFile 'MDSnd ) -> Maybe ( CIQuote c ) -> m ( ChatItem c 'MDSnd )
saveSndChatItem user cd msg @ SndMessage { sharedMsgId } content ciFile quotedItem = do
2022-01-28 11:52:10 +04:00
createdAt <- liftIO getCurrentTime
2022-06-18 20:06:13 +01:00
ciId <- withStore' $ \ db -> createNewSndChatItem db user cd msg content quotedItem createdAt
forM_ ciFile $ \ CIFile { fileId } -> withStore' $ \ db -> updateFileTransferChatItemId db fileId ciId
2022-04-10 13:30:58 +04:00
liftIO $ mkChatItem cd ciId content ciFile quotedItem ( Just sharedMsgId ) createdAt createdAt
2022-01-26 16:18:27 +04:00
2022-04-10 13:30:58 +04:00
saveRcvChatItem :: ChatMonad m => User -> ChatDirection c 'MDRcv -> RcvMessage -> MsgMeta -> CIContent 'MDRcv -> Maybe ( CIFile 'MDRcv ) -> m ( ChatItem c 'MDRcv )
2022-05-17 11:22:09 +04:00
saveRcvChatItem user cd msg @ RcvMessage { sharedMsgId_ } = saveRcvChatItem' user cd msg sharedMsgId_
saveRcvChatItem' :: ChatMonad m => User -> ChatDirection c 'MDRcv -> RcvMessage -> Maybe SharedMsgId -> MsgMeta -> CIContent 'MDRcv -> Maybe ( CIFile 'MDRcv ) -> m ( ChatItem c 'MDRcv )
saveRcvChatItem' user cd msg sharedMsgId_ MsgMeta { broker = ( _ , brokerTs ) } content ciFile = do
2022-01-28 11:52:10 +04:00
createdAt <- liftIO getCurrentTime
2022-06-18 20:06:13 +01:00
( ciId , quotedItem ) <- withStore' $ \ db -> createNewRcvChatItem db user cd msg sharedMsgId_ content brokerTs createdAt
forM_ ciFile $ \ CIFile { fileId } -> withStore' $ \ db -> updateFileTransferChatItemId db fileId ciId
2022-04-10 13:30:58 +04:00
liftIO $ mkChatItem cd ciId content ciFile quotedItem sharedMsgId_ brokerTs createdAt
2022-03-16 13:20:47 +00:00
2022-04-10 13:30:58 +04:00
mkChatItem :: MsgDirectionI d => ChatDirection c d -> ChatItemId -> CIContent d -> Maybe ( CIFile d ) -> Maybe ( CIQuote c ) -> Maybe SharedMsgId -> ChatItemTs -> UTCTime -> IO ( ChatItem c d )
2022-05-04 13:31:00 +01:00
mkChatItem cd ciId content file quotedItem sharedMsgId itemTs currentTs = do
2022-03-16 13:20:47 +00:00
tz <- getCurrentTimeZone
let itemText = ciContentToText content
2022-05-04 13:31:00 +01:00
meta = mkCIMeta ciId content itemText ciStatusNew sharedMsgId False False tz currentTs itemTs currentTs currentTs
2022-04-10 13:30:58 +04:00
pure ChatItem { chatDir = toCIDirection cd , meta , content , formattedText = parseMaybeMarkdownList itemText , quotedItem , file }
2021-07-24 10:26:28 +01:00
2022-09-14 19:45:21 +04:00
createAgentConnectionAsync :: forall m c . ( ChatMonad m , ConnectionModeI c ) => User -> Bool -> SConnectionMode c -> m ( CommandId , ConnId )
createAgentConnectionAsync user enableNtfs cMode = do
cmdId <- withStore' $ \ db -> createCommand db user Nothing CFCreateConn
connId <- withAgent $ \ a -> createConnectionAsync a ( aCorrId cmdId ) enableNtfs cMode
pure ( cmdId , connId )
joinAgentConnectionAsync :: ChatMonad m => User -> Bool -> ConnectionRequestUri c -> ConnInfo -> m ( CommandId , ConnId )
joinAgentConnectionAsync user enableNtfs cReqUri cInfo = do
cmdId <- withStore' $ \ db -> createCommand db user Nothing CFJoinConn
connId <- withAgent $ \ a -> joinConnectionAsync a ( aCorrId cmdId ) enableNtfs cReqUri cInfo
pure ( cmdId , connId )
2022-10-14 13:06:33 +01:00
allowAgentConnectionAsync :: ( MsgEncodingI e , ChatMonad m ) => User -> Connection -> ConfirmationId -> ChatMsgEvent e -> m ()
2022-09-14 19:45:21 +04:00
allowAgentConnectionAsync user conn @ Connection { connId } confId msg = do
cmdId <- withStore' $ \ db -> createCommand db user ( Just connId ) CFAllowConn
withAgent $ \ a -> allowConnectionAsync a ( aCorrId cmdId ) ( aConnId conn ) confId $ directMessage msg
2022-06-18 20:06:13 +01:00
withStore' $ \ db -> updateConnectionStatus db conn ConnAccepted
2021-07-05 19:54:44 +01:00
2022-10-14 14:57:01 +04:00
agentAcceptContactAsync :: ChatMonad m => User -> Bool -> InvitationId -> ChatMsgEvent -> m ( CommandId , ConnId )
agentAcceptContactAsync user enableNtfs invId msg = do
cmdId <- withStore' $ \ db -> createCommand db user Nothing CFAcceptContact
connId <- withAgent $ \ a -> acceptContactAsync a ( aCorrId cmdId ) enableNtfs invId $ directMessage msg
pure ( cmdId , connId )
2022-09-30 16:18:43 +04:00
deleteAgentConnectionAsync :: ChatMonad m => User -> Connection -> m ()
deleteAgentConnectionAsync user Connection { agentConnId , connId } =
deleteAgentConnectionAsync' user connId agentConnId
deleteAgentConnectionAsync' :: ChatMonad m => User -> Int64 -> AgentConnId -> m ()
deleteAgentConnectionAsync' user connId ( AgentConnId acId ) = do
cmdId <- withStore' $ \ db -> createCommand db user ( Just connId ) CFDeleteConn
withAgent $ \ a -> deleteConnectionAsync a ( aCorrId cmdId ) acId
2021-07-05 19:54:44 +01:00
getCreateActiveUser :: SQLiteStore -> IO User
getCreateActiveUser st = do
user <-
2022-06-18 20:06:13 +01:00
withTransaction st getUsers >>= \ case
2021-07-05 19:54:44 +01:00
[] -> newUser
users -> maybe ( selectUser users ) pure ( find activeUser users )
putStrLn $ " Current user: " <> userStr user
pure user
where
newUser :: IO User
newUser = do
putStrLn
" No user profiles found, it will be created now. \ n \
2021-07-14 20:11:41 +01:00
\ Please choose your display name and your full name .\ n \
2021-07-05 19:54:44 +01:00
\ They will be sent to your contacts when you connect .\ n \
\ They are only stored on your device and you can change them later . "
loop
where
loop = do
2021-07-14 20:11:41 +01:00
displayName <- getContactName
fullName <- T . pack <$> getWithPrompt " full name (optional) "
2022-06-18 20:06:13 +01:00
withTransaction st ( \ db -> runExceptT $ createUser db Profile { displayName , fullName , image = Nothing } True ) >>= \ case
2021-07-14 20:11:41 +01:00
Left SEDuplicateName -> do
putStrLn " chosen display name is already used by another profile on this device, choose another one "
2021-07-05 19:54:44 +01:00
loop
Left e -> putStrLn ( " database error " <> show e ) >> exitFailure
Right user -> pure user
selectUser :: [ User ] -> IO User
selectUser [ user ] = do
2022-06-18 20:06:13 +01:00
withTransaction st ( ` setActiveUser ` userId user )
2021-07-05 19:54:44 +01:00
pure user
selectUser users = do
2021-07-05 20:05:07 +01:00
putStrLn " Select user profile: "
2021-07-05 19:54:44 +01:00
forM_ ( zip [ 1 .. ] users ) $ \ ( n :: Int , user ) -> putStrLn $ show n <> " - " <> userStr user
loop
where
loop = do
nStr <- getWithPrompt $ " user profile number (1 .. " <> show ( length users ) <> " ) "
case readMaybe nStr :: Maybe Int of
Nothing -> putStrLn " invalid user number " >> loop
Just n
| n <= 0 || n > length users -> putStrLn " invalid user number " >> loop
| otherwise -> do
2022-10-14 13:06:33 +01:00
let user = users !! ( n - 1 )
withTransaction st ( ` setActiveUser ` userId user )
pure user
2021-07-05 19:54:44 +01:00
userStr :: User -> String
2022-08-18 11:35:31 +04:00
userStr User { localDisplayName , profile = LocalProfile { fullName } } =
2021-08-22 15:56:36 +01:00
T . unpack $ localDisplayName <> if T . null fullName || localDisplayName == fullName then " " else " ( " <> fullName <> " ) "
2021-07-14 20:11:41 +01:00
getContactName :: IO ContactName
getContactName = do
displayName <- getWithPrompt " display name (no spaces) "
if null displayName || isJust ( find ( == ' ' ) displayName )
then putStrLn " display name has space(s), choose another one " >> getContactName
else pure $ T . pack displayName
2021-07-05 19:54:44 +01:00
getWithPrompt :: String -> IO String
getWithPrompt s = putStr ( s <> " : " ) >> hFlush stdout >> getLine
2021-06-25 18:18:24 +01:00
2022-03-13 20:13:47 +00:00
showMsgToast :: ( MonadUnliftIO m , MonadReader ChatController m ) => Text -> MsgContent -> Maybe MarkdownList -> m ()
showMsgToast from mc md_ = showToast from $ maybe ( msgContentText mc ) ( mconcat . map hideSecret ) md_
where
hideSecret :: FormattedText -> Text
hideSecret FormattedText { format = Just Secret } = " ... "
hideSecret FormattedText { text } = text
2021-07-04 18:42:24 +01:00
showToast :: ( MonadUnliftIO m , MonadReader ChatController m ) => Text -> Text -> m ()
showToast title text = atomically . ( ` writeTBQueue ` Notification { title , text } ) =<< asks notifyQ
2021-06-26 20:20:33 +01:00
notificationSubscriber :: ( MonadUnliftIO m , MonadReader ChatController m ) => m ()
notificationSubscriber = do
ChatController { notifyQ , sendNotification } <- ask
forever $ atomically ( readTBQueue notifyQ ) >>= liftIO . sendNotification
2022-02-06 16:18:01 +00:00
withUser' :: ChatMonad m => ( User -> m a ) -> m a
withUser' action =
asks currentUser
>>= readTVarIO
>>= maybe ( throwChatError CENoActiveUser ) action
withUser :: ChatMonad m => ( User -> m a ) -> m a
withUser action = withUser' $ \ user ->
ifM chatStarted ( action user ) ( throwChatError CEChatNotStarted )
2022-10-03 17:44:56 +04:00
chatStarted :: ChatMonad m => m Bool
chatStarted = fmap isJust . readTVarIO =<< asks agentAsync
2022-02-06 16:18:01 +00:00
2021-07-05 19:54:44 +01:00
withAgent :: ChatMonad m => ( AgentClient -> ExceptT AgentErrorType m a ) -> m a
withAgent action =
2021-06-25 18:18:24 +01:00
asks smpAgent
>>= runExceptT . action
2021-07-05 19:54:44 +01:00
>>= liftEither . first ChatErrorAgent
2021-06-25 18:18:24 +01:00
2022-06-18 20:06:13 +01:00
withStore' :: ChatMonad m => ( DB . Connection -> IO a ) -> m a
withStore' action = withStore $ liftIO . action
2021-07-04 18:42:24 +01:00
withStore ::
ChatMonad m =>
2022-06-18 20:06:13 +01:00
( DB . Connection -> ExceptT StoreError IO a ) ->
2021-07-04 18:42:24 +01:00
m a
2022-06-18 20:06:13 +01:00
withStore action = do
2022-09-23 19:22:56 +01:00
ChatController { chatStore } <- ask
2022-06-18 20:06:13 +01:00
liftEitherError ChatErrorStore $
2022-09-23 19:22:56 +01:00
withTransaction chatStore ( runExceptT . action ) ` E . catch ` handleInternal
2022-06-18 20:06:13 +01:00
where
2022-07-01 10:37:26 +01:00
handleInternal :: E . SomeException -> IO ( Either StoreError a )
2022-06-18 20:06:13 +01:00
handleInternal = pure . Left . SEInternalError . show
2021-07-04 18:42:24 +01:00
2021-06-25 18:18:24 +01:00
chatCommandP :: Parser ChatCommand
chatCommandP =
2022-07-20 09:36:43 +01:00
A . choice
2022-09-05 15:23:38 +01:00
[ " /mute " *> ( ( ` ShowMessages ` False ) <$> chatNameP' ) ,
" /unmute " *> ( ( ` ShowMessages ` True ) <$> chatNameP' ) ,
( " /user " <|> " /u " ) *> ( CreateActiveUser <$> userProfile ) ,
2022-07-20 09:36:43 +01:00
( " /user " <|> " /u " ) $> ShowActiveUser ,
2022-09-28 20:47:06 +04:00
" /_start subscribe= " *> ( StartChat <$> onOffP <* " expire= " <*> onOffP ) ,
" /_start " $> StartChat True True ,
2022-07-20 09:36:43 +01:00
" /_stop " $> APIStopChat ,
" /_app activate " $> APIActivateChat ,
" /_app suspend " *> ( APISuspendChat <$> A . decimal ) ,
" /_resubscribe all " $> ResubscribeAllConnections ,
" /_files_folder " *> ( SetFilesFolder <$> filePath ) ,
" /_db export " *> ( APIExportArchive <$> jsonP ) ,
" /_db import " *> ( APIImportArchive <$> jsonP ) ,
" /_db delete " $> APIDeleteStorage ,
2022-09-06 21:25:07 +01:00
" /_db encryption " *> ( APIStorageEncryption <$> jsonP ) ,
2022-09-05 14:54:39 +01:00
" /db encrypt " *> ( APIStorageEncryption . DBEncryptionConfig " " <$> dbKeyP ) ,
2022-09-08 17:36:16 +01:00
" /db key " *> ( APIStorageEncryption <$> ( DBEncryptionConfig <$> dbKeyP <* A . space <*> dbKeyP ) ) ,
2022-09-05 14:54:39 +01:00
" /db decrypt " *> ( APIStorageEncryption . ( ` DBEncryptionConfig ` " " ) <$> dbKeyP ) ,
2022-09-17 16:06:27 +01:00
" /sql chat " *> ( ExecChatStoreSQL <$> textP ) ,
" /sql agent " *> ( ExecAgentStoreSQL <$> textP ) ,
2022-07-20 09:36:43 +01:00
" /_get chats " *> ( APIGetChats <$> ( " pcc=on " $> True <|> " pcc=off " $> False <|> pure False ) ) ,
2022-08-16 19:56:21 +01:00
" /_get chat " *> ( APIGetChat <$> chatRefP <* A . space <*> chatPaginationP <*> optional searchP ) ,
2022-07-20 09:36:43 +01:00
" /_get items count= " *> ( APIGetChatItems <$> A . decimal ) ,
" /_send " *> ( APISendMessage <$> chatRefP <*> ( " json " *> jsonP <|> " text " *> ( ComposedMessage Nothing Nothing <$> mcTextP ) ) ) ,
" /_update item " *> ( APIUpdateChatItem <$> chatRefP <* A . space <*> A . decimal <* A . space <*> msgContentP ) ,
" /_delete item " *> ( APIDeleteChatItem <$> chatRefP <* A . space <*> A . decimal <* A . space <*> ciDeleteMode ) ,
" /_read chat " *> ( APIChatRead <$> chatRefP <*> optional ( A . space *> ( ( , ) <$> ( " from= " *> A . decimal ) <* A . space <*> ( " to= " *> A . decimal ) ) ) ) ,
" /_delete " *> ( APIDeleteChat <$> chatRefP ) ,
" /_clear chat " *> ( APIClearChat <$> chatRefP ) ,
" /_accept " *> ( APIAcceptContact <$> A . decimal ) ,
" /_reject " *> ( APIRejectContact <$> A . decimal ) ,
" /_call invite @ " *> ( APISendCallInvitation <$> A . decimal <* A . space <*> jsonP ) ,
( " /call @ " <|> " /call " ) *> ( SendCallInvitation <$> displayName <*> pure defaultCallType ) ,
" /_call reject @ " *> ( APIRejectCall <$> A . decimal ) ,
" /_call offer @ " *> ( APISendCallOffer <$> A . decimal <* A . space <*> jsonP ) ,
" /_call answer @ " *> ( APISendCallAnswer <$> A . decimal <* A . space <*> jsonP ) ,
" /_call extra @ " *> ( APISendCallExtraInfo <$> A . decimal <* A . space <*> jsonP ) ,
" /_call end @ " *> ( APIEndCall <$> A . decimal ) ,
" /_call status @ " *> ( APICallStatus <$> A . decimal <* A . space <*> strP ) ,
" /_call get " $> APIGetCallInvitations ,
" /_profile " *> ( APIUpdateProfile <$> jsonP ) ,
2022-08-24 19:03:43 +04:00
" /_set alias @ " *> ( APISetContactAlias <$> A . decimal <*> ( A . space *> textP <|> pure " " ) ) ,
2022-09-27 20:45:46 +01:00
" /_set alias : " *> ( APISetConnectionAlias <$> A . decimal <*> ( A . space *> textP <|> pure " " ) ) ,
2022-07-20 09:36:43 +01:00
" /_parse " *> ( APIParseMarkdown . safeDecodeUtf8 <$> A . takeByteString ) ,
" /_ntf get " $> APIGetNtfToken ,
" /_ntf register " *> ( APIRegisterToken <$> strP_ <*> strP ) ,
" /_ntf verify " *> ( APIVerifyToken <$> strP <* A . space <*> strP <* A . space <*> strP ) ,
" /_ntf delete " *> ( APIDeleteToken <$> strP ) ,
" /_ntf message " *> ( APIGetNtfMessage <$> strP <* A . space <*> strP ) ,
" /_add # " *> ( APIAddMember <$> A . decimal <* A . space <*> A . decimal <*> memberRole ) ,
" /_join # " *> ( APIJoinGroup <$> A . decimal ) ,
2022-10-03 09:00:47 +01:00
" /_member role # " *> ( APIMemberRole <$> A . decimal <* A . space <*> A . decimal <*> memberRole ) ,
2022-07-20 09:36:43 +01:00
" /_remove # " *> ( APIRemoveMember <$> A . decimal <* A . space <*> A . decimal ) ,
" /_leave # " *> ( APILeaveGroup <$> A . decimal ) ,
" /_members # " *> ( APIListMembers <$> A . decimal ) ,
" /smp_servers default " $> SetUserSMPServers [] ,
" /smp_servers " *> ( SetUserSMPServers <$> smpServersP ) ,
" /smp_servers " $> GetUserSMPServers ,
2022-09-28 20:47:06 +04:00
" /_ttl " *> ( APISetChatItemTTL <$> ciTTLDecimal ) ,
" /ttl " *> ( APISetChatItemTTL <$> ciTTL ) ,
" /ttl " $> APIGetChatItemTTL ,
2022-07-25 14:04:27 +01:00
" /_network " *> ( APISetNetworkConfig <$> jsonP ) ,
( " /network " <|> " /net " ) *> ( APISetNetworkConfig <$> netCfgP ) ,
( " /network " <|> " /net " ) $> APIGetNetworkConfig ,
2022-08-19 22:44:00 +01:00
" /_settings " *> ( APISetChatSettings <$> chatRefP <* A . space <*> jsonP ) ,
2022-07-20 14:57:16 +01:00
" /_info # " *> ( APIGroupMemberInfo <$> A . decimal <* A . space <*> A . decimal ) ,
" /_info @ " *> ( APIContactInfo <$> A . decimal ) ,
( " /info # " <|> " /i # " ) *> ( GroupMemberInfo <$> displayName <* A . space <* optional ( A . char '@' ) <*> displayName ) ,
( " /info @ " <|> " /info " <|> " /i @ " <|> " /i " ) *> ( ContactInfo <$> displayName ) ,
2022-07-20 09:36:43 +01:00
( " /help files " <|> " /help file " <|> " /hf " ) $> ChatHelp HSFiles ,
( " /help groups " <|> " /help group " <|> " /hg " ) $> ChatHelp HSGroups ,
( " /help address " <|> " /ha " ) $> ChatHelp HSMyAddress ,
( " /help messages " <|> " /hm " ) $> ChatHelp HSMessages ,
2022-07-26 07:29:28 +01:00
( " /help settings " <|> " /hs " ) $> ChatHelp HSSettings ,
2022-07-20 09:36:43 +01:00
( " /help " <|> " /h " ) $> ChatHelp HSMain ,
( " /group # " <|> " /group " <|> " /g # " <|> " /g " ) *> ( NewGroup <$> groupProfile ) ,
2022-07-27 12:15:09 +01:00
" /_group " *> ( NewGroup <$> jsonP ) ,
2022-09-05 15:23:38 +01:00
( " /add # " <|> " /add " <|> " /a # " <|> " /a " ) *> ( AddMember <$> displayName <* A . space <* optional ( A . char '@' ) <*> displayName <*> memberRole ) ,
2022-07-20 09:36:43 +01:00
( " /join # " <|> " /join " <|> " /j # " <|> " /j " ) *> ( JoinGroup <$> displayName ) ,
2022-10-03 09:00:47 +01:00
( " /member role # " <|> " /member role " <|> " /mr # " <|> " /mr " ) *> ( MemberRole <$> displayName <* A . space <* optional ( A . char '@' ) <*> displayName <*> memberRole ) ,
2022-09-05 15:23:38 +01:00
( " /remove # " <|> " /remove " <|> " /rm # " <|> " /rm " ) *> ( RemoveMember <$> displayName <* A . space <* optional ( A . char '@' ) <*> displayName ) ,
2022-07-20 09:36:43 +01:00
( " /leave # " <|> " /leave " <|> " /l # " <|> " /l " ) *> ( LeaveGroup <$> displayName ) ,
( " /delete # " <|> " /d # " ) *> ( DeleteGroup <$> displayName ) ,
( " /delete @ " <|> " /delete " <|> " /d @ " <|> " /d " ) *> ( DeleteContact <$> displayName ) ,
" /clear # " *> ( ClearGroup <$> displayName ) ,
( " /clear @ " <|> " /clear " ) *> ( ClearContact <$> displayName ) ,
( " /members # " <|> " /members " <|> " /ms # " <|> " /ms " ) *> ( ListMembers <$> displayName ) ,
( " /groups " <|> " /gs " ) $> ListGroups ,
2022-07-29 19:04:32 +01:00
" /_group_profile # " *> ( APIUpdateGroupProfile <$> A . decimal <* A . space <*> jsonP ) ,
( " /group_profile # " <|> " /gp # " <|> " /group_profile " <|> " /gp " ) *> ( UpdateGroupProfile <$> displayName <* A . space <*> groupProfile ) ,
2022-10-13 17:12:22 +04:00
" /_create link # " *> ( APICreateGroupLink <$> A . decimal ) ,
" /_delete link # " *> ( APIDeleteGroupLink <$> A . decimal ) ,
" /_get link # " *> ( APIGetGroupLink <$> A . decimal ) ,
" /create link # " *> ( CreateGroupLink <$> displayName ) ,
" /delete link # " *> ( DeleteGroupLink <$> displayName ) ,
" /show link # " *> ( ShowGroupLink <$> displayName ) ,
2022-07-20 09:36:43 +01:00
( " ># " <|> " > # " ) *> ( SendGroupMessageQuote <$> displayName <* A . space <*> pure Nothing <*> quotedMsg <*> A . takeByteString ) ,
( " ># " <|> " > # " ) *> ( SendGroupMessageQuote <$> displayName <* A . space <* optional ( A . char '@' ) <*> ( Just <$> displayName ) <* A . space <*> quotedMsg <*> A . takeByteString ) ,
( " /contacts " <|> " /cs " ) $> ListContacts ,
( " /connect " <|> " /c " ) *> ( Connect <$> ( ( Just <$> strP ) <|> A . takeByteString $> Nothing ) ) ,
( " /connect " <|> " /c " ) $> AddContact ,
2022-08-08 22:48:42 +04:00
SendMessage <$> chatNameP <* A . space <*> A . takeByteString ,
2022-07-20 09:36:43 +01:00
( " >@ " <|> " > @ " ) *> sendMsgQuote ( AMsgDirection SMDRcv ) ,
( " >>@ " <|> " >> @ " ) *> sendMsgQuote ( AMsgDirection SMDSnd ) ,
( " \ \ " <|> " \ \ " ) *> ( DeleteMessage <$> chatNameP <* A . space <*> A . takeByteString ) ,
( " ! " <|> " ! " ) *> ( EditMessage <$> chatNameP <* A . space <*> ( quotedMsg <|> pure " " ) <*> A . takeByteString ) ,
" /feed " *> ( SendMessageBroadcast <$> A . takeByteString ) ,
( " /tail " <|> " /t " ) *> ( LastMessages <$> optional ( A . space *> chatNameP ) <*> msgCountP ) ,
( " /file " <|> " /f " ) *> ( SendFile <$> chatNameP' <* A . space <*> filePath ) ,
( " /image " <|> " /img " ) *> ( SendImage <$> chatNameP' <* A . space <*> filePath ) ,
( " /fforward " <|> " /ff " ) *> ( ForwardFile <$> chatNameP' <* A . space <*> A . decimal ) ,
( " /image_forward " <|> " /imgf " ) *> ( ForwardImage <$> chatNameP' <* A . space <*> A . decimal ) ,
( " /freceive " <|> " /fr " ) *> ( ReceiveFile <$> A . decimal <*> optional ( A . space *> filePath ) ) ,
( " /fcancel " <|> " /fc " ) *> ( CancelFile <$> A . decimal ) ,
( " /fstatus " <|> " /fs " ) *> ( FileStatus <$> A . decimal ) ,
" /simplex " $> ConnectSimplex ,
( " /address " <|> " /ad " ) $> CreateMyAddress ,
( " /delete_address " <|> " /da " ) $> DeleteMyAddress ,
( " /show_address " <|> " /sa " ) $> ShowMyAddress ,
" /auto_accept " *> ( AddressAutoAccept <$> onOffP <*> optional ( A . space *> msgContentP ) ) ,
( " /accept @ " <|> " /accept " <|> " /ac @ " <|> " /ac " ) *> ( AcceptContact <$> displayName ) ,
( " /reject @ " <|> " /reject " <|> " /rc @ " <|> " /rc " ) *> ( RejectContact <$> displayName ) ,
( " /markdown " <|> " /m " ) $> ChatHelp HSMarkdown ,
( " /welcome " <|> " /w " ) $> Welcome ,
" /profile_image " *> ( UpdateProfileImage . Just . ImageData <$> imageP ) ,
" /profile_image " $> UpdateProfileImage Nothing ,
( " /profile " <|> " /p " ) *> ( uncurry UpdateProfile <$> userNames ) ,
( " /profile " <|> " /p " ) $> ShowProfile ,
2022-08-18 11:35:31 +04:00
" /incognito " *> ( SetIncognito <$> onOffP ) ,
2022-07-20 09:36:43 +01:00
( " /quit " <|> " /q " <|> " /exit " ) $> QuitChat ,
( " /version " <|> " /v " ) $> ShowVersion
]
2021-06-25 18:18:24 +01:00
where
2022-03-10 15:45:40 +04:00
imagePrefix = ( <> ) <$> " data: " <*> ( " image/png;base64, " <|> " image/jpg;base64, " )
imageP = safeDecodeUtf8 <$> ( ( <> ) <$> imagePrefix <*> ( B64 . encode <$> base64P ) )
2022-04-23 17:32:40 +01:00
chatTypeP = A . char '@' $> CTDirect <|> A . char '#' $> CTGroup <|> A . char ':' $> CTContactConnection
2022-02-01 15:05:27 +04:00
chatPaginationP =
( CPLast <$ " count= " <*> A . decimal )
<|> ( CPAfter <$ " after= " <*> A . decimal <* A . space <* " count= " <*> A . decimal )
<|> ( CPBefore <$ " before= " <*> A . decimal <* A . space <* " count= " <*> A . decimal )
2022-05-06 09:17:49 +01:00
mcTextP = MCText . safeDecodeUtf8 <$> A . takeByteString
msgContentP = " text " *> mcTextP <|> " json " *> jsonP
2022-03-28 20:35:57 +04:00
ciDeleteMode = " broadcast " $> CIDMBroadcast <|> " internal " $> CIDMInternal
2021-07-14 20:11:41 +01:00
displayName = safeDecodeUtf8 <$> ( B . cons <$> A . satisfy refChar <*> A . takeTill ( == ' ' ) )
2022-03-19 09:04:53 +00:00
sendMsgQuote msgDir = SendMessageQuote <$> displayName <* A . space <*> pure msgDir <*> quotedMsg <*> A . takeByteString
2022-03-13 19:34:03 +00:00
quotedMsg = A . char '(' *> A . takeTill ( == ')' ) <* A . char ')' <* optional A . space
2021-07-11 12:22:22 +01:00
refChar c = c > ' ' && c /= '#' && c /= '@'
2022-02-14 14:59:11 +04:00
onOffP = ( " on " $> True ) <|> ( " off " $> False )
2022-03-10 15:45:40 +04:00
userNames = do
2021-08-22 15:56:36 +01:00
cName <- displayName
fullName <- fullNameP cName
2022-03-10 15:45:40 +04:00
pure ( cName , fullName )
userProfile = do
( cName , fullName ) <- userNames
pure Profile { displayName = cName , fullName , image = Nothing }
2022-03-23 20:52:00 +00:00
jsonP :: J . FromJSON a => Parser a
jsonP = J . eitherDecodeStrict' <$?> A . takeByteString
2021-07-12 19:00:03 +01:00
groupProfile = do
2021-07-16 07:40:55 +01:00
gName <- displayName
2021-08-22 15:56:36 +01:00
fullName <- fullNameP gName
2022-03-10 15:45:40 +04:00
pure GroupProfile { displayName = gName , fullName , image = Nothing }
2021-08-22 15:56:36 +01:00
fullNameP name = do
n <- ( A . space *> A . takeByteString ) <|> pure " "
pure $ if B . null n then name else safeDecodeUtf8 n
2022-08-24 19:03:43 +04:00
textP = safeDecodeUtf8 <$> A . takeByteString
2021-09-04 07:32:56 +01:00
filePath = T . unpack . safeDecodeUtf8 <$> A . takeByteString
2022-08-16 19:56:21 +01:00
searchP = T . unpack . safeDecodeUtf8 <$> ( " search= " *> A . takeByteString )
2021-07-11 12:22:22 +01:00
memberRole =
2022-10-01 20:30:47 +01:00
A . choice
[ " owner " $> GROwner ,
" admin " $> GRAdmin ,
" member " $> GRMember ,
-- " author" $> GRAuthor,
pure GRAdmin
]
2022-04-28 08:34:21 +01:00
chatNameP = ChatName <$> chatTypeP <*> displayName
2022-04-30 19:18:46 +04:00
chatNameP' = ChatName <$> ( chatTypeP <|> pure CTDirect ) <*> displayName
2022-04-28 08:34:21 +01:00
chatRefP = ChatRef <$> chatTypeP <*> A . decimal
2022-04-28 07:26:43 +01:00
msgCountP = A . space *> A . decimal <|> pure 10
2022-09-28 20:47:06 +04:00
ciTTLDecimal = ( " none " $> Nothing ) <|> ( Just <$> A . decimal )
ciTTL =
( " day " $> Just 86400 )
<|> ( " week " $> Just ( 7 * 86400 ) )
<|> ( " month " $> Just ( 30 * 86400 ) )
<|> ( " none " $> Nothing )
2022-07-25 14:04:27 +01:00
netCfgP = do
socksProxy <- " socks= " *> ( " off " $> Nothing <|> " on " $> Just defaultSocksProxy <|> Just <$> strP )
t_ <- optional $ " timeout= " *> A . decimal
let tcpTimeout = 1000000 * fromMaybe ( maybe 5 ( const 10 ) socksProxy ) t_
2022-08-02 15:36:12 +01:00
pure $ fullNetworkConfig socksProxy tcpTimeout
2022-09-05 14:54:39 +01:00
dbKeyP = nonEmptyKey <$?> strP
nonEmptyKey k @ ( DBEncryptionKey s ) = if null s then Left " empty key " else Right k
2021-12-18 10:23:47 +00:00
2022-01-12 17:37:46 +00:00
adminContactReq :: ConnReqContact
adminContactReq =
either error id $ strDecode " https://simplex.chat/contact#/?v=1&smp=smp%3A%2F%2FPQUV2eL0t7OStZOoAsPEV2QYWt4-xilbakvGUGOItUo%3D%40smp6.simplex.im%2FK1rslx-m5bpXVIdMZg9NLUZ_8JBm8xTt%23MCowBQYDK2VuAyEALDeVe-sG8mRY22LsXlPgiwTNs9dbiLrNuA7f3ZMAJ2w%3D "