@@ -48,6 +48,7 @@ module Simplex.Messaging.Client
4848 subscribeSMPQueuesNtfs ,
4949 secureSMPQueue ,
5050 secureSndSMPQueue ,
51+ proxySecureSndSMPQueue ,
5152 enableSMPQueueNotifications ,
5253 disableSMPQueueNotifications ,
5354 enableSMPQueuesNtfs ,
@@ -59,7 +60,7 @@ module Simplex.Messaging.Client
5960 deleteSMPQueues ,
6061 connectSMPProxiedRelay ,
6162 proxySMPMessage ,
62- forwardSMPMessage ,
63+ forwardSMPTransmission ,
6364 getSMPQueueInfo ,
6465 sendProtocolCommand ,
6566
@@ -736,6 +737,10 @@ secureSndSMPQueue :: SMPClient -> SndPrivateAuthKey -> SenderId -> SndPublicAuth
736737secureSndSMPQueue c spKey sId senderKey = okSMPCommand (SKEY senderKey) c spKey sId
737738{-# INLINE secureSndSMPQueue #-}
738739
740+ proxySecureSndSMPQueue :: SMPClient -> ProxiedRelay -> SndPrivateAuthKey -> SenderId -> SndPublicAuthKey -> ExceptT SMPClientError IO (Either ProxyClientError () )
741+ proxySecureSndSMPQueue c proxiedRelay spKey sId senderKey = proxySMPCommand c proxiedRelay (Just spKey) sId (SKEY senderKey)
742+ {-# INLINE proxySecureSndSMPQueue #-}
743+
739744-- | Enable notifications for the queue for push notifications server.
740745--
741746-- https://github.com/simplex-chat/simplexmq/blob/master/protocol/simplex-messaging.md#enable-notifications-command
@@ -776,6 +781,9 @@ sendSMPMessage c spKey sId flags msg =
776781 OK -> pure ()
777782 r -> throwE $ unexpectedResponse r
778783
784+ proxySMPMessage :: SMPClient -> ProxiedRelay -> Maybe SndPrivateAuthKey -> SenderId -> MsgFlags -> MsgBody -> ExceptT SMPClientError IO (Either ProxyClientError () )
785+ proxySMPMessage c proxiedRelay spKey sId flags msg = proxySMPCommand c proxiedRelay spKey sId (SEND flags msg)
786+
779787-- | Acknowledge message delivery (server deletes the message).
780788--
781789-- https://github.com/simplex-chat/simplexmq/blob/master/protocol/simplex-messaging.md#acknowledge-message-delivery
@@ -877,39 +885,39 @@ instance StrEncoding ProxyClientError where
877885-- 8) PFWD(SEND) -> WTF -> ProxyUnexpectedResponse - client/proxy protocol logic
878886-- 9) PFWD(SEND) -> ??? -> ProxyResponseError - client/proxy syntax
879887--
880- -- We report as proxySMPMessage error (ExceptT error) the errors of two kinds:
888+ -- We report as proxySMPCommand error (ExceptT error) the errors of two kinds:
881889-- - protocol errors from the destination relay wrapped in PRES - to simplify processing of AUTH and QUOTA errors, in this case proxy is "transparent" for such errors (PCEProtocolError, PCEUnexpectedResponse, PCEResponseError)
882890-- - other response/transport/connection errors from the client connected to proxy itself
883891-- Other errors are reported in the function result as `Either ProxiedRelayError ()`, including
884892-- - protocol errors from the client connected to proxy in ProxyClientError (PCEProtocolError, PCEUnexpectedResponse, PCEResponseError)
885893-- - other errors from the client running on proxy and connected to relay in PREProxiedRelayError
886894
887- proxySMPMessage ::
895+ -- This function proxies Sender commands that return OK or ERR
896+ proxySMPCommand ::
888897 SMPClient ->
889898 -- proxy session from PKEY
890899 ProxiedRelay ->
891900 -- message to deliver
892901 Maybe SndPrivateAuthKey ->
893902 SenderId ->
894- MsgFlags ->
895- MsgBody ->
903+ Command 'Sender ->
896904 ExceptT SMPClientError IO (Either ProxyClientError () )
897- proxySMPMessage c@ ProtocolClient {thParams = proxyThParams, client_ = PClient {clientCorrId = g, tcpTimeout}} (ProxiedRelay sessionId v serverKey) spKey sId flags msg = do
905+ proxySMPCommand c@ ProtocolClient {thParams = proxyThParams, client_ = PClient {clientCorrId = g, tcpTimeout}} (ProxiedRelay sessionId v serverKey) spKey sId command = do
898906 -- prepare params
899907 let serverThAuth = (\ ta -> ta {serverPeerPubKey = serverKey}) <$> thAuth proxyThParams
900908 serverThParams = smpTHParamsSetVersion v proxyThParams {sessionId, thAuth = serverThAuth}
901909 (cmdPubKey, cmdPrivKey) <- liftIO . atomically $ C. generateKeyPair @ 'C.X25519 g
902910 let cmdSecret = C. dh' serverKey cmdPrivKey
903911 nonce@ (C. CbNonce corrId) <- liftIO . atomically $ C. randomCbNonce g
904912 -- encode
905- let TransmissionForAuth {tForAuth, tToSend} = encodeTransmissionForAuth serverThParams (CorrId corrId, sId, Cmd SSender ( SEND flags msg) )
913+ let TransmissionForAuth {tForAuth, tToSend} = encodeTransmissionForAuth serverThParams (CorrId corrId, sId, Cmd SSender command )
906914 auth <- liftEitherWith PCETransportError $ authTransmission serverThAuth spKey nonce tForAuth
907915 b <- case batchTransmissions (batch serverThParams) (blockSize serverThParams) [Right (auth, tToSend)] of
908916 [] -> throwE $ PCETransportError TELargeMsg
909917 TBError e _ : _ -> throwE $ PCETransportError e
910918 TBTransmission s _ : _ -> pure s
911919 TBTransmissions s _ _ : _ -> pure s
912- et <- liftEitherWith PCECryptoError $ EncTransmission <$> C. cbEncrypt cmdSecret nonce b paddedProxiedMsgLength
920+ et <- liftEitherWith PCECryptoError $ EncTransmission <$> C. cbEncrypt cmdSecret nonce b paddedProxiedTLength
913921 -- proxy interaction errors are wrapped
914922 let tOut = Just $ 2 * tcpTimeout
915923 tryE (sendProtocolCommand_ c (Just nonce) tOut Nothing sessionId (Cmd SProxiedClient (PFWD v cmdPubKey et))) >>= \ case
@@ -937,8 +945,8 @@ proxySMPMessage c@ProtocolClient {thParams = proxyThParams, client_ = PClient {c
937945-- sends RFWD :: EncFwdTransmission -> Command Sender
938946-- receives RRES :: EncFwdResponse -> BrokerMsg
939947-- proxy should send PRES to the client with EncResponse
940- forwardSMPMessage :: SMPClient -> CorrId -> VersionSMP -> C. PublicKeyX25519 -> EncTransmission -> ExceptT SMPClientError IO EncResponse
941- forwardSMPMessage c@ ProtocolClient {thParams, client_ = PClient {clientCorrId = g}} fwdCorrId fwdVersion fwdKey fwdTransmission = do
948+ forwardSMPTransmission :: SMPClient -> CorrId -> VersionSMP -> C. PublicKeyX25519 -> EncTransmission -> ExceptT SMPClientError IO EncResponse
949+ forwardSMPTransmission c@ ProtocolClient {thParams, client_ = PClient {clientCorrId = g}} fwdCorrId fwdVersion fwdKey fwdTransmission = do
942950 -- prepare params
943951 sessSecret <- case thAuth thParams of
944952 Nothing -> throwE $ PCETransportError TENoServerAuth
0 commit comments