Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
17 changes: 11 additions & 6 deletions src/Simplex/Messaging/Agent.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeApplications #-}
{-# OPTIONS_GHC -fno-warn-ambiguous-fields #-}

Check warning on line 18 in src/Simplex/Messaging/Agent.hs

View workflow job for this annotation

GitHub Actions / build-ubuntu-20.04-8.10.7

unrecognised warning flag: -fno-warn-ambiguous-fields

-- |
-- Module : Simplex.Messaging.Agent
Expand Down Expand Up @@ -687,9 +687,15 @@
enqueueCommand c corrId connId (Just server) $ AClientCommand $ LET confId ownConnInfo
_ -> throwE $ CMD PROHIBITED "allowConnectionAsync"

-- TODO
-- Unlike `acceptContact` (synchronous version), `acceptContactAsync` uses `unacceptInvitation` in case of error,
-- because we're not taking lock here. In practice it is less likely to fail because it doesn't involve network IO,
-- and also it can't be triggered by user concurrently several times in a row. It could be improved similarly to
-- `acceptContact` by creating a new map for invitation locks and taking lock here, and removing `unacceptInvitation`
-- while marking invitation as accepted inside "lock level transaction" after successful `joinConnAsync`.
acceptContactAsync' :: AgentClient -> ACorrId -> Bool -> InvitationId -> ConnInfo -> PQSupport -> SubscriptionMode -> AM ConnId
acceptContactAsync' c corrId enableNtfs invId ownConnInfo pqSupport subMode = do
Invitation {contactConnId, connReq} <- withStore c (`getInvitation` invId)
Invitation {contactConnId, connReq} <- withStore c $ \db -> getInvitation db "acceptContactAsync'" invId
withStore c (`getConn` contactConnId) >>= \case
SomeConn _ (ContactConnection ConnData {userId} _) -> do
withStore' c $ \db -> acceptInvitation db invId ownConnInfo
Expand Down Expand Up @@ -809,7 +815,7 @@

newConnToAccept :: AgentClient -> ConnId -> Bool -> ConfirmationId -> PQSupport -> AM ConnId
newConnToAccept c connId enableNtfs invId pqSup = do
Invitation {connReq, contactConnId} <- withStore c (`getInvitation` invId)
Invitation {connReq, contactConnId} <- withStore c $ \db -> getInvitation db "newConnToAccept" invId
withStore c (`getConn` contactConnId) >>= \case
SomeConn _ (ContactConnection ConnData {userId} _) ->
newConnToJoin c userId connId enableNtfs connReq pqSup
Expand Down Expand Up @@ -941,13 +947,12 @@
-- | Accept contact (ACPT command) in Reader monad
acceptContact' :: AgentClient -> ConnId -> Bool -> InvitationId -> ConnInfo -> PQSupport -> SubscriptionMode -> AM SndQueueSecured
acceptContact' c connId enableNtfs invId ownConnInfo pqSupport subMode = withConnLock c connId "acceptContact" $ do
Invitation {contactConnId, connReq} <- withStore c (`getInvitation` invId)
Invitation {contactConnId, connReq} <- withStore c $ \db -> getInvitation db "acceptContact'" invId
withStore c (`getConn` contactConnId) >>= \case
SomeConn _ (ContactConnection ConnData {userId} _) -> do
sqSecured <- joinConn c userId connId enableNtfs connReq ownConnInfo pqSupport subMode
withStore' c $ \db -> acceptInvitation db invId ownConnInfo
joinConn c userId connId enableNtfs connReq ownConnInfo pqSupport subMode `catchAgentError` \err -> do
withStore' c (`unacceptInvitation` invId)
throwE err
pure sqSecured
_ -> throwE $ CMD PROHIBITED "acceptContact"

-- | Reject contact (RJCT command) in Reader monad
Expand Down
2 changes: 1 addition & 1 deletion src/Simplex/Messaging/Agent/Client.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2020,7 +2020,7 @@
SEConnDuplicate -> CONN DUPLICATE
SEBadConnType CRcv -> CONN SIMPLEX
SEBadConnType CSnd -> CONN SIMPLEX
SEInvitationNotFound -> CMD PROHIBITED "SEInvitationNotFound"
SEInvitationNotFound cxt invId -> CMD PROHIBITED $ "SEInvitationNotFound " <> cxt <> ", invitationId = " <> show invId
-- this error is never reported as store error,
-- it is used to wrap agent operations when "transaction-like" store access is needed
-- NOTE: network IO should NOT be used inside AgentStoreMonad
Expand All @@ -2028,7 +2028,7 @@
SEDatabaseBusy e -> CRITICAL True $ B.unpack e
e -> INTERNAL $ show e

userServers :: forall p. (ProtocolTypeI p, UserProtocol p) => AgentClient -> TMap UserId (UserServers p)

Check warning on line 2031 in src/Simplex/Messaging/Agent/Client.hs

View workflow job for this annotation

GitHub Actions / build-ubuntu-20.04-9.6.3

Redundant constraint: UserProtocol p

Check warning on line 2031 in src/Simplex/Messaging/Agent/Client.hs

View workflow job for this annotation

GitHub Actions / build-ubuntu-22.04-9.6.3

Redundant constraint: UserProtocol p
userServers c = case protocolTypeI @p of
SPSMP -> smpServers c
SPXFTP -> xftpServers c
Expand Down Expand Up @@ -2061,7 +2061,7 @@
hasUsedHost (ProtoServerWithAuth srv _) = any (`S.member` usedHosts) $ serverHosts srv

getNextServer_ ::
(ProtocolTypeI p, UserProtocol p) =>

Check warning on line 2064 in src/Simplex/Messaging/Agent/Client.hs

View workflow job for this annotation

GitHub Actions / build-ubuntu-20.04-9.6.3

Redundant constraints: (ProtocolTypeI p, UserProtocol p)

Check warning on line 2064 in src/Simplex/Messaging/Agent/Client.hs

View workflow job for this annotation

GitHub Actions / build-ubuntu-22.04-9.6.3

Redundant constraints: (ProtocolTypeI p, UserProtocol p)
NonEmpty (Maybe OperatorId, ProtoServerWithAuth p) ->
(Set (Maybe OperatorId), Set TransportHost) ->
AM (NonEmpty (Maybe OperatorId, ProtoServerWithAuth p), ProtoServerWithAuth p)
Expand Down
2 changes: 1 addition & 1 deletion src/Simplex/Messaging/Agent/Store.hs
Original file line number Diff line number Diff line change
Expand Up @@ -623,7 +623,7 @@ data StoreError
| -- | Confirmation not found.
SEConfirmationNotFound
| -- | Invitation not found
SEInvitationNotFound
SEInvitationNotFound String InvitationId
| -- | Message not found
SEMsgNotFound
| -- | Command not found
Expand Down
6 changes: 3 additions & 3 deletions src/Simplex/Messaging/Agent/Store/SQLite.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fno-warn-ambiguous-fields #-}

Check warning on line 25 in src/Simplex/Messaging/Agent/Store/SQLite.hs

View workflow job for this annotation

GitHub Actions / build-ubuntu-20.04-8.10.7

unrecognised warning flag: -fno-warn-ambiguous-fields
{-# OPTIONS_GHC -fno-warn-orphans #-}

module Simplex.Messaging.Agent.Store.SQLite
Expand Down Expand Up @@ -926,9 +926,9 @@
|]
(invitationId, contactConnId, connReq, recipientConnInfo)

getInvitation :: DB.Connection -> InvitationId -> IO (Either StoreError Invitation)
getInvitation db invitationId =
firstRow invitation SEInvitationNotFound $
getInvitation :: DB.Connection -> String -> InvitationId -> IO (Either StoreError Invitation)
getInvitation db cxt invitationId =
firstRow invitation (SEInvitationNotFound cxt invitationId) $
DB.query
db
[sql|
Expand Down
Loading