Skip to content

Commit 0a82730

Browse files
authored
build: remove some modules from the client build (#1418)
* build: remove some modules from the client build * remove websockets from client_library
1 parent 79e9447 commit 0a82730

File tree

7 files changed

+86
-85
lines changed

7 files changed

+86
-85
lines changed

simplexmq.cabal

Lines changed: 13 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -73,7 +73,6 @@ library
7373
Simplex.FileTransfer.Chunks
7474
Simplex.FileTransfer.Client
7575
Simplex.FileTransfer.Client.Agent
76-
Simplex.FileTransfer.Client.Main
7776
Simplex.FileTransfer.Client.Presets
7877
Simplex.FileTransfer.Crypto
7978
Simplex.FileTransfer.Description
@@ -152,7 +151,6 @@ library
152151
Simplex.Messaging.Notifications.Types
153152
Simplex.Messaging.Parsers
154153
Simplex.Messaging.Protocol
155-
Simplex.Messaging.Server.CLI
156154
Simplex.Messaging.Server.Expiration
157155
Simplex.Messaging.Server.QueueStore.QueueInfo
158156
Simplex.Messaging.ServiceScheme
@@ -168,7 +166,6 @@ library
168166
Simplex.Messaging.Transport.HTTP2.Server
169167
Simplex.Messaging.Transport.KeepAlive
170168
Simplex.Messaging.Transport.Server
171-
Simplex.Messaging.Transport.WebSockets
172169
Simplex.Messaging.Util
173170
Simplex.Messaging.Version
174171
Simplex.Messaging.Version.Internal
@@ -179,14 +176,25 @@ library
179176
Simplex.RemoteControl.Types
180177
if !flag(client_library)
181178
exposed-modules:
179+
Simplex.FileTransfer.Client.Main
182180
Simplex.FileTransfer.Server
183181
Simplex.FileTransfer.Server.Control
184182
Simplex.FileTransfer.Server.Env
185183
Simplex.FileTransfer.Server.Main
186184
Simplex.FileTransfer.Server.Stats
187185
Simplex.FileTransfer.Server.Store
188186
Simplex.FileTransfer.Server.StoreLog
187+
Simplex.Messaging.Notifications.Server
188+
Simplex.Messaging.Notifications.Server.Control
189+
Simplex.Messaging.Notifications.Server.Env
190+
Simplex.Messaging.Notifications.Server.Main
191+
Simplex.Messaging.Notifications.Server.Push.APNS
192+
Simplex.Messaging.Notifications.Server.Push.APNS.Internal
193+
Simplex.Messaging.Notifications.Server.Stats
194+
Simplex.Messaging.Notifications.Server.Store
195+
Simplex.Messaging.Notifications.Server.StoreLog
189196
Simplex.Messaging.Server
197+
Simplex.Messaging.Server.CLI
190198
Simplex.Messaging.Server.Control
191199
Simplex.Messaging.Server.Env.STM
192200
Simplex.Messaging.Server.Information
@@ -201,15 +209,7 @@ library
201209
Simplex.Messaging.Server.Stats
202210
Simplex.Messaging.Server.StoreLog
203211
Simplex.Messaging.Server.StoreLog.Types
204-
Simplex.Messaging.Notifications.Server
205-
Simplex.Messaging.Notifications.Server.Control
206-
Simplex.Messaging.Notifications.Server.Env
207-
Simplex.Messaging.Notifications.Server.Main
208-
Simplex.Messaging.Notifications.Server.Push.APNS
209-
Simplex.Messaging.Notifications.Server.Push.APNS.Internal
210-
Simplex.Messaging.Notifications.Server.Stats
211-
Simplex.Messaging.Notifications.Server.Store
212-
Simplex.Messaging.Notifications.Server.StoreLog
212+
Simplex.Messaging.Transport.WebSockets
213213
other-modules:
214214
Paths_simplexmq
215215
hs-source-dirs:
@@ -270,7 +270,6 @@ library
270270
, transformers ==0.6.*
271271
, unliftio ==0.2.*
272272
, unliftio-core ==0.2.*
273-
, websockets ==0.12.*
274273
, yaml ==0.11.*
275274
, zstd ==0.1.3.*
276275
default-language: Haskell2010
@@ -280,6 +279,7 @@ library
280279
build-depends:
281280
case-insensitive ==1.2.*
282281
, hashable ==1.4.*
282+
, websockets ==0.12.*
283283
if impl(ghc >= 9.6.2)
284284
build-depends:
285285
bytestring ==0.11.*

src/Simplex/FileTransfer/Agent.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -51,8 +51,7 @@ import Data.Text (Text)
5151
import Data.Time.Clock (getCurrentTime)
5252
import Data.Time.Format (defaultTimeLocale, formatTime)
5353
import Simplex.FileTransfer.Chunks (toKB)
54-
import Simplex.FileTransfer.Client (XFTPChunkSpec (..))
55-
import Simplex.FileTransfer.Client.Main
54+
import Simplex.FileTransfer.Client (XFTPChunkSpec (..), getChunkDigest, prepareChunkSizes, prepareChunkSpecs, singleChunkSize)
5655
import Simplex.FileTransfer.Crypto
5756
import Simplex.FileTransfer.Description
5857
import Simplex.FileTransfer.Protocol (FileParty (..), SFileParty (..))

src/Simplex/FileTransfer/Client.hs

Lines changed: 42 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -20,14 +20,18 @@ import Data.Bifunctor (first)
2020
import Data.ByteString.Builder (Builder, byteString)
2121
import Data.ByteString.Char8 (ByteString)
2222
import qualified Data.ByteString.Char8 as B
23+
import qualified Data.ByteString.Lazy as LB
2324
import Data.Int (Int64)
25+
import Data.List (foldl')
2426
import Data.List.NonEmpty (NonEmpty (..))
27+
import Data.Maybe (listToMaybe)
2528
import Data.Time.Clock (UTCTime)
2629
import Data.Word (Word32)
2730
import qualified Data.X509 as X
2831
import qualified Data.X509.Validation as XV
2932
import qualified Network.HTTP.Types as N
3033
import qualified Network.HTTP2.Client as H
34+
import Simplex.FileTransfer.Chunks
3135
import Simplex.FileTransfer.Protocol
3236
import Simplex.FileTransfer.Transport
3337
import Simplex.Messaging.Client
@@ -298,3 +302,41 @@ noFile HTTP2Body {bodyPart} a = case bodyPart of
298302

299303
-- FACK :: FileCommand Recipient
300304
-- PING :: FileCommand Recipient
305+
306+
singleChunkSize :: Int64 -> Maybe Word32
307+
singleChunkSize size' =
308+
listToMaybe $ dropWhile (< chunkSize) serverChunkSizes
309+
where
310+
chunkSize = fromIntegral size'
311+
312+
prepareChunkSizes :: Int64 -> [Word32]
313+
prepareChunkSizes size' = prepareSizes size'
314+
where
315+
(smallSize, bigSize)
316+
| size' > size34 chunkSize3 = (chunkSize2, chunkSize3)
317+
| size' > size34 chunkSize2 = (chunkSize1, chunkSize2)
318+
| otherwise = (chunkSize0, chunkSize1)
319+
size34 sz = (fromIntegral sz * 3) `div` 4
320+
prepareSizes 0 = []
321+
prepareSizes size
322+
| size >= fromIntegral bigSize = replicate (fromIntegral n1) bigSize <> prepareSizes remSz
323+
| size > size34 bigSize = [bigSize]
324+
| otherwise = replicate (fromIntegral n2') smallSize
325+
where
326+
(n1, remSz) = size `divMod` fromIntegral bigSize
327+
n2' = let (n2, remSz2) = (size `divMod` fromIntegral smallSize) in if remSz2 == 0 then n2 else n2 + 1
328+
329+
prepareChunkSpecs :: FilePath -> [Word32] -> [XFTPChunkSpec]
330+
prepareChunkSpecs filePath chunkSizes = reverse . snd $ foldl' addSpec (0, []) chunkSizes
331+
where
332+
addSpec :: (Int64, [XFTPChunkSpec]) -> Word32 -> (Int64, [XFTPChunkSpec])
333+
addSpec (chunkOffset, specs) sz =
334+
let spec = XFTPChunkSpec {filePath, chunkOffset, chunkSize = sz}
335+
in (chunkOffset + fromIntegral sz, spec : specs)
336+
337+
getChunkDigest :: XFTPChunkSpec -> IO ByteString
338+
getChunkDigest XFTPChunkSpec {filePath = chunkPath, chunkOffset, chunkSize} =
339+
withFile chunkPath ReadMode $ \h -> do
340+
hSeek h AbsoluteSeek $ fromIntegral chunkOffset
341+
chunk <- LB.hGet h (fromIntegral chunkSize)
342+
pure $! LC.sha256Hash chunk

src/Simplex/FileTransfer/Client/Main.hs

Lines changed: 1 addition & 68 deletions
Original file line numberDiff line numberDiff line change
@@ -19,11 +19,7 @@ module Simplex.FileTransfer.Client.Main
1919
singleChunkSize,
2020
prepareChunkSizes,
2121
prepareChunkSpecs,
22-
maxFileSize,
23-
maxFileSizeHard,
24-
fileSizeLen,
2522
getChunkDigest,
26-
SentRecipientReplica (..),
2723
)
2824
where
2925

@@ -34,7 +30,6 @@ import Control.Monad.Trans.Except
3430
import Crypto.Random (ChaChaDRG)
3531
import qualified Data.Attoparsec.ByteString.Char8 as A
3632
import Data.Bifunctor (first)
37-
import Data.ByteString.Char8 (ByteString)
3833
import qualified Data.ByteString.Char8 as B
3934
import qualified Data.ByteString.Lazy.Char8 as LB
4035
import Data.Char (toLower)
@@ -45,7 +40,7 @@ import Data.List.NonEmpty (NonEmpty (..), nonEmpty)
4540
import qualified Data.List.NonEmpty as L
4641
import Data.Map.Strict (Map)
4742
import qualified Data.Map.Strict as M
48-
import Data.Maybe (fromMaybe, listToMaybe)
43+
import Data.Maybe (fromMaybe)
4944
import qualified Data.Text as T
5045
import Data.Word (Word32)
5146
import GHC.Records (HasField (getField))
@@ -80,20 +75,6 @@ import UnliftIO.Directory
8075
xftpClientVersion :: String
8176
xftpClientVersion = "1.0.1"
8277

83-
-- | Soft limit for XFTP clients. Should be checked and reported to user.
84-
maxFileSize :: Int64
85-
maxFileSize = gb 1
86-
87-
maxFileSizeStr :: String
88-
maxFileSizeStr = B.unpack . strEncode $ FileSize maxFileSize
89-
90-
-- | Hard internal limit for XFTP agent after which it refuses to prepare chunks.
91-
maxFileSizeHard :: Int64
92-
maxFileSizeHard = gb 5
93-
94-
fileSizeLen :: Int64
95-
fileSizeLen = 8
96-
9778
newtype CLIError = CLIError String
9879
deriving (Eq, Show, Exception)
9980

@@ -231,16 +212,6 @@ data SentFileChunkReplica = SentFileChunkReplica
231212
}
232213
deriving (Show)
233214

234-
data SentRecipientReplica = SentRecipientReplica
235-
{ chunkNo :: Int,
236-
server :: XFTPServer,
237-
rcvNo :: Int,
238-
replicaId :: ChunkReplicaId,
239-
replicaKey :: C.APrivateAuthKey,
240-
digest :: FileDigest,
241-
chunkSize :: FileSize Word32
242-
}
243-
244215
logCfg :: LogConfig
245216
logCfg = LogConfig {lc_file = Nothing, lc_stderr = True}
246217

@@ -414,13 +385,6 @@ cliSendFileOpts SendOptions {filePath, outputDir, numRecipients, xftpServers, re
414385
B.writeFile fdSndPath $ strEncode fdSnd
415386
pure (fdRcvPaths, fdSndPath)
416387

417-
getChunkDigest :: XFTPChunkSpec -> IO ByteString
418-
getChunkDigest XFTPChunkSpec {filePath = chunkPath, chunkOffset, chunkSize} =
419-
withFile chunkPath ReadMode $ \h -> do
420-
hSeek h AbsoluteSeek $ fromIntegral chunkOffset
421-
chunk <- LB.hGet h (fromIntegral chunkSize)
422-
pure $! LC.sha256Hash chunk
423-
424388
cliReceiveFile :: ReceiveOptions -> ExceptT CLIError IO ()
425389
cliReceiveFile ReceiveOptions {fileDescription, filePath, retryCount, tempPath, verbose, yes} =
426390
getFileDescription' fileDescription >>= receive
@@ -536,37 +500,6 @@ getFileDescription' path =
536500
getFileDescription path >>= \case
537501
AVFD fd -> either (throwE . CLIError) pure $ checkParty fd
538502

539-
singleChunkSize :: Int64 -> Maybe Word32
540-
singleChunkSize size' =
541-
listToMaybe $ dropWhile (< chunkSize) serverChunkSizes
542-
where
543-
chunkSize = fromIntegral size'
544-
545-
prepareChunkSizes :: Int64 -> [Word32]
546-
prepareChunkSizes size' = prepareSizes size'
547-
where
548-
(smallSize, bigSize)
549-
| size' > size34 chunkSize3 = (chunkSize2, chunkSize3)
550-
| size' > size34 chunkSize2 = (chunkSize1, chunkSize2)
551-
| otherwise = (chunkSize0, chunkSize1)
552-
size34 sz = (fromIntegral sz * 3) `div` 4
553-
prepareSizes 0 = []
554-
prepareSizes size
555-
| size >= fromIntegral bigSize = replicate (fromIntegral n1) bigSize <> prepareSizes remSz
556-
| size > size34 bigSize = [bigSize]
557-
| otherwise = replicate (fromIntegral n2') smallSize
558-
where
559-
(n1, remSz) = size `divMod` fromIntegral bigSize
560-
n2' = let (n2, remSz2) = (size `divMod` fromIntegral smallSize) in if remSz2 == 0 then n2 else n2 + 1
561-
562-
prepareChunkSpecs :: FilePath -> [Word32] -> [XFTPChunkSpec]
563-
prepareChunkSpecs filePath chunkSizes = reverse . snd $ foldl' addSpec (0, []) chunkSizes
564-
where
565-
addSpec :: (Int64, [XFTPChunkSpec]) -> Word32 -> (Int64, [XFTPChunkSpec])
566-
addSpec (chunkOffset, specs) sz =
567-
let spec = XFTPChunkSpec {filePath, chunkOffset, chunkSize = sz}
568-
in (chunkOffset + fromIntegral sz, spec : specs)
569-
570503
getEncPath :: MonadIO m => Maybe FilePath -> String -> m FilePath
571504
getEncPath path name = (`uniqueCombine` (name <> ".encrypted")) =<< maybe (liftIO getCanonicalTemporaryDirectory) pure path
572505

src/Simplex/FileTransfer/Description.hs

Lines changed: 19 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -37,6 +37,10 @@ module Simplex.FileTransfer.Description
3737
FileClientData,
3838
fileDescriptionURI,
3939
qrSizeLimit,
40+
maxFileSize,
41+
maxFileSizeStr,
42+
maxFileSizeHard,
43+
fileSizeLen,
4044
)
4145
where
4246

@@ -266,6 +270,21 @@ instance StrEncoding FileDescriptionURI where
266270
qrSizeLimit :: Int
267271
qrSizeLimit = 1002 -- ~2 chunks in URLencoded YAML with some spare size for server hosts
268272

273+
-- | Soft limit for XFTP clients. Should be checked and reported to user.
274+
maxFileSize :: Int64
275+
maxFileSize = gb 1
276+
277+
maxFileSizeStr :: String
278+
maxFileSizeStr = B.unpack . strEncode $ FileSize maxFileSize
279+
280+
-- | Hard internal limit for XFTP agent after which it refuses to prepare chunks.
281+
maxFileSizeHard :: Int64
282+
maxFileSizeHard = gb 5
283+
284+
fileSizeLen :: Int64
285+
fileSizeLen = 8
286+
287+
269288
instance (Integral a, Show a) => StrEncoding (FileSize a) where
270289
strEncode (FileSize b)
271290
| b' /= 0 = bshow b

src/Simplex/FileTransfer/Types.hs

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -246,6 +246,16 @@ data DeletedSndChunkReplica = DeletedSndChunkReplica
246246
}
247247
deriving (Show)
248248

249+
data SentRecipientReplica = SentRecipientReplica
250+
{ chunkNo :: Int,
251+
server :: XFTPServer,
252+
rcvNo :: Int,
253+
replicaId :: ChunkReplicaId,
254+
replicaKey :: C.APrivateAuthKey,
255+
digest :: FileDigest,
256+
chunkSize :: FileSize Word32
257+
}
258+
249259
data FileErrorType
250260
= -- | cannot proceed with download from not approved relays without proxy
251261
NOT_APPROVED

src/Simplex/Messaging/Client.hs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -145,7 +145,6 @@ import qualified Simplex.Messaging.TMap as TM
145145
import Simplex.Messaging.Transport
146146
import Simplex.Messaging.Transport.Client (SocksAuth (..), SocksProxyWithAuth (..), TransportClientConfig (..), TransportHost (..), defaultSMPPort, defaultTcpConnectTimeout, runTransportClient)
147147
import Simplex.Messaging.Transport.KeepAlive
148-
import Simplex.Messaging.Transport.WebSockets (WS)
149148
import Simplex.Messaging.Util (bshow, diffToMicroseconds, ifM, liftEitherWith, raceAny_, threadDelay', tshow, whenM)
150149
import Simplex.Messaging.Version
151150
import System.Mem.Weak (Weak, deRefWeak)
@@ -544,7 +543,6 @@ getProtocolClient g transportSession@(_, srv, _) cfg@ProtocolClientConfig {qSize
544543
"" -> case protocolTypeI @(ProtoType msg) of
545544
SPSMP | smpWebPort -> ("443", transport @TLS)
546545
_ -> defaultTransport cfg
547-
"80" -> ("80", transport @WS)
548546
p -> (p, transport @TLS)
549547

550548
client :: forall c. Transport c => TProxy c -> PClient v err msg -> TMVar (Either (ProtocolClientError err) (ProtocolClient v err msg)) -> c -> IO ()

0 commit comments

Comments
 (0)