2023-10-11 11:45:05 +03:00
{- # LANGUAGE DataKinds # -}
2023-09-27 11:41:02 +03:00
{- # LANGUAGE DuplicateRecordFields # -}
{- # LANGUAGE FlexibleContexts # -}
2023-10-13 20:53:04 +03:00
{- # LANGUAGE GADTs # -}
2023-09-27 11:41:02 +03:00
{- # LANGUAGE LambdaCase # -}
{- # LANGUAGE NamedFieldPuns # -}
2023-11-08 22:13:52 +02:00
{- # LANGUAGE OverloadedLists # -}
2023-09-27 11:41:02 +03:00
{- # LANGUAGE OverloadedStrings # -}
{- # LANGUAGE ScopedTypeVariables # -}
2023-10-07 16:23:24 +03:00
{- # LANGUAGE TupleSections # -}
2023-10-13 17:52:27 +01:00
{- # OPTIONS_GHC - fno - warn - ambiguous - fields # -}
2023-09-27 11:41:02 +03:00
module Simplex.Chat.Remote where
2023-10-30 16:00:54 +02:00
import Control.Applicative ( ( <|> ) )
2023-10-07 16:23:24 +03:00
import Control.Logger.Simple
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-29 19:06:32 +00:00
import Control.Monad.Reader
2023-10-04 18:36:10 +03:00
import Crypto.Random ( getRandomBytes )
2023-09-27 11:41:02 +03:00
import qualified Data.Aeson as J
2023-11-08 22:13:52 +02:00
import qualified Data.Aeson.Types as JT
import Data.Bifunctor ( second )
2023-10-22 11:42:19 +03:00
import Data.ByteString ( ByteString )
2023-10-04 18:36:10 +03:00
import qualified Data.ByteString.Base64.URL as B64U
2023-10-22 11:42:19 +03:00
import Data.ByteString.Builder ( Builder )
2023-10-04 18:36:10 +03:00
import qualified Data.ByteString.Char8 as B
2023-10-30 16:00:54 +02:00
import Data.Functor ( ( $> ) )
2023-11-17 20:50:38 +02:00
import Data.List.NonEmpty ( nonEmpty )
2023-09-27 11:41:02 +03:00
import qualified Data.Map.Strict as M
2023-11-12 12:40:13 +00:00
import Data.Maybe ( fromMaybe )
2023-10-15 00:18:04 +01:00
import Data.Text ( Text )
2023-10-07 16:23:24 +03:00
import qualified Data.Text as T
2023-11-13 20:16:34 +00:00
import Data.Text.Encoding ( decodeLatin1 , encodeUtf8 )
2023-11-17 20:50:38 +02:00
import Data.Word ( Word32 )
2023-10-22 11:42:19 +03:00
import qualified Network.HTTP.Types as N
2023-10-30 16:00:54 +02:00
import Network.HTTP2.Server ( responseStreaming )
2023-11-08 22:13:52 +02:00
import qualified Paths_simplex_chat as SC
2023-10-29 19:06:32 +00:00
import Simplex.Chat.Archive ( archiveFilesFolder )
2023-09-27 11:41:02 +03:00
import Simplex.Chat.Controller
2023-10-29 19:06:32 +00:00
import Simplex.Chat.Files
import Simplex.Chat.Messages ( chatNameStr )
2023-11-08 22:13:52 +02:00
import Simplex.Chat.Remote.AppVersion
2023-10-22 11:42:19 +03:00
import Simplex.Chat.Remote.Protocol
2023-11-08 22:13:52 +02:00
import Simplex.Chat.Remote.RevHTTP ( attachHTTP2Server , attachRevHTTP2Client )
2023-10-29 19:06:32 +00:00
import Simplex.Chat.Remote.Transport
2023-09-27 11:41:02 +03:00
import Simplex.Chat.Remote.Types
2023-10-29 19:06:32 +00:00
import Simplex.Chat.Store.Files
2023-09-29 14:56:56 +03:00
import Simplex.Chat.Store.Remote
2023-10-29 19:06:32 +00:00
import Simplex.Chat.Store.Shared
2023-11-08 22:13:52 +02:00
import Simplex.Chat.Types
2023-10-29 19:06:32 +00:00
import Simplex.Chat.Util ( encryptFile )
import Simplex.FileTransfer.Description ( FileDigest ( .. ) )
2023-11-08 22:13:52 +02:00
import Simplex.Messaging.Agent
import Simplex.Messaging.Agent.Protocol ( AgentErrorType ( RCP ) )
2023-10-29 19:06:32 +00:00
import Simplex.Messaging.Crypto.File ( CryptoFile ( .. ) , CryptoFileArgs ( .. ) )
import qualified Simplex.Messaging.Crypto.File as CF
2023-09-29 14:56:56 +03:00
import Simplex.Messaging.Encoding.String ( StrEncoding ( .. ) )
2023-10-30 16:00:54 +02:00
import qualified Simplex.Messaging.TMap as TM
2023-11-10 16:10:10 +00:00
import Simplex.Messaging.Transport ( TLS , closeConnection , tlsUniq )
2023-11-08 22:13:52 +02:00
import Simplex.Messaging.Transport.HTTP2.Client ( HTTP2ClientError , closeHTTP2Client )
2023-10-29 19:06:32 +00:00
import Simplex.Messaging.Transport.HTTP2.Server ( HTTP2Request ( .. ) )
2023-11-08 22:13:52 +02:00
import Simplex.Messaging.Util
import Simplex.RemoteControl.Client
2023-11-17 20:50:38 +02:00
import Simplex.RemoteControl.Invitation ( RCInvitation ( .. ) , RCSignedInvitation ( .. ) , RCVerifiedInvitation ( .. ) , verifySignedInvitation )
2023-11-01 12:48:58 +02:00
import Simplex.RemoteControl.Types
2023-10-30 16:00:54 +02:00
import System.FilePath ( takeFileName , ( </> ) )
2023-09-29 14:56:56 +03:00
import UnliftIO
2023-11-08 22:13:52 +02:00
import UnliftIO.Concurrent ( forkIO )
2023-11-15 17:57:29 +02:00
import UnliftIO.Directory ( copyFile , createDirectoryIfMissing , doesDirectoryExist , removeDirectoryRecursive , renameFile )
2023-10-22 11:42:19 +03:00
2023-11-08 22:13:52 +02:00
-- when acting as host
minRemoteCtrlVersion :: AppVersion
2023-11-12 14:40:49 +00:00
minRemoteCtrlVersion = AppVersion [ 5 , 4 , 0 , 3 ]
2023-09-27 11:41:02 +03:00
2023-11-08 22:13:52 +02:00
-- when acting as controller
minRemoteHostVersion :: AppVersion
2023-11-12 14:40:49 +00:00
minRemoteHostVersion = AppVersion [ 5 , 4 , 0 , 3 ]
2023-10-22 11:42:19 +03:00
2023-11-08 22:13:52 +02:00
currentAppVersion :: AppVersion
currentAppVersion = AppVersion SC . version
ctrlAppVersionRange :: AppVersionRange
ctrlAppVersionRange = mkAppVersionRange minRemoteHostVersion currentAppVersion
hostAppVersionRange :: AppVersionRange
hostAppVersionRange = mkAppVersionRange minRemoteCtrlVersion currentAppVersion
2023-10-15 14:17:36 +01:00
2023-11-13 20:39:41 +02:00
networkIOTimeout :: Int
networkIOTimeout = 15000000
2023-11-17 20:50:38 +02:00
discoveryTimeout :: Int
discoveryTimeout = 60000000
2023-11-08 22:13:52 +02:00
-- * Desktop side
getRemoteHostClient :: ChatMonad m => RemoteHostId -> m RemoteHostClient
getRemoteHostClient rhId = withRemoteHostSession rhKey $ \ case
s @ RHSessionConnected { rhClient } -> Right ( rhClient , s )
_ -> Left $ ChatErrorRemoteHost rhKey RHEBadState
2023-10-15 14:17:36 +01:00
where
2023-11-08 22:13:52 +02:00
rhKey = RHId rhId
2023-10-22 11:42:19 +03:00
2023-11-08 22:13:52 +02:00
withRemoteHostSession :: ChatMonad m => RHKey -> ( RemoteHostSession -> Either ChatError ( a , RemoteHostSession ) ) -> m a
withRemoteHostSession rhKey state = withRemoteHostSession_ rhKey $ maybe ( Left $ ChatErrorRemoteHost rhKey $ RHEMissing ) ( ( second . second ) Just . state )
withRemoteHostSession_ :: ChatMonad m => RHKey -> ( Maybe RemoteHostSession -> Either ChatError ( a , Maybe RemoteHostSession ) ) -> m a
withRemoteHostSession_ rhKey state = do
sessions <- asks remoteHostSessions
r <- atomically $ do
s <- TM . lookup rhKey sessions
case state s of
Left e -> pure $ Left e
Right ( a , s' ) -> Right a <$ maybe ( TM . delete rhKey ) ( TM . insert rhKey ) s' sessions
liftEither r
setNewRemoteHostId :: ChatMonad m => RHKey -> RemoteHostId -> m ()
setNewRemoteHostId rhKey rhId = do
2023-10-22 11:42:19 +03:00
sessions <- asks remoteHostSessions
2023-11-08 22:13:52 +02:00
r <- atomically $ do
TM . lookupDelete rhKey sessions >>= \ case
Nothing -> pure $ Left $ ChatErrorRemoteHost rhKey RHEMissing
Just s -> Right () <$ TM . insert ( RHId rhId ) s sessions
liftEither r
2023-11-11 16:03:12 +00:00
startRemoteHost :: ChatMonad m => Maybe ( RemoteHostId , Bool ) -> m ( Maybe RemoteHostInfo , RCSignedInvitation )
startRemoteHost rh_ = do
2023-11-08 22:13:52 +02:00
( rhKey , multicast , remoteHost_ , pairing ) <- case rh_ of
Just ( rhId , multicast ) -> do
rh @ RemoteHost { hostPairing } <- withStore $ \ db -> getRemoteHost db rhId
2023-11-13 20:16:34 +00:00
pure ( RHId rhId , multicast , Just $ remoteHostInfo rh $ Just RHSStarting , hostPairing ) -- get from the database, start multicast if requested
2023-11-08 22:13:52 +02:00
Nothing -> ( RHNew , False , Nothing , ) <$> rcNewHostPairing
withRemoteHostSession_ rhKey $ maybe ( Right ( () , Just RHSessionStarting ) ) ( \ _ -> Left $ ChatErrorRemoteHost rhKey RHEBusy )
ctrlAppInfo <- mkCtrlAppInfo
2023-11-20 11:33:43 +02:00
( invitation , rchClient , vars ) <- handleConnectError rhKey . withAgent $ \ a -> rcConnectHost a pairing ( J . toJSON ctrlAppInfo ) multicast
2023-11-09 20:25:05 +02:00
cmdOk <- newEmptyTMVarIO
rhsWaitSession <- async $ do
2023-11-11 16:03:12 +00:00
rhKeyVar <- newTVarIO rhKey
2023-11-09 20:25:05 +02:00
atomically $ takeTMVar cmdOk
2023-11-11 16:03:12 +00:00
handleHostError rhKeyVar $ waitForHostSession remoteHost_ rhKey rhKeyVar vars
2023-11-08 22:13:52 +02:00
let rhs = RHPendingSession { rhKey , rchClient , rhsWaitSession , remoteHost_ }
withRemoteHostSession rhKey $ \ case
2023-11-13 20:16:34 +00:00
RHSessionStarting ->
let inv = decodeLatin1 $ strEncode invitation
in Right ( () , RHSessionConnecting inv rhs )
2023-11-08 22:13:52 +02:00
_ -> Left $ ChatErrorRemoteHost rhKey RHEBadState
2023-11-09 20:25:05 +02:00
( remoteHost_ , invitation ) <$ atomically ( putTMVar cmdOk () )
2023-10-07 16:23:24 +03:00
where
2023-11-08 22:13:52 +02:00
mkCtrlAppInfo = do
deviceName <- chatReadVar localDeviceName
pure CtrlAppInfo { appVersionRange = ctrlAppVersionRange , deviceName }
2023-11-09 09:37:56 +00:00
parseHostAppInfo :: RCHostHello -> ExceptT RemoteHostError IO HostAppInfo
parseHostAppInfo RCHostHello { app = hostAppInfo } = do
2023-11-09 20:25:05 +02:00
hostInfo @ HostAppInfo { appVersion , encoding } <-
2023-11-09 09:37:56 +00:00
liftEitherWith ( RHEProtocolError . RPEInvalidJSON ) $ JT . parseEither J . parseJSON hostAppInfo
unless ( isAppCompatible appVersion ctrlAppVersionRange ) $ throwError $ RHEBadVersion appVersion
when ( encoding == PEKotlin && localEncoding == PESwift ) $ throwError $ RHEProtocolError RPEIncompatibleEncoding
pure hostInfo
2023-11-20 11:33:43 +02:00
handleConnectError :: ChatMonad m => RHKey -> m a -> m a
handleConnectError rhKey action = action ` catchChatError ` \ err -> do
logError $ " startRemoteHost.rcConnectHost crashed: " <> tshow err
cancelRemoteHostSession True rhKey
throwError err
2023-11-11 16:03:12 +00:00
handleHostError :: ChatMonad m => TVar RHKey -> m () -> m ()
2023-11-15 19:31:36 +02:00
handleHostError rhKeyVar action = action ` catchChatError ` \ err -> do
logError $ " startRemoteHost.waitForHostSession crashed: " <> tshow err
2023-11-16 16:56:39 +02:00
readTVarIO rhKeyVar >>= cancelRemoteHostSession True
2023-11-13 20:16:34 +00:00
waitForHostSession :: ChatMonad m => Maybe RemoteHostInfo -> RHKey -> TVar RHKey -> RCStepTMVar ( ByteString , TLS , RCStepTMVar ( RCHostSession , RCHostHello , RCHostPairing ) ) -> m ()
2023-11-11 16:03:12 +00:00
waitForHostSession remoteHost_ rhKey rhKeyVar vars = do
2023-11-16 16:56:39 +02:00
( sessId , tls , vars' ) <- timeoutThrow ( ChatErrorRemoteHost rhKey RHETimeout ) 60000000 $ takeRCStep vars
2023-11-15 13:17:31 +00:00
let sessionCode = verificationCode sessId
2023-11-13 20:16:34 +00:00
withRemoteHostSession rhKey $ \ case
2023-11-15 13:17:31 +00:00
RHSessionConnecting _inv rhs' -> Right ( () , RHSessionPendingConfirmation sessionCode tls rhs' ) -- TODO check it's the same session?
2023-11-13 20:16:34 +00:00
_ -> Left $ ChatErrorRemoteHost rhKey RHEBadState
2023-11-14 22:27:21 +00:00
-- display confirmation code, wait for mobile to confirm
2023-11-15 13:17:31 +00:00
let rh_' = ( \ rh -> ( rh :: RemoteHostInfo ) { sessionState = Just $ RHSPendingConfirmation { sessionCode } } ) <$> remoteHost_
toView $ CRRemoteHostSessionCode { remoteHost_ = rh_' , sessionCode }
2023-11-16 16:56:39 +02:00
( RCHostSession { sessionKeys } , rhHello , pairing' ) <- timeoutThrow ( ChatErrorRemoteHost rhKey RHETimeout ) 60000000 $ takeRCStep vars'
2023-11-09 09:37:56 +00:00
hostInfo @ HostAppInfo { deviceName = hostDeviceName } <-
liftError ( ChatErrorRemoteHost rhKey ) $ parseHostAppInfo rhHello
2023-11-08 22:13:52 +02:00
withRemoteHostSession rhKey $ \ case
2023-11-13 20:16:34 +00:00
RHSessionPendingConfirmation _ tls' rhs' -> Right ( () , RHSessionConfirmed tls' rhs' ) -- TODO check it's the same session?
2023-11-09 20:25:05 +02:00
_ -> Left $ ChatErrorRemoteHost rhKey RHEBadState
2023-11-08 22:13:52 +02:00
-- update remoteHost with updated pairing
2023-11-15 13:17:31 +00:00
rhi @ RemoteHostInfo { remoteHostId , storePath } <- upsertRemoteHost pairing' rh_' hostDeviceName RHSConfirmed { sessionCode }
2023-11-09 20:25:05 +02:00
let rhKey' = RHId remoteHostId -- rhKey may be invalid after upserting on RHNew
2023-11-12 21:43:43 +00:00
when ( rhKey' /= rhKey ) $ do
atomically $ writeTVar rhKeyVar rhKey'
toView $ CRNewRemoteHost rhi
2023-11-15 19:31:36 +02:00
disconnected <- toIO $ onDisconnected rhKey'
2023-11-09 20:25:05 +02:00
httpClient <- liftEitherError ( httpError rhKey' ) $ attachRevHTTP2Client disconnected tls
2023-11-10 16:10:10 +00:00
rhClient <- mkRemoteHostClient httpClient sessionKeys sessId storePath hostInfo
2023-11-08 22:13:52 +02:00
pollAction <- async $ pollEvents remoteHostId rhClient
withRemoteHostSession rhKey' $ \ case
2023-11-13 20:39:41 +02:00
RHSessionConfirmed _ RHPendingSession { rchClient } -> Right ( () , RHSessionConnected { rchClient , tls , rhClient , pollAction , storePath } )
2023-11-09 20:25:05 +02:00
_ -> Left $ ChatErrorRemoteHost rhKey' RHEBadState
2023-11-08 22:13:52 +02:00
chatWriteVar currentRemoteHost $ Just remoteHostId -- this is required for commands to be passed to remote host
2023-11-15 13:17:31 +00:00
toView $ CRRemoteHostConnected rhi { sessionState = Just RHSConnected { sessionCode } }
2023-11-13 20:16:34 +00:00
upsertRemoteHost :: ChatMonad m => RCHostPairing -> Maybe RemoteHostInfo -> Text -> RemoteHostSessionState -> m RemoteHostInfo
upsertRemoteHost pairing' @ RCHostPairing { knownHost = kh_ } rhi_ hostDeviceName state = do
2023-11-08 22:13:52 +02:00
KnownHostPairing { hostDhPubKey = hostDhPubKey' } <- maybe ( throwError . ChatError $ CEInternalError " KnownHost is known after verification " ) pure kh_
2023-11-09 20:25:05 +02:00
case rhi_ of
2023-11-08 22:13:52 +02:00
Nothing -> do
storePath <- liftIO randomStorePath
rh @ RemoteHost { remoteHostId } <- withStore $ \ db -> insertRemoteHost db hostDeviceName storePath pairing' >>= getRemoteHost db
setNewRemoteHostId RHNew remoteHostId
2023-11-13 20:16:34 +00:00
pure $ remoteHostInfo rh $ Just state
2023-11-08 22:13:52 +02:00
Just rhi @ RemoteHostInfo { remoteHostId } -> do
withStore' $ \ db -> updateHostPairing db remoteHostId hostDeviceName hostDhPubKey'
2023-11-13 20:16:34 +00:00
pure ( rhi :: RemoteHostInfo ) { sessionState = Just state }
2023-11-15 19:31:36 +02:00
onDisconnected :: ChatMonad m => RHKey -> m ()
onDisconnected rhKey = do
2023-11-08 22:13:52 +02:00
logDebug " HTTP2 client disconnected "
2023-11-16 16:56:39 +02:00
cancelRemoteHostSession True rhKey
2023-11-08 22:13:52 +02:00
pollEvents :: ChatMonad m => RemoteHostId -> RemoteHostClient -> m ()
pollEvents rhId rhClient = do
2023-10-15 14:17:36 +01:00
oq <- asks outputQ
2023-11-08 22:13:52 +02:00
forever $ do
r_ <- liftRH rhId $ remoteRecv rhClient 10000000
forM r_ $ \ r -> atomically $ writeTBQueue oq ( Nothing , Just rhId , r )
httpError :: RHKey -> HTTP2ClientError -> ChatError
httpError rhKey = ChatErrorRemoteHost rhKey . RHEProtocolError . RPEHTTP2 . tshow
closeRemoteHost :: ChatMonad m => RHKey -> m ()
closeRemoteHost rhKey = do
logNote $ " Closing remote host session for " <> tshow rhKey
2023-11-16 16:56:39 +02:00
cancelRemoteHostSession False rhKey
2023-11-15 19:31:36 +02:00
2023-11-16 16:56:39 +02:00
cancelRemoteHostSession :: ChatMonad m => Bool -> RHKey -> m ()
cancelRemoteHostSession handlingError rhKey = handleAny ( logError . tshow ) $ do
2023-11-08 22:13:52 +02:00
chatModifyVar currentRemoteHost $ \ cur -> if ( RHId <$> cur ) == Just rhKey then Nothing else cur -- only wipe the closing RH
2023-11-15 19:31:36 +02:00
sessions <- asks remoteHostSessions
2023-11-16 16:56:39 +02:00
session_ <- atomically $ TM . lookupDelete rhKey sessions -- XXX: when invoked from delayed error handler this can wipe the next session instead
2023-11-15 19:31:36 +02:00
forM_ session_ $ \ session -> do
2023-11-16 16:56:39 +02:00
liftIO $ cancelRemoteHost handlingError session ` catchAny ` ( logError . tshow )
when handlingError $ toView $ CRRemoteHostStopped rhId_
2023-11-15 19:31:36 +02:00
where
rhId_ = case rhKey of
RHNew -> Nothing
RHId rhId -> Just rhId
2023-11-08 22:13:52 +02:00
2023-11-15 19:31:36 +02:00
cancelRemoteHost :: Bool -> RemoteHostSession -> IO ()
2023-11-16 16:56:39 +02:00
cancelRemoteHost handlingError = \ case
2023-11-08 22:13:52 +02:00
RHSessionStarting -> pure ()
2023-11-13 20:16:34 +00:00
RHSessionConnecting _inv rhs -> cancelPendingSession rhs
RHSessionPendingConfirmation _sessCode tls rhs -> do
cancelPendingSession rhs
closeConnection tls
2023-11-10 00:43:44 +02:00
RHSessionConfirmed tls rhs -> do
cancelPendingSession rhs
closeConnection tls
2023-11-13 20:39:41 +02:00
RHSessionConnected { rchClient , tls , rhClient = RemoteHostClient { httpClient } , pollAction } -> do
2023-11-08 22:13:52 +02:00
uninterruptibleCancel pollAction
2023-11-15 19:31:36 +02:00
cancelHostClient rchClient ` catchAny ` ( logError . tshow )
2023-11-16 16:56:39 +02:00
closeConnection tls ` catchAny ` ( logError . tshow )
unless handlingError $ closeHTTP2Client httpClient ` catchAny ` ( logError . tshow )
2023-11-08 22:13:52 +02:00
where
cancelPendingSession RHPendingSession { rchClient , rhsWaitSession } = do
2023-11-16 16:56:39 +02:00
unless handlingError $ uninterruptibleCancel rhsWaitSession ` catchAny ` ( logError . tshow )
cancelHostClient rchClient ` catchAny ` ( logError . tshow )
2023-10-04 18:36:10 +03:00
-- | Generate a random 16-char filepath without / in it by using base64url encoding.
randomStorePath :: IO FilePath
randomStorePath = B . unpack . B64U . encode <$> getRandomBytes 12
2023-10-15 14:17:36 +01:00
listRemoteHosts :: ChatMonad m => m [ RemoteHostInfo ]
2023-10-04 18:36:10 +03:00
listRemoteHosts = do
2023-11-13 20:16:34 +00:00
sessions <- chatReadVar remoteHostSessions
map ( rhInfo sessions ) <$> withStore' getRemoteHosts
2023-10-14 13:10:06 +01:00
where
2023-11-13 20:16:34 +00:00
rhInfo sessions rh @ RemoteHost { remoteHostId } =
remoteHostInfo rh ( rhsSessionState <$> M . lookup ( RHId remoteHostId ) sessions )
2023-10-15 00:18:04 +01:00
2023-11-10 19:49:23 +02:00
switchRemoteHost :: ChatMonad m => Maybe RemoteHostId -> m ( Maybe RemoteHostInfo )
switchRemoteHost rhId_ = do
rhi_ <- forM rhId_ $ \ rhId -> do
let rhKey = RHId rhId
2023-11-13 20:16:34 +00:00
rh <- withStore ( ` getRemoteHost ` rhId )
sessions <- chatReadVar remoteHostSessions
case M . lookup rhKey sessions of
2023-11-15 13:17:31 +00:00
Just RHSessionConnected { tls } -> pure $ remoteHostInfo rh $ Just RHSConnected { sessionCode = tlsSessionCode tls }
2023-11-10 19:49:23 +02:00
_ -> throwError $ ChatErrorRemoteHost rhKey RHEInactive
rhi_ <$ chatWriteVar currentRemoteHost rhId_
2023-11-13 20:16:34 +00:00
remoteHostInfo :: RemoteHost -> Maybe RemoteHostSessionState -> RemoteHostInfo
remoteHostInfo RemoteHost { remoteHostId , storePath , hostDeviceName } sessionState =
RemoteHostInfo { remoteHostId , storePath , hostDeviceName , sessionState }
2023-10-04 18:36:10 +03:00
2023-10-15 14:17:36 +01:00
deleteRemoteHost :: ChatMonad m => RemoteHostId -> m ()
deleteRemoteHost rhId = do
RemoteHost { storePath } <- withStore ( ` getRemoteHost ` rhId )
2023-11-15 17:57:29 +02:00
chatReadVar remoteHostsFolder >>= \ case
2023-10-13 20:53:04 +03:00
Just baseDir -> do
let hostStore = baseDir </> storePath
2023-11-15 15:09:52 +02:00
logInfo $ " removing host store at " <> tshow hostStore
2023-11-15 17:57:29 +02:00
whenM ( doesDirectoryExist hostStore ) $ removeDirectoryRecursive hostStore
2023-10-13 20:53:04 +03:00
Nothing -> logWarn " Local file store not available while deleting remote host "
2023-10-15 14:17:36 +01:00
withStore' ( ` deleteRemoteHostRecord ` rhId )
2023-10-29 19:06:32 +00:00
storeRemoteFile :: forall m . ChatMonad m => RemoteHostId -> Maybe Bool -> FilePath -> m CryptoFile
storeRemoteFile rhId encrypted_ localPath = do
2023-11-08 22:13:52 +02:00
c @ RemoteHostClient { encryptHostFiles , storePath } <- getRemoteHostClient rhId
let encrypt = fromMaybe encryptHostFiles encrypted_
cf @ CryptoFile { filePath } <- if encrypt then encryptLocalFile else pure $ CF . plain localPath
filePath' <- liftRH rhId $ remoteStoreFile c filePath ( takeFileName localPath )
hf_ <- chatReadVar remoteHostsFolder
forM_ hf_ $ \ hf -> do
let rhf = hf </> storePath </> archiveFilesFolder
hPath = rhf </> takeFileName filePath'
createDirectoryIfMissing True rhf
( if encrypt then renameFile else copyFile ) filePath hPath
pure ( cf :: CryptoFile ) { filePath = filePath' }
2023-10-29 19:06:32 +00:00
where
encryptLocalFile :: m CryptoFile
encryptLocalFile = do
tmpDir <- getChatTempDirectory
createDirectoryIfMissing True tmpDir
tmpFile <- tmpDir ` uniqueCombine ` takeFileName localPath
cfArgs <- liftIO CF . randomArgs
liftError ( ChatError . CEFileWrite tmpFile ) $ encryptFile localPath tmpFile cfArgs
pure $ CryptoFile tmpFile $ Just cfArgs
getRemoteFile :: ChatMonad m => RemoteHostId -> RemoteFile -> m ()
getRemoteFile rhId rf = do
2023-11-08 22:13:52 +02:00
c @ RemoteHostClient { storePath } <- getRemoteHostClient rhId
dir <- ( </> storePath </> archiveFilesFolder ) <$> ( maybe getDefaultFilesFolder pure =<< chatReadVar remoteHostsFolder )
createDirectoryIfMissing True dir
liftRH rhId $ remoteGetFile c dir rf
processRemoteCommand :: ChatMonad m => RemoteHostId -> RemoteHostClient -> ChatCommand -> ByteString -> m ChatResponse
processRemoteCommand remoteHostId c cmd s = case cmd of
2023-10-29 19:06:32 +00:00
SendFile chatName f -> sendFile " /f " chatName f
2023-10-30 16:00:54 +02:00
SendImage chatName f -> sendFile " /img " chatName f
2023-11-08 22:13:52 +02:00
_ -> liftRH remoteHostId $ remoteSend c s
2023-10-29 19:06:32 +00:00
where
sendFile cmdName chatName ( CryptoFile path cfArgs ) = do
-- don't encrypt in host if already encrypted locally
CryptoFile path' cfArgs' <- storeRemoteFile remoteHostId ( cfArgs $> False ) path
let f = CryptoFile path' ( cfArgs <|> cfArgs' ) -- use local or host encryption
2023-11-08 22:13:52 +02:00
liftRH remoteHostId $ remoteSend c $ B . unwords [ cmdName , B . pack ( chatNameStr chatName ) , cryptoFileStr f ]
2023-10-29 19:06:32 +00:00
cryptoFileStr CryptoFile { filePath , cryptoArgs } =
maybe " " ( \ ( CFArgs key nonce ) -> " key= " <> strEncode key <> " nonce= " <> strEncode nonce <> " " ) cryptoArgs
<> encodeUtf8 ( T . pack filePath )
2023-10-07 16:23:24 +03:00
2023-10-22 11:42:19 +03:00
liftRH :: ChatMonad m => RemoteHostId -> ExceptT RemoteProtocolError IO a -> m a
2023-11-08 22:13:52 +02:00
liftRH rhId = liftError ( ChatErrorRemoteHost ( RHId rhId ) . RHEProtocolError )
2023-09-29 14:56:56 +03:00
2023-10-22 11:42:19 +03:00
-- * Mobile side
2023-09-29 14:56:56 +03:00
2023-11-17 20:50:38 +02:00
-- ** QR/link
2023-11-08 22:13:52 +02:00
-- | Use provided OOB link as an annouce
2023-11-17 20:50:38 +02:00
connectRemoteCtrlURI :: ChatMonad m => RCSignedInvitation -> m ( Maybe RemoteCtrlInfo , CtrlAppInfo )
connectRemoteCtrlURI signedInv = handleCtrlError " connectRemoteCtrl " $ do
verifiedInv <- maybe ( throwError $ ChatErrorRemoteCtrl RCEBadInvitation ) pure $ verifySignedInvitation signedInv
2023-11-08 22:13:52 +02:00
withRemoteCtrlSession_ $ maybe ( Right ( () , Just RCSessionStarting ) ) ( \ _ -> Left $ ChatErrorRemoteCtrl RCEBusy )
2023-11-17 20:50:38 +02:00
connectRemoteCtrl verifiedInv
-- ** Multicast
findKnownRemoteCtrl :: ChatMonad m => m ()
findKnownRemoteCtrl = handleCtrlError " findKnownRemoteCtrl " $ do
knownCtrls <- withStore' getRemoteCtrls
pairings <- case nonEmpty knownCtrls of
Nothing -> throwError $ ChatErrorRemoteCtrl RCENoKnownControllers
Just ne -> pure $ fmap ( \ RemoteCtrl { ctrlPairing } -> ctrlPairing ) ne
withRemoteCtrlSession_ $ maybe ( Right ( () , Just RCSessionStarting ) ) ( \ _ -> Left $ ChatErrorRemoteCtrl RCEBusy )
foundCtrl <- newEmptyTMVarIO
cmdOk <- newEmptyTMVarIO
action <- async $ handleCtrlError " findKnownRemoteCtrl.discover " $ do
atomically $ takeTMVar cmdOk
( RCCtrlPairing { ctrlFingerprint } , inv ) <- timeoutThrow ( ChatErrorRemoteCtrl RCETimeout ) discoveryTimeout . withAgent $ \ a -> rcDiscoverCtrl a pairings
rc <- withStore' ( ` getRemoteCtrlByFingerprint ` ctrlFingerprint ) >>= \ case
Nothing -> throwChatError $ CEInternalError " connecting with a stored ctrl "
Just rc -> pure rc
atomically $ putTMVar foundCtrl ( rc , inv )
toView CRRemoteCtrlFound { remoteCtrl = remoteCtrlInfo rc ( Just RCSSearching ) }
withRemoteCtrlSession $ \ case
RCSessionStarting -> Right ( () , RCSessionSearching { action , foundCtrl } )
_ -> Left $ ChatErrorRemoteCtrl RCEBadState
atomically $ putTMVar cmdOk ()
confirmRemoteCtrl :: ChatMonad m => RemoteCtrlId -> m ( RemoteCtrlInfo , CtrlAppInfo )
confirmRemoteCtrl rcId = do
( listener , found ) <- withRemoteCtrlSession $ \ case
RCSessionSearching { action , foundCtrl } -> Right ( ( action , foundCtrl ) , RCSessionStarting ) -- drop intermediate "Searching" state so connectRemoteCtrl can proceed
_ -> throwError $ ChatErrorRemoteCtrl RCEBadState
uninterruptibleCancel listener
( RemoteCtrl { remoteCtrlId = foundRcId } , verifiedInv ) <- atomically $ takeTMVar found
unless ( rcId == foundRcId ) $ throwError $ ChatErrorRemoteCtrl RCEBadController
connectRemoteCtrl verifiedInv >>= \ case
( Nothing , _ ) -> throwChatError $ CEInternalError " connecting with a stored ctrl "
( Just rci , appInfo ) -> pure ( rci , appInfo )
-- ** Common
connectRemoteCtrl :: ChatMonad m => RCVerifiedInvitation -> m ( Maybe RemoteCtrlInfo , CtrlAppInfo )
connectRemoteCtrl verifiedInv @ ( RCVerifiedInvitation inv @ RCInvitation { ca , app } ) = handleCtrlError " connectRemoteCtrl " $ do
( ctrlInfo @ CtrlAppInfo { deviceName = ctrlDeviceName } , v ) <- parseCtrlAppInfo app
2023-11-08 22:13:52 +02:00
rc_ <- withStore' $ \ db -> getRemoteCtrlByFingerprint db ca
2023-11-12 14:40:49 +00:00
mapM_ ( validateRemoteCtrl inv ) rc_
2023-11-08 22:13:52 +02:00
hostAppInfo <- getHostAppInfo v
2023-11-13 20:39:41 +02:00
( rcsClient , vars ) <- timeoutThrow ( ChatErrorRemoteCtrl RCETimeout ) networkIOTimeout . withAgent $ \ a ->
2023-11-17 20:50:38 +02:00
rcConnectCtrl a verifiedInv ( ctrlPairing <$> rc_ ) ( J . toJSON hostAppInfo )
2023-11-09 20:25:05 +02:00
cmdOk <- newEmptyTMVarIO
rcsWaitSession <- async $ do
atomically $ takeTMVar cmdOk
2023-11-11 16:03:12 +00:00
handleCtrlError " waitForCtrlSession " $ waitForCtrlSession rc_ ctrlDeviceName rcsClient vars
2023-11-12 14:40:49 +00:00
updateRemoteCtrlSession $ \ case
2023-11-15 13:17:31 +00:00
RCSessionStarting -> Right RCSessionConnecting { remoteCtrlId_ = remoteCtrlId' <$> rc_ , rcsClient , rcsWaitSession }
2023-11-09 20:25:05 +02:00
_ -> Left $ ChatErrorRemoteCtrl RCEBadState
atomically $ putTMVar cmdOk ()
2023-11-15 13:17:31 +00:00
pure ( ( ` remoteCtrlInfo ` Just RCSConnecting ) <$> rc_ , ctrlInfo )
2023-11-08 22:13:52 +02:00
where
2023-11-12 14:40:49 +00:00
validateRemoteCtrl RCInvitation { idkey } RemoteCtrl { ctrlPairing = RCCtrlPairing { idPubKey } } =
unless ( idkey == idPubKey ) $ throwError $ ChatErrorRemoteCtrl $ RCEProtocolError $ PRERemoteControl RCEIdentity
2023-11-11 16:03:12 +00:00
waitForCtrlSession :: ChatMonad m => Maybe RemoteCtrl -> Text -> RCCtrlClient -> RCStepTMVar ( ByteString , TLS , RCStepTMVar ( RCCtrlSession , RCCtrlPairing ) ) -> m ()
waitForCtrlSession rc_ ctrlName rcsClient vars = do
2023-11-13 20:39:41 +02:00
( uniq , tls , rcsWaitConfirmation ) <- timeoutThrow ( ChatErrorRemoteCtrl RCETimeout ) networkIOTimeout $ takeRCStep vars
2023-11-08 22:13:52 +02:00
let sessionCode = verificationCode uniq
updateRemoteCtrlSession $ \ case
2023-11-15 13:17:31 +00:00
RCSessionConnecting { rcsWaitSession } ->
let remoteCtrlId_ = remoteCtrlId' <$> rc_
in Right RCSessionPendingConfirmation { remoteCtrlId_ , ctrlDeviceName = ctrlName , rcsClient , tls , sessionCode , rcsWaitSession , rcsWaitConfirmation }
2023-11-09 20:25:05 +02:00
_ -> Left $ ChatErrorRemoteCtrl RCEBadState
2023-11-15 13:17:31 +00:00
toView CRRemoteCtrlSessionCode { remoteCtrl_ = ( ` remoteCtrlInfo ` Just RCSPendingConfirmation { sessionCode } ) <$> rc_ , sessionCode }
2023-11-08 22:13:52 +02:00
parseCtrlAppInfo ctrlAppInfo = do
2023-11-12 14:40:49 +00:00
ctrlInfo @ CtrlAppInfo { appVersionRange } <-
2023-11-08 22:13:52 +02:00
liftEitherWith ( const $ ChatErrorRemoteCtrl RCEBadInvitation ) $ JT . parseEither J . parseJSON ctrlAppInfo
v <- case compatibleAppVersion hostAppVersionRange appVersionRange of
Just ( AppCompatible v ) -> pure v
Nothing -> throwError $ ChatErrorRemoteCtrl $ RCEBadVersion $ maxVersion appVersionRange
2023-11-12 14:40:49 +00:00
pure ( ctrlInfo , v )
2023-11-08 22:13:52 +02:00
getHostAppInfo appVersion = do
hostDeviceName <- chatReadVar localDeviceName
encryptFiles <- chatReadVar encryptLocalFiles
pure HostAppInfo { appVersion , deviceName = hostDeviceName , encoding = localEncoding , encryptFiles }
2023-11-10 16:10:10 +00:00
handleRemoteCommand :: forall m . ChatMonad m => ( ByteString -> m ChatResponse ) -> RemoteCrypto -> TBQueue ChatResponse -> HTTP2Request -> m ()
handleRemoteCommand execChatCommand encryption remoteOutputQ HTTP2Request { request , reqBody , sendResponse } = do
2023-10-22 11:42:19 +03:00
logDebug " handleRemoteCommand "
liftRC ( tryRemoteError parseRequest ) >>= \ case
2023-10-29 19:06:32 +00:00
Right ( getNext , rc ) -> do
chatReadVar currentUser >>= \ case
Nothing -> replyError $ ChatError CENoActiveUser
Just user -> processCommand user getNext rc ` catchChatError ` replyError
2023-10-22 11:42:19 +03:00
Left e -> reply $ RRProtocolError e
2023-10-15 14:17:36 +01:00
where
2023-10-22 11:42:19 +03:00
parseRequest :: ExceptT RemoteProtocolError IO ( GetChunk , RemoteCommand )
parseRequest = do
2023-11-10 16:10:10 +00:00
( header , getNext ) <- parseDecryptHTTP2Body encryption request reqBody
( getNext , ) <$> liftEitherWith RPEInvalidJSON ( J . eitherDecode header )
2023-10-29 19:06:32 +00:00
replyError = reply . RRChatResponse . CRChatCmdError Nothing
processCommand :: User -> GetChunk -> RemoteCommand -> m ()
processCommand user getNext = \ case
2023-10-22 11:42:19 +03:00
RCSend { command } -> handleSend execChatCommand command >>= reply
RCRecv { wait = time } -> handleRecv time remoteOutputQ >>= reply
2023-11-14 16:44:12 +00:00
RCStoreFile { fileName , fileSize , fileDigest } -> handleStoreFile encryption fileName fileSize fileDigest getNext >>= reply
RCGetFile { file } -> handleGetFile encryption user file replyWith
2023-10-22 11:42:19 +03:00
reply :: RemoteResponse -> m ()
reply = ( ` replyWith ` \ _ -> pure () )
replyWith :: Respond m
2023-11-10 16:10:10 +00:00
replyWith rr attach = do
resp <- liftRC $ encryptEncodeHTTP2Body encryption $ J . encode rr
2023-10-22 11:42:19 +03:00
liftIO . sendResponse . responseStreaming N . status200 [] $ \ send flush -> do
2023-11-10 16:10:10 +00:00
send resp
2023-10-22 11:42:19 +03:00
attach send
flush
2023-11-08 22:13:52 +02:00
takeRCStep :: ChatMonad m => RCStepTMVar a -> m a
takeRCStep = liftEitherError ( \ e -> ChatErrorAgent { agentError = RCP e , connectionEntity_ = Nothing } ) . atomically . takeTMVar
2023-10-22 11:42:19 +03:00
type GetChunk = Int -> IO ByteString
type SendChunk = Builder -> IO ()
type Respond m = RemoteResponse -> ( SendChunk -> IO () ) -> m ()
liftRC :: ChatMonad m => ExceptT RemoteProtocolError IO a -> m a
liftRC = liftError ( ChatErrorRemoteCtrl . RCEProtocolError )
tryRemoteError :: ExceptT RemoteProtocolError IO a -> ExceptT RemoteProtocolError IO ( Either RemoteProtocolError a )
tryRemoteError = tryAllErrors ( RPEException . tshow )
{- # INLINE tryRemoteError # -}
handleSend :: ChatMonad m => ( ByteString -> m ChatResponse ) -> Text -> m RemoteResponse
handleSend execChatCommand command = do
logDebug $ " Send: " <> tshow command
-- execChatCommand checks for remote-allowed commands
-- convert errors thrown in ChatMonad into error responses to prevent aborting the protocol wrapper
RRChatResponse <$> execChatCommand ( encodeUtf8 command ) ` catchError ` ( pure . CRChatError Nothing )
handleRecv :: MonadUnliftIO m => Int -> TBQueue ChatResponse -> m RemoteResponse
handleRecv time events = do
logDebug $ " Recv: " <> tshow time
RRChatEvent <$> ( timeout time . atomically $ readTBQueue events )
2023-10-29 19:06:32 +00:00
-- TODO this command could remember stored files and return IDs to allow removing files that are not needed.
-- Also, there should be some process removing unused files uploaded to remote host (possibly, all unused files).
2023-11-14 16:44:12 +00:00
handleStoreFile :: forall m . ChatMonad m => RemoteCrypto -> FilePath -> Word32 -> FileDigest -> GetChunk -> m RemoteResponse
handleStoreFile encryption fileName fileSize fileDigest getChunk =
2023-10-29 19:06:32 +00:00
either RRProtocolError RRFileStored <$> ( chatReadVar filesFolder >>= storeFile )
where
storeFile :: Maybe FilePath -> m ( Either RemoteProtocolError FilePath )
storeFile = \ case
Just ff -> takeFileName <$$> storeFileTo ff
Nothing -> storeFileTo =<< getDefaultFilesFolder
storeFileTo :: FilePath -> m ( Either RemoteProtocolError FilePath )
storeFileTo dir = liftRC . tryRemoteError $ do
filePath <- dir ` uniqueCombine ` fileName
2023-11-14 16:44:12 +00:00
receiveEncryptedFile encryption getChunk fileSize fileDigest filePath
2023-10-29 19:06:32 +00:00
pure filePath
2023-11-14 16:44:12 +00:00
handleGetFile :: ChatMonad m => RemoteCrypto -> User -> RemoteFile -> Respond m -> m ()
handleGetFile encryption User { userId } RemoteFile { userId = commandUserId , fileId , sent , fileSource = cf' @ CryptoFile { filePath } } reply = do
2023-10-29 19:06:32 +00:00
logDebug $ " GetFile: " <> tshow filePath
unless ( userId == commandUserId ) $ throwChatError $ CEDifferentActiveUser { commandUserId , activeUserId = userId }
path <- maybe filePath ( </> filePath ) <$> chatReadVar filesFolder
withStore $ \ db -> do
cf <- getLocalCryptoFile db commandUserId fileId sent
unless ( cf == cf' ) $ throwError $ SEFileNotFound fileId
liftRC ( tryRemoteError $ getFileInfo path ) >>= \ case
Left e -> reply ( RRProtocolError e ) $ \ _ -> pure ()
Right ( fileSize , fileDigest ) ->
2023-11-14 16:44:12 +00:00
withFile path ReadMode $ \ h -> do
encFile <- liftRC $ prepareEncryptedFile encryption ( h , fileSize )
reply RRFile { fileSize , fileDigest } $ sendEncryptedFile encFile
2023-10-15 14:17:36 +01:00
listRemoteCtrls :: ChatMonad m => m [ RemoteCtrlInfo ]
2023-10-04 18:36:10 +03:00
listRemoteCtrls = do
2023-11-15 13:17:31 +00:00
session <- chatReadVar remoteCtrlSession
let rcId = sessionRcId =<< session
sessState = rcsSessionState <$> session
map ( rcInfo rcId sessState ) <$> withStore' getRemoteCtrls
2023-10-14 13:10:06 +01:00
where
2023-11-15 13:17:31 +00:00
rcInfo :: Maybe RemoteCtrlId -> Maybe RemoteCtrlSessionState -> RemoteCtrl -> RemoteCtrlInfo
rcInfo rcId sessState rc @ RemoteCtrl { remoteCtrlId } =
remoteCtrlInfo rc $ if rcId == Just remoteCtrlId then sessState else Nothing
sessionRcId = \ case
RCSessionConnecting { remoteCtrlId_ } -> remoteCtrlId_
RCSessionPendingConfirmation { remoteCtrlId_ } -> remoteCtrlId_
RCSessionConnected { remoteCtrlId } -> Just remoteCtrlId
_ -> Nothing
remoteCtrlInfo :: RemoteCtrl -> Maybe RemoteCtrlSessionState -> RemoteCtrlInfo
remoteCtrlInfo RemoteCtrl { remoteCtrlId , ctrlDeviceName } sessionState =
RemoteCtrlInfo { remoteCtrlId , ctrlDeviceName , sessionState }
2023-10-04 18:36:10 +03:00
2023-11-08 22:13:52 +02:00
-- | Take a look at emoji of tlsunique, commit pairing, and start session server
verifyRemoteCtrlSession :: ChatMonad m => ( ByteString -> m ChatResponse ) -> Text -> m RemoteCtrlInfo
2023-11-11 16:03:12 +00:00
verifyRemoteCtrlSession execChatCommand sessCode' = handleCtrlError " verifyRemoteCtrlSession " $ do
2023-11-08 22:13:52 +02:00
( client , ctrlName , sessionCode , vars ) <-
getRemoteCtrlSession >>= \ case
2023-11-12 14:40:49 +00:00
RCSessionPendingConfirmation { rcsClient , ctrlDeviceName = ctrlName , sessionCode , rcsWaitConfirmation } -> pure ( rcsClient , ctrlName , sessionCode , rcsWaitConfirmation )
2023-11-08 22:13:52 +02:00
_ -> throwError $ ChatErrorRemoteCtrl RCEBadState
let verified = sameVerificationCode sessCode' sessionCode
2023-11-13 20:39:41 +02:00
timeoutThrow ( ChatErrorRemoteCtrl RCETimeout ) networkIOTimeout . liftIO $ confirmCtrlSession client verified -- signal verification result before crashing
2023-11-10 16:10:10 +00:00
unless verified $ throwError $ ChatErrorRemoteCtrl $ RCEProtocolError PRESessionCode
2023-11-13 20:39:41 +02:00
( rcsSession @ RCCtrlSession { tls , sessionKeys } , rcCtrlPairing ) <- timeoutThrow ( ChatErrorRemoteCtrl RCETimeout ) networkIOTimeout $ takeRCStep vars
2023-11-09 20:25:05 +02:00
rc @ RemoteCtrl { remoteCtrlId } <- upsertRemoteCtrl ctrlName rcCtrlPairing
2023-11-08 22:13:52 +02:00
remoteOutputQ <- asks ( tbqSize . config ) >>= newTBQueueIO
2023-11-10 16:10:10 +00:00
encryption <- mkCtrlRemoteCrypto sessionKeys $ tlsUniq tls
http2Server <- async $ attachHTTP2Server tls $ handleRemoteCommand execChatCommand encryption remoteOutputQ
2023-11-09 20:25:05 +02:00
void . forkIO $ monitor http2Server
2023-11-08 22:13:52 +02:00
withRemoteCtrlSession $ \ case
2023-11-10 00:43:44 +02:00
RCSessionPendingConfirmation { } -> Right ( () , RCSessionConnected { remoteCtrlId , rcsClient = client , rcsSession , tls , http2Server , remoteOutputQ } )
2023-11-08 22:13:52 +02:00
_ -> Left $ ChatErrorRemoteCtrl RCEBadState
2023-11-15 13:17:31 +00:00
pure $ remoteCtrlInfo rc $ Just RCSConnected { sessionCode = tlsSessionCode tls }
2023-11-09 20:25:05 +02:00
where
upsertRemoteCtrl :: ChatMonad m => Text -> RCCtrlPairing -> m RemoteCtrl
upsertRemoteCtrl ctrlName rcCtrlPairing = withStore $ \ db -> do
rc_ <- liftIO $ getRemoteCtrlByFingerprint db ( ctrlFingerprint rcCtrlPairing )
case rc_ of
Nothing -> insertRemoteCtrl db ctrlName rcCtrlPairing >>= getRemoteCtrl db
2023-11-12 12:40:13 +00:00
Just rc @ RemoteCtrl { ctrlPairing } -> do
let dhPrivKey' = dhPrivKey rcCtrlPairing
liftIO $ updateRemoteCtrl db rc ctrlName dhPrivKey'
2023-11-12 14:40:49 +00:00
pure rc { ctrlDeviceName = ctrlName , ctrlPairing = ctrlPairing { dhPrivKey = dhPrivKey' } }
2023-11-10 00:43:44 +02:00
monitor :: ChatMonad m => Async () -> m ()
2023-11-09 20:25:05 +02:00
monitor server = do
2023-11-10 00:43:44 +02:00
res <- waitCatch server
logInfo $ " HTTP2 server stopped: " <> tshow res
2023-11-15 19:31:36 +02:00
cancelActiveRemoteCtrl True
2023-10-15 14:17:36 +01:00
stopRemoteCtrl :: ChatMonad m => m ()
2023-11-15 19:31:36 +02:00
stopRemoteCtrl = cancelActiveRemoteCtrl False
2023-11-08 22:13:52 +02:00
2023-11-11 16:03:12 +00:00
handleCtrlError :: ChatMonad m => Text -> m a -> m a
2023-11-17 20:50:38 +02:00
handleCtrlError name action =
action ` catchChatError ` \ e -> do
logError $ name <> " remote ctrl error: " <> tshow e
cancelActiveRemoteCtrl True
throwError e
2023-11-11 16:03:12 +00:00
2023-11-15 19:31:36 +02:00
cancelActiveRemoteCtrl :: ChatMonad m => Bool -> m ()
2023-11-16 16:56:39 +02:00
cancelActiveRemoteCtrl handlingError = handleAny ( logError . tshow ) $ do
2023-11-15 19:31:36 +02:00
session_ <- withRemoteCtrlSession_ ( \ s -> pure ( s , Nothing ) )
forM_ session_ $ \ session -> do
2023-11-16 16:56:39 +02:00
liftIO $ cancelRemoteCtrl handlingError session
when handlingError $ toView CRRemoteCtrlStopped
2023-11-11 16:03:12 +00:00
2023-11-16 16:56:39 +02:00
cancelRemoteCtrl :: Bool -> RemoteCtrlSession -> IO ()
cancelRemoteCtrl handlingError = \ case
2023-11-08 22:13:52 +02:00
RCSessionStarting -> pure ()
2023-11-17 20:50:38 +02:00
RCSessionSearching { action } -> uninterruptibleCancel action
2023-11-08 22:13:52 +02:00
RCSessionConnecting { rcsClient , rcsWaitSession } -> do
2023-11-16 16:56:39 +02:00
unless handlingError $ uninterruptibleCancel rcsWaitSession
2023-11-08 22:13:52 +02:00
cancelCtrlClient rcsClient
2023-11-10 00:43:44 +02:00
RCSessionPendingConfirmation { rcsClient , tls , rcsWaitSession } -> do
2023-11-16 16:56:39 +02:00
unless handlingError $ uninterruptibleCancel rcsWaitSession
2023-11-08 22:13:52 +02:00
cancelCtrlClient rcsClient
2023-11-10 00:43:44 +02:00
closeConnection tls
RCSessionConnected { rcsClient , tls , http2Server } -> do
2023-11-16 16:56:39 +02:00
unless handlingError $ uninterruptibleCancel http2Server
2023-11-10 00:43:44 +02:00
cancelCtrlClient rcsClient
closeConnection tls
2023-10-07 16:23:24 +03:00
2023-10-15 14:17:36 +01:00
deleteRemoteCtrl :: ChatMonad m => RemoteCtrlId -> m ()
deleteRemoteCtrl rcId = do
checkNoRemoteCtrlSession
-- TODO check it exists
withStore' ( ` deleteRemoteCtrlRecord ` rcId )
getRemoteCtrlSession :: ChatMonad m => m RemoteCtrlSession
getRemoteCtrlSession =
chatReadVar remoteCtrlSession >>= maybe ( throwError $ ChatErrorRemoteCtrl RCEInactive ) pure
checkNoRemoteCtrlSession :: ChatMonad m => m ()
checkNoRemoteCtrlSession =
chatReadVar remoteCtrlSession >>= maybe ( pure () ) ( \ _ -> throwError $ ChatErrorRemoteCtrl RCEBusy )
2023-10-11 11:45:05 +03:00
2023-11-08 22:13:52 +02:00
withRemoteCtrlSession :: ChatMonad m => ( RemoteCtrlSession -> Either ChatError ( a , RemoteCtrlSession ) ) -> m a
withRemoteCtrlSession state = withRemoteCtrlSession_ $ maybe ( Left $ ChatErrorRemoteCtrl RCEInactive ) ( ( second . second ) Just . state )
-- | Atomically process controller state wrt. specific remote ctrl session
withRemoteCtrlSession_ :: ChatMonad m => ( Maybe RemoteCtrlSession -> Either ChatError ( a , Maybe RemoteCtrlSession ) ) -> m a
withRemoteCtrlSession_ state = do
session <- asks remoteCtrlSession
r <-
atomically $ stateTVar session $ \ s ->
case state s of
Left e -> ( Left e , s )
Right ( a , s' ) -> ( Right a , s' )
liftEither r
updateRemoteCtrlSession :: ChatMonad m => ( RemoteCtrlSession -> Either ChatError RemoteCtrlSession ) -> m ()
updateRemoteCtrlSession state = withRemoteCtrlSession $ fmap ( () , ) . state
2023-10-11 11:45:05 +03:00
utf8String :: [ Char ] -> ByteString
utf8String = encodeUtf8 . T . pack
{- # INLINE utf8String # -}