2023-09-27 11:41:02 +03:00
|
|
|
{-# LANGUAGE DuplicateRecordFields #-}
|
|
|
|
{-# LANGUAGE FlexibleContexts #-}
|
|
|
|
{-# LANGUAGE LambdaCase #-}
|
|
|
|
{-# LANGUAGE NamedFieldPuns #-}
|
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
{-# LANGUAGE ScopedTypeVariables #-}
|
|
|
|
|
|
|
|
module Simplex.Chat.Remote where
|
|
|
|
|
2023-10-04 18:36:10 +03:00
|
|
|
import Control.Monad
|
2023-09-27 11:41:02 +03:00
|
|
|
import Control.Monad.Except
|
|
|
|
import Control.Monad.IO.Class
|
2023-10-04 18:36:10 +03:00
|
|
|
import Control.Monad.STM (retry)
|
|
|
|
import Crypto.Random (getRandomBytes)
|
2023-09-27 11:41:02 +03:00
|
|
|
import qualified Data.Aeson as J
|
2023-09-27 18:24:38 +03:00
|
|
|
import qualified Data.Binary.Builder as Binary
|
2023-10-04 18:36:10 +03:00
|
|
|
import Data.ByteString (ByteString)
|
|
|
|
import qualified Data.ByteString.Base64.URL as B64U
|
|
|
|
import qualified Data.ByteString.Char8 as B
|
|
|
|
import Data.List.NonEmpty (NonEmpty (..))
|
2023-09-27 11:41:02 +03:00
|
|
|
import qualified Data.Map.Strict as M
|
|
|
|
import qualified Network.HTTP.Types as HTTP
|
|
|
|
import qualified Network.HTTP2.Client as HTTP2Client
|
2023-09-29 14:56:56 +03:00
|
|
|
import Network.Socket (SockAddr (..), hostAddressToTuple)
|
2023-09-27 11:41:02 +03:00
|
|
|
import Simplex.Chat.Controller
|
2023-09-29 14:56:56 +03:00
|
|
|
import qualified Simplex.Chat.Remote.Discovery as Discovery
|
2023-09-27 11:41:02 +03:00
|
|
|
import Simplex.Chat.Remote.Types
|
2023-09-29 14:56:56 +03:00
|
|
|
import Simplex.Chat.Store.Remote
|
2023-09-27 11:41:02 +03:00
|
|
|
import Simplex.Chat.Types
|
2023-09-29 14:56:56 +03:00
|
|
|
import qualified Simplex.Messaging.Crypto as C
|
|
|
|
import Simplex.Messaging.Encoding.String (StrEncoding (..))
|
|
|
|
import qualified Simplex.Messaging.TMap as TM
|
|
|
|
import Simplex.Messaging.Transport.Client (TransportHost (..))
|
2023-10-04 18:36:10 +03:00
|
|
|
import Simplex.Messaging.Transport.Credentials (genCredentials, tlsCredentials)
|
2023-09-27 11:41:02 +03:00
|
|
|
import Simplex.Messaging.Transport.HTTP2 (HTTP2Body (..))
|
2023-10-04 18:36:10 +03:00
|
|
|
import Simplex.Messaging.Transport.HTTP2.Client (HTTP2Client)
|
2023-09-27 11:41:02 +03:00
|
|
|
import qualified Simplex.Messaging.Transport.HTTP2.Client as HTTP2
|
2023-09-27 18:24:38 +03:00
|
|
|
import qualified Simplex.Messaging.Transport.HTTP2.Server as HTTP2
|
|
|
|
import Simplex.Messaging.Util (bshow)
|
2023-09-27 11:41:02 +03:00
|
|
|
import System.Directory (getFileSize)
|
2023-09-29 14:56:56 +03:00
|
|
|
import UnliftIO
|
2023-09-27 11:41:02 +03:00
|
|
|
|
2023-09-27 18:24:38 +03:00
|
|
|
withRemoteHostSession :: (ChatMonad m) => RemoteHostId -> (RemoteHostSession -> m a) -> m a
|
2023-09-27 11:41:02 +03:00
|
|
|
withRemoteHostSession remoteHostId action = do
|
|
|
|
chatReadVar remoteHostSessions >>= maybe err action . M.lookup remoteHostId
|
|
|
|
where
|
|
|
|
err = throwError $ ChatErrorRemoteHost remoteHostId RHMissing
|
|
|
|
|
2023-10-04 18:36:10 +03:00
|
|
|
withRemoteHost :: (ChatMonad m) => RemoteHostId -> (RemoteHost -> m a) -> m a
|
|
|
|
withRemoteHost remoteHostId action =
|
|
|
|
withStore' (`getRemoteHost` remoteHostId) >>= \case
|
|
|
|
Nothing -> throwError $ ChatErrorRemoteHost remoteHostId RHMissing
|
|
|
|
Just rh -> action rh
|
|
|
|
|
2023-09-29 14:56:56 +03:00
|
|
|
startRemoteHost :: (ChatMonad m) => RemoteHostId -> m ChatResponse
|
|
|
|
startRemoteHost remoteHostId = do
|
2023-10-04 18:36:10 +03:00
|
|
|
M.lookup remoteHostId <$> chatReadVar remoteHostSessions >>= \case
|
|
|
|
Just _ -> throwError $ ChatErrorRemoteHost remoteHostId RHBusy
|
|
|
|
Nothing -> withRemoteHost remoteHostId run
|
|
|
|
where
|
|
|
|
run RemoteHost {storePath, caKey, caCert} = do
|
|
|
|
announcer <- async $ do
|
|
|
|
cleanup <- toIO $ closeRemoteHostSession remoteHostId >>= toView
|
|
|
|
let parent = (C.signatureKeyPair caKey, caCert)
|
|
|
|
sessionCreds <- liftIO $ genCredentials (Just parent) (0, 24) "Session"
|
|
|
|
let (fingerprint, credentials) = tlsCredentials $ sessionCreds :| [parent]
|
|
|
|
Discovery.announceRevHTTP2 cleanup fingerprint credentials >>= \case
|
|
|
|
Left todo'err -> liftIO cleanup -- TODO: log error
|
|
|
|
Right ctrlClient -> do
|
|
|
|
chatModifyVar remoteHostSessions $ M.insert remoteHostId RemoteHostSessionStarted {storePath, ctrlClient}
|
|
|
|
-- TODO: start streaming outputQ
|
|
|
|
toView CRRemoteHostConnected {remoteHostId}
|
|
|
|
chatModifyVar remoteHostSessions $ M.insert remoteHostId RemoteHostSessionStarting {announcer}
|
|
|
|
pure CRRemoteHostStarted {remoteHostId}
|
|
|
|
|
|
|
|
closeRemoteHostSession :: (ChatMonad m) => RemoteHostId -> m ChatResponse
|
|
|
|
closeRemoteHostSession remoteHostId = withRemoteHostSession remoteHostId $ \session -> do
|
|
|
|
case session of
|
|
|
|
RemoteHostSessionStarting {announcer} -> cancel announcer
|
|
|
|
RemoteHostSessionStarted {ctrlClient} -> liftIO (HTTP2.closeHTTP2Client ctrlClient)
|
|
|
|
chatModifyVar remoteHostSessions $ M.delete remoteHostId
|
|
|
|
pure CRRemoteHostStopped { remoteHostId }
|
|
|
|
|
|
|
|
createRemoteHost :: (ChatMonad m) => m ChatResponse
|
|
|
|
createRemoteHost = do
|
|
|
|
let displayName = "TODO" -- you don't have remote host name here, it will be passed from remote host
|
|
|
|
((_, caKey), caCert) <- liftIO $ genCredentials Nothing (-25, 24 * 365) displayName
|
|
|
|
storePath <- liftIO randomStorePath
|
|
|
|
remoteHostId <- withStore' $ \db -> insertRemoteHost db storePath displayName caKey caCert
|
|
|
|
let oobData =
|
|
|
|
RemoteCtrlOOB
|
|
|
|
{ caFingerprint = C.certificateFingerprint caCert
|
|
|
|
}
|
|
|
|
pure CRRemoteHostCreated {remoteHostId, oobData}
|
|
|
|
|
|
|
|
-- | Generate a random 16-char filepath without / in it by using base64url encoding.
|
|
|
|
randomStorePath :: IO FilePath
|
|
|
|
randomStorePath = B.unpack . B64U.encode <$> getRandomBytes 12
|
|
|
|
|
|
|
|
listRemoteHosts :: (ChatMonad m) => m ChatResponse
|
|
|
|
listRemoteHosts = do
|
|
|
|
stored <- withStore' getRemoteHosts
|
|
|
|
active <- chatReadVar remoteHostSessions
|
|
|
|
pure $ CRRemoteHostList $ do
|
|
|
|
RemoteHost {remoteHostId, storePath, displayName} <- stored
|
|
|
|
let sessionActive = M.member remoteHostId active
|
|
|
|
pure RemoteHostInfo {remoteHostId, storePath, displayName, sessionActive}
|
|
|
|
|
|
|
|
deleteRemoteHost :: (ChatMonad m) => RemoteHostId -> m ChatResponse
|
|
|
|
deleteRemoteHost remoteHostId = withRemoteHost remoteHostId $ \rh -> do
|
|
|
|
-- TODO: delete files
|
|
|
|
withStore' $ \db -> deleteRemoteHostRecord db remoteHostId
|
|
|
|
pure CRRemoteHostDeleted {remoteHostId}
|
2023-09-27 13:40:19 +03:00
|
|
|
|
2023-09-27 18:24:38 +03:00
|
|
|
processRemoteCommand :: (ChatMonad m) => RemoteHostSession -> (ByteString, ChatCommand) -> m ChatResponse
|
2023-10-04 18:36:10 +03:00
|
|
|
processRemoteCommand RemoteHostSessionStarting {} _ = error "TODO: sending remote commands before session started"
|
|
|
|
processRemoteCommand RemoteHostSessionStarted {ctrlClient} (s, cmd) =
|
2023-09-27 11:41:02 +03:00
|
|
|
-- XXX: intercept and filter some commands
|
|
|
|
-- TODO: store missing files on remote host
|
2023-10-04 18:36:10 +03:00
|
|
|
relayCommand ctrlClient s
|
2023-09-27 11:41:02 +03:00
|
|
|
|
2023-10-04 18:36:10 +03:00
|
|
|
relayCommand :: (ChatMonad m) => HTTP2Client -> ByteString -> m ChatResponse
|
|
|
|
relayCommand http s =
|
|
|
|
postBytestring Nothing http "/relay" mempty s >>= \case
|
2023-09-27 18:24:38 +03:00
|
|
|
Left e -> error "TODO: http2chatError"
|
|
|
|
Right HTTP2.HTTP2Response {respBody = HTTP2Body {bodyHead}} -> do
|
|
|
|
remoteChatResponse <-
|
|
|
|
if iTax
|
|
|
|
then case J.eitherDecodeStrict bodyHead of -- XXX: large JSONs can overflow into buffered chunks
|
|
|
|
Left e -> error "TODO: json2chatError" e
|
|
|
|
Right (raw :: J.Value) -> case J.fromJSON (sum2tagged raw) of
|
|
|
|
J.Error e -> error "TODO: json2chatError" e
|
|
|
|
J.Success cr -> pure cr
|
|
|
|
else case J.eitherDecodeStrict bodyHead of -- XXX: large JSONs can overflow into buffered chunks
|
|
|
|
Left e -> error "TODO: json2chatError" e
|
|
|
|
Right cr -> pure cr
|
|
|
|
case remoteChatResponse of
|
|
|
|
-- TODO: intercept file responses and fetch files when needed
|
|
|
|
-- XXX: is that even possible, to have a file response to a command?
|
|
|
|
_ -> pure remoteChatResponse
|
2023-09-27 11:41:02 +03:00
|
|
|
where
|
|
|
|
iTax = True -- TODO: get from RemoteHost
|
|
|
|
-- XXX: extract to http2 transport
|
|
|
|
postBytestring timeout c path hs body = liftIO $ HTTP2.sendRequest c req timeout
|
|
|
|
where
|
|
|
|
req = HTTP2Client.requestBuilder "POST" path hs (Binary.fromByteString body)
|
|
|
|
|
2023-10-04 18:36:10 +03:00
|
|
|
-- | Convert swift single-field sum encoding into tagged/discriminator-field
|
|
|
|
sum2tagged :: J.Value -> J.Value
|
|
|
|
sum2tagged = \case
|
|
|
|
J.Object todo'convert -> J.Object todo'convert
|
|
|
|
skip -> skip
|
|
|
|
|
|
|
|
storeRemoteFile :: (ChatMonad m) => HTTP2Client -> FilePath -> m ChatResponse
|
|
|
|
storeRemoteFile http localFile = do
|
|
|
|
postFile Nothing http "/store" mempty localFile >>= \case
|
2023-09-29 14:56:56 +03:00
|
|
|
Left todo'err -> error "TODO: http2chatError"
|
2023-09-27 18:24:38 +03:00
|
|
|
Right HTTP2.HTTP2Response {response} -> case HTTP.statusCode <$> HTTP2Client.responseStatus response of
|
2023-09-27 11:41:02 +03:00
|
|
|
Just 200 -> pure $ CRCmdOk Nothing
|
2023-09-29 14:56:56 +03:00
|
|
|
todo'notOk -> error "TODO: http2chatError"
|
2023-09-27 11:41:02 +03:00
|
|
|
where
|
|
|
|
postFile timeout c path hs file = liftIO $ do
|
|
|
|
fileSize <- fromIntegral <$> getFileSize file
|
|
|
|
HTTP2.sendRequest c (req fileSize) timeout
|
|
|
|
where
|
|
|
|
req size = HTTP2Client.requestFile "POST" path hs (HTTP2Client.FileSpec file 0 size)
|
|
|
|
|
2023-10-04 18:36:10 +03:00
|
|
|
fetchRemoteFile :: (ChatMonad m) => HTTP2Client -> FilePath -> FileTransferId -> m ChatResponse
|
|
|
|
fetchRemoteFile http storePath remoteFileId = do
|
|
|
|
liftIO (HTTP2.sendRequest http req Nothing) >>= \case
|
2023-09-27 11:41:02 +03:00
|
|
|
Left e -> error "TODO: http2chatError"
|
|
|
|
Right HTTP2.HTTP2Response {respBody} -> do
|
|
|
|
error "TODO: stream body into a local file" -- XXX: consult headers for a file name?
|
|
|
|
where
|
|
|
|
req = HTTP2Client.requestNoBody "GET" path mempty
|
|
|
|
path = "/fetch/" <> bshow remoteFileId
|
|
|
|
|
2023-10-04 18:36:10 +03:00
|
|
|
processControllerRequest :: (ChatMonad m) => RemoteCtrlId -> HTTP2.HTTP2Request -> m ()
|
|
|
|
processControllerRequest rc req = error "TODO: processControllerRequest"
|
2023-09-29 14:56:56 +03:00
|
|
|
|
|
|
|
-- * ChatRequest handlers
|
|
|
|
|
|
|
|
startRemoteCtrl :: (ChatMonad m) => m ChatResponse
|
|
|
|
startRemoteCtrl =
|
|
|
|
chatReadVar remoteCtrlSession >>= \case
|
|
|
|
Just _busy -> throwError $ ChatErrorRemoteCtrl RCEBusy
|
|
|
|
Nothing -> do
|
|
|
|
accepted <- newEmptyTMVarIO
|
|
|
|
discovered <- newTVarIO mempty
|
2023-10-04 18:36:10 +03:00
|
|
|
discoverer <- async $ discoverRemoteCtrls discovered
|
|
|
|
supervisor <- async $ do
|
|
|
|
remoteCtrlId <- atomically (readTMVar accepted)
|
|
|
|
withRemoteCtrl remoteCtrlId $ \RemoteCtrl {displayName, fingerprint} -> do
|
|
|
|
source <- atomically $ TM.lookup fingerprint discovered >>= maybe retry pure
|
|
|
|
toView $ CRRemoteCtrlConnecting {remoteCtrlId, displayName}
|
|
|
|
atomically $ writeTVar discovered mempty -- flush unused sources
|
|
|
|
server <- async $ Discovery.connectRevHTTP2 source fingerprint (processControllerRequest remoteCtrlId)
|
|
|
|
chatModifyVar remoteCtrlSession $ fmap $ \s -> s {hostServer = Just server}
|
|
|
|
toView $ CRRemoteCtrlConnected {remoteCtrlId, displayName}
|
|
|
|
_ <- waitCatch server
|
|
|
|
chatWriteVar remoteCtrlSession Nothing
|
|
|
|
toView $ CRRemoteCtrlStopped {remoteCtrlId}
|
|
|
|
chatWriteVar remoteCtrlSession $ Just RemoteCtrlSession {discoverer, supervisor, hostServer = Nothing, discovered, accepted}
|
2023-10-05 21:49:20 +03:00
|
|
|
pure $ CRRemoteCtrlStarted Nothing
|
2023-09-29 14:56:56 +03:00
|
|
|
|
2023-10-04 18:36:10 +03:00
|
|
|
discoverRemoteCtrls :: (ChatMonad m) => TM.TMap C.KeyHash TransportHost -> m ()
|
2023-09-29 14:56:56 +03:00
|
|
|
discoverRemoteCtrls discovered = Discovery.openListener >>= go
|
|
|
|
where
|
|
|
|
go sock =
|
|
|
|
Discovery.recvAnnounce sock >>= \case
|
|
|
|
(SockAddrInet _port addr, invite) -> case strDecode invite of
|
|
|
|
Left _ -> go sock -- ignore malformed datagrams
|
|
|
|
Right fingerprint -> do
|
2023-10-04 18:36:10 +03:00
|
|
|
atomically $ TM.insert fingerprint (THIPv4 $ hostAddressToTuple addr) discovered
|
|
|
|
withStore' (`getRemoteCtrlByFingerprint` fingerprint) >>= \case
|
|
|
|
Nothing -> toView $ CRRemoteCtrlAnnounce fingerprint -- unknown controller, ui action required
|
|
|
|
Just found@RemoteCtrl {remoteCtrlId, accepted=storedChoice} -> case storedChoice of
|
|
|
|
Nothing -> toView $ CRRemoteCtrlFound found -- first-time controller, ui action required
|
|
|
|
Just False -> pure () -- skipping a rejected item
|
|
|
|
Just True -> chatReadVar remoteCtrlSession >>= \case
|
|
|
|
Nothing -> toView . CRChatError Nothing . ChatError $ CEInternalError "Remote host found without running a session"
|
|
|
|
Just RemoteCtrlSession {accepted} -> atomically $ void $ tryPutTMVar accepted remoteCtrlId -- previously accepted controller, connect automatically
|
2023-09-29 14:56:56 +03:00
|
|
|
_nonV4 -> go sock
|
|
|
|
|
2023-10-04 18:36:10 +03:00
|
|
|
registerRemoteCtrl :: (ChatMonad m) => RemoteCtrlOOB -> m ChatResponse
|
|
|
|
registerRemoteCtrl RemoteCtrlOOB {caFingerprint} = do
|
|
|
|
let displayName = "TODO" -- maybe include into OOB data
|
|
|
|
remoteCtrlId <- withStore' $ \db -> insertRemoteCtrl db displayName caFingerprint
|
|
|
|
pure $ CRRemoteCtrlRegistered {remoteCtrlId}
|
2023-09-29 14:56:56 +03:00
|
|
|
|
2023-10-04 18:36:10 +03:00
|
|
|
listRemoteCtrls :: (ChatMonad m) => m ChatResponse
|
|
|
|
listRemoteCtrls = do
|
|
|
|
stored <- withStore' getRemoteCtrls
|
|
|
|
active <-
|
|
|
|
chatReadVar remoteCtrlSession >>= \case
|
|
|
|
Nothing -> pure Nothing
|
|
|
|
Just RemoteCtrlSession {accepted} -> atomically (tryReadTMVar accepted)
|
|
|
|
pure $ CRRemoteCtrlList $ do
|
|
|
|
RemoteCtrl {remoteCtrlId, displayName} <- stored
|
|
|
|
let sessionActive = active == Just remoteCtrlId
|
|
|
|
pure RemoteCtrlInfo {remoteCtrlId, displayName, sessionActive}
|
|
|
|
|
|
|
|
acceptRemoteCtrl :: (ChatMonad m) => RemoteCtrlId -> m ChatResponse
|
|
|
|
acceptRemoteCtrl remoteCtrlId = do
|
|
|
|
withStore' $ \db -> markRemoteCtrlResolution db remoteCtrlId True
|
2023-09-29 14:56:56 +03:00
|
|
|
chatReadVar remoteCtrlSession >>= \case
|
|
|
|
Nothing -> throwError $ ChatErrorRemoteCtrl RCEInactive
|
2023-10-04 18:36:10 +03:00
|
|
|
Just RemoteCtrlSession {accepted} -> atomically . void $ tryPutTMVar accepted remoteCtrlId -- the remote host can now proceed with connection
|
|
|
|
pure $ CRRemoteCtrlAccepted {remoteCtrlId}
|
2023-09-29 14:56:56 +03:00
|
|
|
|
|
|
|
rejectRemoteCtrl :: (ChatMonad m) => RemoteCtrlId -> m ChatResponse
|
2023-10-04 18:36:10 +03:00
|
|
|
rejectRemoteCtrl remoteCtrlId = do
|
|
|
|
withStore' $ \db -> markRemoteCtrlResolution db remoteCtrlId False
|
2023-09-29 14:56:56 +03:00
|
|
|
chatReadVar remoteCtrlSession >>= \case
|
|
|
|
Nothing -> throwError $ ChatErrorRemoteCtrl RCEInactive
|
2023-10-04 18:36:10 +03:00
|
|
|
Just RemoteCtrlSession {discoverer, supervisor} -> do
|
|
|
|
cancel discoverer
|
|
|
|
cancel supervisor
|
|
|
|
pure $ CRRemoteCtrlRejected {remoteCtrlId}
|
2023-09-29 14:56:56 +03:00
|
|
|
|
|
|
|
stopRemoteCtrl :: (ChatMonad m) => RemoteCtrlId -> m ChatResponse
|
|
|
|
stopRemoteCtrl remoteCtrlId =
|
|
|
|
chatReadVar remoteCtrlSession >>= \case
|
|
|
|
Nothing -> throwError $ ChatErrorRemoteCtrl RCEInactive
|
2023-10-04 18:36:10 +03:00
|
|
|
Just RemoteCtrlSession {discoverer, supervisor, hostServer} -> do
|
|
|
|
cancel discoverer -- may be gone by now
|
|
|
|
case hostServer of
|
|
|
|
Just host -> cancel host -- supervisor will clean up
|
|
|
|
Nothing -> do
|
|
|
|
cancel supervisor -- supervisor is blocked until session progresses
|
|
|
|
chatWriteVar remoteCtrlSession Nothing
|
|
|
|
toView $ CRRemoteCtrlStopped {remoteCtrlId}
|
|
|
|
pure $ CRCmdOk Nothing
|
2023-09-29 14:56:56 +03:00
|
|
|
|
2023-10-04 18:36:10 +03:00
|
|
|
deleteRemoteCtrl :: (ChatMonad m) => RemoteCtrlId -> m ChatResponse
|
|
|
|
deleteRemoteCtrl remoteCtrlId =
|
2023-09-29 14:56:56 +03:00
|
|
|
chatReadVar remoteCtrlSession >>= \case
|
|
|
|
Nothing -> do
|
2023-10-04 18:36:10 +03:00
|
|
|
withStore' $ \db -> deleteRemoteCtrlRecord db remoteCtrlId
|
|
|
|
pure $ CRRemoteCtrlDeleted {remoteCtrlId}
|
2023-09-29 14:56:56 +03:00
|
|
|
Just _ -> throwError $ ChatErrorRemoteCtrl RCEBusy
|
2023-10-04 18:36:10 +03:00
|
|
|
|
|
|
|
withRemoteCtrl :: (ChatMonad m) => RemoteCtrlId -> (RemoteCtrl -> m a) -> m a
|
|
|
|
withRemoteCtrl remoteCtrlId action =
|
|
|
|
withStore' (`getRemoteCtrl` remoteCtrlId) >>= \case
|
|
|
|
Nothing -> throwError $ ChatErrorRemoteCtrl RCEMissing {remoteCtrlId}
|
|
|
|
Just rc -> action rc
|