• Home
  • Features
  • Pricing
  • Docs
  • Announcements
  • Sign In

lehins / mempack / 8

26 Sep 2025 07:45PM UTC coverage: 84.043% (-1.9%) from 85.987%
8

push

github

web-flow
Merge b2672ad52 into 072e28fea

61 of 91 new or added lines in 2 files covered. (67.03%)

56 existing lines in 3 files now uncovered.

711 of 846 relevant lines covered (84.04%)

1.6 hits per line

Source File
Press 'n' to go to next uncovered line, 'b' for previous

89.11
/src/Data/MemPack.hs
1
{-# LANGUAGE AllowAmbiguousTypes #-}
2
{-# LANGUAGE BangPatterns #-}
3
{-# LANGUAGE BinaryLiterals #-}
4
{-# LANGUAGE CPP #-}
5
{-# LANGUAGE DefaultSignatures #-}
6
{-# LANGUAGE FlexibleInstances #-}
7
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
8
{-# LANGUAGE LambdaCase #-}
9
{-# LANGUAGE MagicHash #-}
10
{-# LANGUAGE MultiParamTypeClasses #-}
11
{-# LANGUAGE NumericUnderscores #-}
12
{-# LANGUAGE RankNTypes #-}
13
{-# LANGUAGE ScopedTypeVariables #-}
14
{-# LANGUAGE TupleSections #-}
15
{-# LANGUAGE TypeApplications #-}
16
{-# LANGUAGE UnboxedTuples #-}
17

18
-- |
19
-- Module      : Data.MemPack
20
-- Copyright   : (c) Alexey Kuleshevich 2024-2025
21
-- License     : BSD3
22
-- Maintainer  : Alexey Kuleshevich <alexey@kuleshevi.ch>
23
-- Stability   : experimental
24
-- Portability : non-portable
25
module Data.MemPack (
26
  Pack (..),
27
  Unpack (..),
28
  MemPack (..),
29

30
  -- * Packing
31
  pack,
32
  packBuffer,
33
  packByteString,
34
  packShortByteString,
35

36
  -- ** Generalized
37
  packByteArray,
38
  packWithByteArray,
39
  packMutableByteArray,
40
  packWithMutableByteArray,
41

42
  -- ** Helpers
43
  packIncrement,
44
  guardAdvanceUnpack,
45

46
  -- * Unpacking
47
  unpack,
48
  unpackFail,
49
  unpackMonadFail,
50
  unpackError,
51
  unpackLeftOver,
52

53
  -- ** Helpers
54
  failUnpack,
55
  unpackByteArray,
56
  unpackByteArrayLen,
57
  packByteStringM,
58
  unpackByteStringM,
59
  packLiftST,
60
  unpackLiftST,
61

62
  -- * Helper packers
63
  VarLen (..),
64
  Length (..),
65
  Tag (..),
66
  packTagM,
67
  unpackTagM,
68
  unknownTagM,
69
  packedTagByteCount,
70

71
  -- * Internal utilities
72
  replicateTailM,
73
  lift_#,
74
  st_,
75

76
  -- * Re-exports for @GeneralizedNewtypeDeriving@
77
  StateT (..),
78
  FailT (..),
79
) where
80

81
#include "MachDeps.h"
82

83
import Control.Applicative (Alternative (..))
84
import Control.Monad (join, unless, when)
85
import qualified Control.Monad.Fail as F
86
import Control.Monad.Reader (MonadReader (..), lift)
87
import Control.Monad.State.Strict (MonadState (..), StateT (..), execStateT)
88
import Control.Monad.Trans.Fail (Fail, FailT (..), errorFail, failT, runFailAgg, runFailAggT)
89
import Data.Array.Byte (ByteArray (..), MutableByteArray (..))
90
import Data.Bifunctor (first)
91
import Data.Bits (Bits (..), FiniteBits (..))
92
import Data.ByteString (ByteString)
93
import qualified Data.ByteString.Lazy as BSL
94
import qualified Data.ByteString.Lazy.Internal as BSL
95
import Data.ByteString.Short (ShortByteString)
96
import Data.Char (ord)
97
import Data.Complex (Complex (..))
98
import qualified Data.Foldable as F (foldl')
99
import Data.List (intercalate)
100
import Data.MemPack.Buffer
101
import Data.MemPack.Error
102
import Data.Primitive.Array (Array (..), newArray, sizeofArray, unsafeFreezeArray, writeArray)
103
import Data.Primitive.PrimArray (PrimArray (..), sizeofPrimArray)
104
import Data.Primitive.Types (Prim (sizeOf#))
105
import Data.Ratio
106
#if MIN_VERSION_text(2,0,0)
107
import qualified Data.Text.Array as T
108
#endif
109
import qualified Data.Text.Encoding as T
110
import Data.Text.Internal (Text (..))
111
import Data.Typeable
112
import Data.Void (Void, absurd)
113
import GHC.Exts
114
import GHC.Int
115
import GHC.ST (ST (..), runST)
116
import GHC.Stable (StablePtr (..))
117
import GHC.Stack (HasCallStack)
118
import GHC.Word
119
import Numeric (showHex)
120
import Prelude hiding (fail)
121
#if __GLASGOW_HASKELL__ >= 900
122
import GHC.Num.Integer (Integer (..), integerCheck)
123
import GHC.Num.Natural (Natural (..), naturalCheck)
124
#elif defined(MIN_VERSION_integer_gmp)
125
import GHC.Integer.GMP.Internals (Integer (..), BigNat(BN#), isValidInteger#)
126
import GHC.Natural (Natural (..), isValidNatural)
127
#else
128
#error "Only integer-gmp is supported for now for older compilers"
129
#endif
130
#if !MIN_VERSION_base(4,13,0)
131
import Prelude (fail)
132
#endif
133
#if !MIN_VERSION_primitive(0,8,0)
134
import qualified Data.Primitive.ByteArray as Prim (ByteArray(..))
135
#endif
136

137
-- | Monad that is used for serializing data into a `MutableByteArray`. It is based on
138
-- `StateT` that tracks the current index into the `MutableByteArray` where next write is
139
-- expected to happen.
140
newtype Pack s a = Pack
141
  { runPack :: MutableByteArray s -> StateT Int (ST s) a
2✔
142
  }
143

UNCOV
144
instance Functor (Pack s) where
×
145
  fmap f (Pack p) = Pack $ \buf -> fmap f (p buf)
×
146
  {-# INLINE fmap #-}
UNCOV
147
instance Applicative (Pack s) where
×
148
  pure = Pack . const . pure
2✔
149
  {-# INLINE pure #-}
UNCOV
150
  Pack a1 <*> Pack a2 =
×
151
    Pack $ \buf -> a1 buf <*> a2 buf
×
152
  {-# INLINE (<*>) #-}
UNCOV
153
  Pack a1 *> Pack a2 =
×
154
    Pack $ \buf -> a1 buf *> a2 buf
×
155
  {-# INLINE (*>) #-}
156
instance Monad (Pack s) where
2✔
157
  Pack m1 >>= p =
2✔
158
    Pack $ \buf -> m1 buf >>= \res -> runPack (p res) buf
2✔
159
  {-# INLINE (>>=) #-}
160
instance MonadReader (MutableByteArray s) (Pack s) where
161
  ask = Pack pure
2✔
162
  {-# INLINE ask #-}
UNCOV
163
  local f (Pack p) = Pack (p . f)
×
164
  {-# INLINE local #-}
UNCOV
165
  reader f = Pack (pure . f)
×
166
  {-# INLINE reader #-}
167
instance MonadState Int (Pack s) where
UNCOV
168
  get = Pack $ const get
×
169
  {-# INLINE get #-}
UNCOV
170
  put = Pack . const . put
×
171
  {-# INLINE put #-}
172
  state = Pack . const . state
2✔
173
  {-# INLINE state #-}
174

175
-- | Monad that is used for deserializing data from a memory `Buffer`. It is based on
176
-- `StateT` that tracks the current index into the @`Buffer` a@, from where the next read
177
-- suppose to happen. Unpacking can `F.fail` with `F.MonadFail` instance or with
178
-- `failUnpack` that provides a more type safe way of failing using `Error` interface.
179
newtype Unpack s b a = Unpack
180
  { runUnpack :: b -> StateT Int (FailT SomeError (ST s)) a
2✔
181
  }
182

NEW
183
instance Functor (Unpack s b) where
×
184
  fmap f (Unpack p) = Unpack $ \buf -> fmap f (p buf)
2✔
185
  {-# INLINE fmap #-}
NEW
186
instance Applicative (Unpack s b) where
×
187
  pure = Unpack . const . pure
2✔
188
  {-# INLINE pure #-}
189
  Unpack a1 <*> Unpack a2 =
2✔
190
    Unpack $ \buf -> a1 buf <*> a2 buf
1✔
191
  {-# INLINE (<*>) #-}
UNCOV
192
  Unpack a1 *> Unpack a2 =
×
193
    Unpack $ \buf -> a1 buf *> a2 buf
×
194
  {-# INLINE (*>) #-}
NEW
195
instance Monad (Unpack s b) where
×
196
  Unpack m1 >>= p =
2✔
197
    Unpack $ \buf -> m1 buf >>= \res -> runUnpack (p res) buf
2✔
198
  {-# INLINE (>>=) #-}
199
#if !(MIN_VERSION_base(4,13,0))
200
  fail = Unpack . const . F.fail
201
#endif
202
instance F.MonadFail (Unpack s b) where
203
  fail = Unpack . const . F.fail
2✔
204
instance MonadReader b (Unpack s b) where
205
  ask = Unpack pure
2✔
206
  {-# INLINE ask #-}
UNCOV
207
  local f (Unpack p) = Unpack (p . f)
×
208
  {-# INLINE local #-}
UNCOV
209
  reader f = Unpack (pure . f)
×
210
  {-# INLINE reader #-}
211
instance MonadState Int (Unpack s b) where
UNCOV
212
  get = Unpack $ const get
×
213
  {-# INLINE get #-}
UNCOV
214
  put = Unpack . const . put
×
215
  {-# INLINE put #-}
216
  state = Unpack . const . state
2✔
217
  {-# INLINE state #-}
218

NEW
219
instance Alternative (Unpack s b) where
×
220
  empty = Unpack $ \_ -> lift empty
×
221
  {-# INLINE empty #-}
222
  Unpack r1 <|> Unpack r2 =
2✔
223
    Unpack $ \buf ->
2✔
224
      case r1 buf of
2✔
225
        StateT m1 ->
226
          case r2 buf of
2✔
227
            StateT m2 -> StateT $ \s -> m1 s <|> m2 s
2✔
228
  {-# INLINE (<|>) #-}
229

230
-- | Failing unpacking with an `Error`.
231
failUnpack :: Error e => e -> Unpack s b a
232
failUnpack e = Unpack $ \_ -> lift $ failT (toSomeError e)
2✔
233

234
-- | Efficient serialization interface that operates directly on memory buffers.
235
class MemPack a where
236
  -- | Name of the type that is being deserialized for error reporting. Default
237
  -- implementation relies on `Typeable`.
238
  typeName :: String
239
  default typeName :: Typeable a => String
240
  typeName = show (typeRep (Proxy @a))
1✔
241

242
  -- | Report the exact size in number of bytes that packed version of this type will
243
  -- occupy. It is very important to get this right, otherwise `packM` will result in a
244
  -- runtime exception. Another words this is the expected property that it should hold:
245
  --
246
  -- prop> packedByteCount a == bufferByteCount (pack a)
247
  packedByteCount :: a -> Int
248

249
  -- | Write binary representation of a type into the `MutableByteArray` which can be
250
  -- accessed with `ask`, whenever direct operations on it are necessary.
251
  packM :: a -> Pack s ()
252

253
  -- | Read binary representation of the type directly from the buffer, which can be
254
  -- accessed with `ask` when necessary.
255
  --
256
  -- /Warning/ - Direct reads from the buffer should be preceded with advancing the buffer offset
257
  -- within `MonadState` by the exact number of bytes that gets consumed from that buffer.
258
  --
259
  -- __âš __ - Violation of the above rule will lead to segfaults.
260
  unpackM :: Buffer b => Unpack s b a
261

UNCOV
262
instance MemPack () where
×
263
  packedByteCount _ = 0
2✔
264
  {-# INLINE packedByteCount #-}
265
  packM () = pure ()
1✔
266
  {-# INLINE packM #-}
267
  unpackM = pure ()
2✔
268
  {-# INLINE unpackM #-}
269

UNCOV
270
instance MemPack Void where
×
271
  packedByteCount _ = 0
×
272
  packM = absurd
×
273
  unpackM = F.fail "Void is unpackable"
×
274

275
instance MemPack Bool where
2✔
276
  packedByteCount _ = packedTagByteCount
2✔
277
  {-# INLINE packedByteCount #-}
278
  packM x = packTagM $ if x then 1 else 0
2✔
279
  {-# INLINE packM #-}
280
  unpackM =
2✔
281
    unpackTagM >>= \case
2✔
282
      0 -> pure False
2✔
283
      1 -> pure True
2✔
UNCOV
284
      n -> F.fail $ "Invalid value detected for Bool: " ++ show n
×
285
  {-# INLINE unpackM #-}
286

287
instance MemPack a => MemPack (Maybe a) where
288
  typeName = "Maybe " ++ typeName @a
2✔
289
  packedByteCount = \case
2✔
290
    Nothing -> packedTagByteCount
2✔
291
    Just a -> packedTagByteCount + packedByteCount a
2✔
292
  {-# INLINE packedByteCount #-}
293
  packM = \case
2✔
294
    Nothing -> packTagM 0
2✔
295
    Just a -> packTagM 1 >> packM a
2✔
296
  {-# INLINE packM #-}
297
  unpackM =
2✔
298
    unpackTagM >>= \case
2✔
299
      0 -> pure Nothing
2✔
300
      1 -> Just <$> unpackM
2✔
UNCOV
301
      n -> unknownTagM @(Maybe a) n
×
302
  {-# INLINE unpackM #-}
303

304
instance (MemPack a, MemPack b) => MemPack (Either a b) where
305
  typeName = "Either " ++ typeName @a ++ " " ++ typeName @b
2✔
306
  packedByteCount = \case
2✔
307
    Left a -> packedTagByteCount + packedByteCount a
1✔
308
    Right b -> packedTagByteCount + packedByteCount b
1✔
309
  {-# INLINE packedByteCount #-}
310
  packM = \case
2✔
311
    Left a -> packTagM 0 >> packM a
2✔
312
    Right b -> packTagM 1 >> packM b
2✔
313
  {-# INLINE packM #-}
314
  unpackM =
2✔
315
    unpackTagM >>= \case
2✔
316
      0 -> Left <$> unpackM
2✔
317
      1 -> Right <$> unpackM
2✔
UNCOV
318
      n -> unknownTagM @(Either a b) n
×
319
  {-# INLINE unpackM #-}
320

321
instance MemPack Char where
2✔
322
  packedByteCount _ = SIZEOF_HSCHAR
2✔
323
  {-# INLINE packedByteCount #-}
324
  packM a@(C# a#) = do
2✔
325
    MutableByteArray mba# <- ask
2✔
326
    I# i# <- packIncrement a
1✔
327
    lift_# (writeWord8ArrayAsWideChar# mba# i# a#)
2✔
328
  {-# INLINE packM #-}
329
  unpackM = do
2✔
330
    I# i# <- guardAdvanceUnpack SIZEOF_HSCHAR
2✔
331
    buf <- ask
2✔
332
    let c =
2✔
333
          buffer
2✔
334
            buf
2✔
335
            (\ba# off# -> C# (indexWord8ArrayAsWideChar# ba# (i# +# off#)))
2✔
336
            (\addr# -> C# (indexWideCharOffAddr# (addr# `plusAddr#` i#) 0#))
2✔
337
        ordc :: Word32
338
        ordc = fromIntegral (ord c)
2✔
339
    when (ordc > 0x10FFFF) $
2✔
340
      F.fail $
2✔
UNCOV
341
        "Out of bounds Char was detected: '\\x" ++ showHex ordc "'"
×
342
    pure c
2✔
343
  {-# INLINE unpackM #-}
344

345
instance MemPack Float where
2✔
346
  packedByteCount _ = SIZEOF_FLOAT
2✔
347
  {-# INLINE packedByteCount #-}
348
  packM a@(F# a#) = do
2✔
349
    MutableByteArray mba# <- ask
2✔
350
    I# i# <- packIncrement a
1✔
351
    lift_# (writeWord8ArrayAsFloat# mba# i# a#)
2✔
352
  {-# INLINE packM #-}
353
  unpackM = do
2✔
354
    I# i# <- guardAdvanceUnpack SIZEOF_FLOAT
2✔
355
    buf <- ask
2✔
356
    pure $!
2✔
357
      buffer
2✔
358
        buf
2✔
359
        (\ba# off# -> F# (indexWord8ArrayAsFloat# ba# (i# +# off#)))
2✔
360
        (\addr# -> F# (indexFloatOffAddr# (addr# `plusAddr#` i#) 0#))
2✔
361
  {-# INLINE unpackM #-}
362

363
instance MemPack Double where
2✔
364
  packedByteCount _ = SIZEOF_DOUBLE
2✔
365
  {-# INLINE packedByteCount #-}
366
  packM a@(D# a#) = do
2✔
367
    MutableByteArray mba# <- ask
2✔
368
    I# i# <- packIncrement a
1✔
369
    lift_# (writeWord8ArrayAsDouble# mba# i# a#)
2✔
370
  {-# INLINE packM #-}
371
  unpackM = do
2✔
372
    I# i# <- guardAdvanceUnpack SIZEOF_DOUBLE
2✔
373
    buf <- ask
2✔
374
    pure $!
2✔
375
      buffer
2✔
376
        buf
2✔
377
        (\ba# off# -> D# (indexWord8ArrayAsDouble# ba# (i# +# off#)))
2✔
378
        (\addr# -> D# (indexDoubleOffAddr# (addr# `plusAddr#` i#) 0#))
2✔
379
  {-# INLINE unpackM #-}
380

381
instance MemPack (Ptr a) where
382
  typeName = "Ptr"
2✔
383
  packedByteCount _ = SIZEOF_HSPTR
2✔
384
  {-# INLINE packedByteCount #-}
385
  packM a@(Ptr a#) = do
2✔
386
    MutableByteArray mba# <- ask
2✔
387
    I# i# <- packIncrement a
1✔
388
    lift_# (writeWord8ArrayAsAddr# mba# i# a#)
2✔
389
  {-# INLINE packM #-}
390
  unpackM = do
2✔
391
    I# i# <- guardAdvanceUnpack SIZEOF_HSPTR
2✔
392
    buf <- ask
2✔
393
    pure $!
2✔
394
      buffer
2✔
395
        buf
2✔
396
        (\ba# off# -> Ptr (indexWord8ArrayAsAddr# ba# (i# +# off#)))
2✔
397
        (\addr# -> Ptr (indexAddrOffAddr# (addr# `plusAddr#` i#) 0#))
2✔
398
  {-# INLINE unpackM #-}
399

400
instance MemPack (StablePtr a) where
401
  typeName = "StablePtr"
2✔
402
  packedByteCount _ = SIZEOF_HSSTABLEPTR
2✔
403
  {-# INLINE packedByteCount #-}
404
  packM a@(StablePtr a#) = do
2✔
405
    MutableByteArray mba# <- ask
2✔
406
    I# i# <- packIncrement a
1✔
407
    lift_# (writeWord8ArrayAsStablePtr# mba# i# a#)
2✔
408
  {-# INLINE packM #-}
409
  unpackM = do
2✔
410
    I# i# <- guardAdvanceUnpack SIZEOF_HSSTABLEPTR
2✔
411
    buf <- ask
2✔
412
    pure $!
2✔
413
      buffer
2✔
414
        buf
2✔
415
        (\ba# off# -> StablePtr (indexWord8ArrayAsStablePtr# ba# (i# +# off#)))
2✔
416
        (\addr# -> StablePtr (indexStablePtrOffAddr# (addr# `plusAddr#` i#) 0#))
2✔
417
  {-# INLINE unpackM #-}
418

419
instance MemPack Int where
2✔
420
  packedByteCount _ = SIZEOF_HSINT
2✔
421
  {-# INLINE packedByteCount #-}
422
  packM a@(I# a#) = do
2✔
423
    MutableByteArray mba# <- ask
2✔
424
    I# i# <- packIncrement a
1✔
425
    lift_# (writeWord8ArrayAsInt# mba# i# a#)
2✔
426
  {-# INLINE packM #-}
427
  unpackM = do
2✔
428
    I# i# <- guardAdvanceUnpack SIZEOF_HSINT
2✔
429
    buf <- ask
2✔
430
    pure $!
2✔
431
      buffer
2✔
432
        buf
2✔
433
        (\ba# off# -> I# (indexWord8ArrayAsInt# ba# (i# +# off#)))
2✔
434
        (\addr# -> I# (indexIntOffAddr# (addr# `plusAddr#` i#) 0#))
2✔
435
  {-# INLINE unpackM #-}
436

437
instance MemPack Int8 where
2✔
438
  packedByteCount _ = SIZEOF_INT8
2✔
439
  {-# INLINE packedByteCount #-}
440
  packM a@(I8# a#) = do
2✔
441
    MutableByteArray mba# <- ask
2✔
442
    I# i# <- packIncrement a
1✔
443
    lift_# (writeInt8Array# mba# i# a#)
2✔
444
  {-# INLINE packM #-}
445
  unpackM = do
2✔
446
    I# i# <- guardAdvanceUnpack SIZEOF_INT8
2✔
447
    buf <- ask
2✔
448
    pure $!
2✔
449
      buffer
2✔
450
        buf
2✔
451
        (\ba# off# -> I8# (indexInt8Array# ba# (i# +# off#)))
2✔
452
        (\addr# -> I8# (indexInt8OffAddr# (addr# `plusAddr#` i#) 0#))
2✔
453
  {-# INLINE unpackM #-}
454

455
instance MemPack Int16 where
2✔
456
  packedByteCount _ = SIZEOF_INT16
2✔
457
  {-# INLINE packedByteCount #-}
458
  packM a@(I16# a#) = do
2✔
459
    MutableByteArray mba# <- ask
2✔
460
    I# i# <- packIncrement a
1✔
461
    lift_# (writeWord8ArrayAsInt16# mba# i# a#)
2✔
462
  {-# INLINE packM #-}
463
  unpackM = do
2✔
464
    buf <- ask
2✔
465
    I# i# <- guardAdvanceUnpack SIZEOF_INT16
2✔
466
    pure $!
2✔
467
      buffer
2✔
468
        buf
2✔
469
        (\ba# off# -> I16# (indexWord8ArrayAsInt16# ba# (i# +# off#)))
2✔
470
        (\addr# -> I16# (indexInt16OffAddr# (addr# `plusAddr#` i#) 0#))
2✔
471
  {-# INLINE unpackM #-}
472

473
instance MemPack Int32 where
2✔
474
  packedByteCount _ = SIZEOF_INT32
2✔
475
  {-# INLINE packedByteCount #-}
476
  packM a@(I32# a#) = do
2✔
477
    MutableByteArray mba# <- ask
2✔
478
    I# i# <- packIncrement a
1✔
479
    lift_# (writeWord8ArrayAsInt32# mba# i# a#)
2✔
480
  {-# INLINE packM #-}
481
  unpackM = do
2✔
482
    buf <- ask
2✔
483
    I# i# <- guardAdvanceUnpack SIZEOF_INT32
2✔
484
    pure $!
2✔
485
      buffer
2✔
486
        buf
2✔
487
        (\ba# off# -> I32# (indexWord8ArrayAsInt32# ba# (i# +# off#)))
2✔
488
        (\addr# -> I32# (indexInt32OffAddr# (addr# `plusAddr#` i#) 0#))
2✔
489
  {-# INLINE unpackM #-}
490

491
instance MemPack Int64 where
2✔
492
  packedByteCount _ = SIZEOF_INT64
2✔
493
  {-# INLINE packedByteCount #-}
494
  packM a@(I64# a#) = do
2✔
495
    MutableByteArray mba# <- ask
2✔
496
    I# i# <- packIncrement a
1✔
497
    lift_# (writeWord8ArrayAsInt64# mba# i# a#)
2✔
498
  {-# INLINE packM #-}
499
  unpackM = do
2✔
500
    buf <- ask
2✔
501
    I# i# <- guardAdvanceUnpack SIZEOF_INT64
2✔
502
    pure $!
2✔
503
      buffer
2✔
504
        buf
2✔
505
        (\ba# off# -> I64# (indexWord8ArrayAsInt64# ba# (i# +# off#)))
2✔
506
        (\addr# -> I64# (indexInt64OffAddr# (addr# `plusAddr#` i#) 0#))
2✔
507
  {-# INLINE unpackM #-}
508

509
instance MemPack Word where
2✔
510
  packedByteCount _ = SIZEOF_HSWORD
2✔
511
  {-# INLINE packedByteCount #-}
512
  packM a@(W# a#) = do
2✔
513
    MutableByteArray mba# <- ask
2✔
514
    I# i# <- packIncrement a
1✔
515
    lift_# (writeWord8ArrayAsWord# mba# i# a#)
2✔
516
  {-# INLINE packM #-}
517
  unpackM = do
2✔
518
    I# i# <- guardAdvanceUnpack SIZEOF_HSWORD
2✔
519
    buf <- ask
2✔
520
    pure $!
2✔
521
      buffer
2✔
522
        buf
2✔
523
        (\ba# off# -> W# (indexWord8ArrayAsWord# ba# (i# +# off#)))
2✔
524
        (\addr# -> W# (indexWordOffAddr# (addr# `plusAddr#` i#) 0#))
2✔
525
  {-# INLINE unpackM #-}
526

527
instance MemPack Word8 where
2✔
528
  packedByteCount _ = SIZEOF_WORD8
2✔
529
  {-# INLINE packedByteCount #-}
530
  packM a@(W8# a#) = do
2✔
531
    MutableByteArray mba# <- ask
2✔
532
    I# i# <- packIncrement a
1✔
533
    lift_# (writeWord8Array# mba# i# a#)
2✔
534
  {-# INLINE packM #-}
535
  unpackM = do
2✔
536
    I# i# <- guardAdvanceUnpack SIZEOF_WORD8
2✔
537
    buf <- ask
2✔
538
    pure $!
2✔
539
      buffer
2✔
540
        buf
2✔
541
        (\ba# off# -> W8# (indexWord8Array# ba# (i# +# off#)))
2✔
542
        (\addr# -> W8# (indexWord8OffAddr# addr# i#))
2✔
543
  {-# INLINE unpackM #-}
544

545
instance MemPack Word16 where
2✔
546
  packedByteCount _ = SIZEOF_WORD16
2✔
547
  {-# INLINE packedByteCount #-}
548
  packM a@(W16# a#) = do
2✔
549
    MutableByteArray mba# <- ask
2✔
550
    I# i# <- packIncrement a
1✔
551
    lift_# (writeWord8ArrayAsWord16# mba# i# a#)
2✔
552
  {-# INLINE packM #-}
553
  unpackM = do
2✔
554
    buf <- ask
2✔
555
    I# i# <- guardAdvanceUnpack SIZEOF_WORD16
2✔
556
    pure $!
2✔
557
      buffer
2✔
558
        buf
2✔
559
        (\ba# off# -> W16# (indexWord8ArrayAsWord16# ba# (i# +# off#)))
2✔
560
        (\addr# -> W16# (indexWord16OffAddr# (addr# `plusAddr#` i#) 0#))
2✔
561
  {-# INLINE unpackM #-}
562

563
instance MemPack Word32 where
2✔
564
  packedByteCount _ = SIZEOF_WORD32
2✔
565
  {-# INLINE packedByteCount #-}
566
  packM a@(W32# a#) = do
2✔
567
    MutableByteArray mba# <- ask
2✔
568
    I# i# <- packIncrement a
1✔
569
    lift_# (writeWord8ArrayAsWord32# mba# i# a#)
2✔
570
  {-# INLINE packM #-}
571
  unpackM = do
2✔
572
    I# i# <- guardAdvanceUnpack SIZEOF_WORD32
2✔
573
    buf <- ask
2✔
574
    pure $!
2✔
575
      buffer
2✔
576
        buf
2✔
577
        (\ba# off# -> W32# (indexWord8ArrayAsWord32# ba# (i# +# off#)))
2✔
578
        (\addr# -> W32# (indexWord32OffAddr# (addr# `plusAddr#` i#) 0#))
2✔
579
  {-# INLINE unpackM #-}
580

581
instance MemPack Word64 where
2✔
582
  packedByteCount _ = SIZEOF_WORD64
2✔
583
  {-# INLINE packedByteCount #-}
584
  packM a@(W64# a#) = do
2✔
585
    MutableByteArray mba# <- ask
2✔
586
    I# i# <- packIncrement a
1✔
587
    lift_# (writeWord8ArrayAsWord64# mba# i# a#)
2✔
588
  {-# INLINE packM #-}
589
  unpackM = do
2✔
590
    I# i# <- guardAdvanceUnpack SIZEOF_WORD64
2✔
591
    buf <- ask
2✔
592
    pure $!
2✔
593
      buffer
2✔
594
        buf
2✔
595
        (\ba# off# -> W64# (indexWord8ArrayAsWord64# ba# (i# +# off#)))
2✔
596
        (\addr# -> W64# (indexWord64OffAddr# (addr# `plusAddr#` i#) 0#))
2✔
597
  {-# INLINE unpackM #-}
598

599
#if __GLASGOW_HASKELL__ >= 900
600
instance MemPack Integer where
2✔
601
  packedByteCount =
2✔
602
    (+ packedTagByteCount) . \case
2✔
603
      IS i# -> packedByteCount (I# i#)
1✔
604
      IP ba# -> packedByteCount (ByteArray ba#)
2✔
605
      IN ba# -> packedByteCount (ByteArray ba#)
2✔
606
  {-# INLINE packedByteCount #-}
607
  packM = \case
2✔
608
    IS i# -> packTagM 0 >> packM (I# i#)
2✔
609
    IP ba# -> packTagM 1 >> packM (ByteArray ba#)
2✔
610
    IN ba# -> packTagM 2 >> packM (ByteArray ba#)
2✔
611
  {-# INLINE packM #-}
612
  unpackM = do
2✔
613
    i <-
614
      unpackTagM >>= \case
2✔
615
        0 -> do
2✔
616
          I# i# <- unpackM
2✔
617
          pure $ IS i#
2✔
618
        1 -> do
2✔
619
          ByteArray ba# <- unpackM
2✔
620
          pure $ IP ba#
2✔
621
        2 -> do
2✔
622
          ByteArray ba# <- unpackM
2✔
623
          pure $ IN ba#
2✔
UNCOV
624
        t -> unknownTagM @Integer t
×
625
    unless (integerCheck i) $ F.fail $ "Invalid Integer decoded " ++ showInteger i
1✔
626
    pure i
2✔
627
    where
UNCOV
628
      showInteger = \case
×
629
        IS i# -> "IS " ++ show (I# i#)
×
630
        IP ba# -> "IP " ++ show (ByteArray ba#)
×
631
        IN ba# -> "IN " ++ show (ByteArray ba#)
×
632
  {-# INLINE unpackM #-}
633

634
instance MemPack Natural where
2✔
635
  packedByteCount =
2✔
636
    (+ packedTagByteCount) . \case
2✔
637
      NS w# -> packedByteCount (W# w#)
1✔
638
      NB ba# -> packedByteCount (ByteArray ba#)
2✔
639
  {-# INLINE packedByteCount #-}
640
  packM = \case
2✔
641
    NS w# -> packTagM 0 >> packM (W# w#)
2✔
642
    NB ba# -> packTagM 1 >> packM (ByteArray ba#)
2✔
643
  {-# INLINE packM #-}
644
  unpackM = do
2✔
645
    n <-
646
      unpackTagM >>= \case
2✔
647
        0 -> do
2✔
648
          W# w# <- unpackM
2✔
649
          pure $ NS w#
2✔
650
        1 -> do
2✔
651
          ByteArray ba# <- unpackM
2✔
652
          pure $ NB ba#
2✔
UNCOV
653
        t -> unknownTagM @Natural t
×
654
    unless (naturalCheck n) $ F.fail $ "Invalid Natural decoded " ++ showNatural n
1✔
655
    pure n
2✔
656
    where
UNCOV
657
      showNatural = \case
×
658
        NS w# -> "NS " ++ show (W# w#)
×
659
        NB ba# -> "NB " ++ show (ByteArray ba#)
×
660
  {-# INLINE unpackM #-}
661

662
#elif defined(MIN_VERSION_integer_gmp)
663

664
instance MemPack Integer where
665
  packedByteCount =
666
    (+ packedTagByteCount) . \case
667
      S# i# -> packedByteCount (I# i#)
668
      Jp# (BN# ba#) -> packedByteCount (ByteArray ba#)
669
      Jn# (BN# ba#) -> packedByteCount (ByteArray ba#)
670
  {-# INLINE packedByteCount #-}
671
  packM = \case
672
    S# i# -> packTagM 0 >> packM (I# i#)
673
    Jp# (BN# ba#) -> packTagM 1 >> packM (ByteArray ba#)
674
    Jn# (BN# ba#) -> packTagM 2 >> packM (ByteArray ba#)
675
  {-# INLINE packM #-}
676
  unpackM = do
677
    i <-
678
      unpackTagM >>= \case
679
        0 -> do
680
          I# i# <- unpackM
681
          pure $ S# i#
682
        1 -> do
683
          ByteArray ba# <- unpackM
684
          pure $ Jp# (BN# ba#)
685
        2 -> do
686
          ByteArray ba# <- unpackM
687
          pure $ Jn# (BN# ba#)
688
        t -> unknownTagM @Integer t
689
    unless (isTrue# (isValidInteger# i)) $ F.fail $ "Invalid Integer decoded " ++ showInteger i
690
    pure i
691
    where
692
      showInteger = \case
693
        S# i# -> "S# " ++ show (I# i#)
694
        Jp# (BN# ba#) -> "Jp# " ++ show (ByteArray ba#)
695
        Jn# (BN# ba#) -> "Jn# " ++ show (ByteArray ba#)
696
  {-# INLINE unpackM #-}
697

698
instance MemPack Natural where
699
  packedByteCount =
700
    (+ packedTagByteCount) . \case
701
      NatS# w# -> packedByteCount (W# w#)
702
      NatJ# (BN# ba#) -> packedByteCount (ByteArray ba#)
703
  {-# INLINE packedByteCount #-}
704
  packM = \case
705
    NatS# w# -> packTagM 0 >> packM (W# w#)
706
    NatJ# (BN# ba#) -> packTagM 1 >> packM (ByteArray ba#)
707
  {-# INLINE packM #-}
708
  unpackM = do
709
    n <-
710
      unpackTagM >>= \case
711
        0 -> do
712
          W# w# <- unpackM
713
          pure $ NatS# w#
714
        1 -> do
715
          ByteArray ba# <- unpackM
716
          pure $ NatJ# (BN# ba#)
717
        t -> unknownTagM @Natural t
718
    unless (isValidNatural n) $ F.fail $ "Invalid Natural decoded " ++ showNatural n
719
    pure n
720
    where
721
      showNatural = \case
722
        NatS# w# -> "NatS# " ++ show (W# w#)
723
        NatJ# (BN#  ba#) -> "NatJ# " ++ show (ByteArray ba#)
724
  {-# INLINE unpackM #-}
725

726
#endif
727

728
instance MemPack a => MemPack (Complex a) where
729
  typeName = "Complex " ++ typeName @a
2✔
730
  packedByteCount (a :+ b) = packedByteCount a + packedByteCount b
1✔
731
  {-# INLINE packedByteCount #-}
732
  packM (a :+ b) = packM a >> packM b
2✔
733
  {-# INLINE packM #-}
734
  unpackM = do
2✔
735
    !a <- unpackM
2✔
736
    !b <- unpackM
2✔
737
    pure (a :+ b)
2✔
738
  {-# INLINE unpackM #-}
739

740
instance (MemPack a, Integral a) => MemPack (Ratio a) where
741
  typeName = "Ratio " ++ typeName @a
2✔
742
  packedByteCount r = packedByteCount (numerator r) + packedByteCount (denominator r)
1✔
743
  {-# INLINE packedByteCount #-}
744
  packM r = packM (numerator r) >> packM (denominator r)
2✔
745
  {-# INLINE packM #-}
746
  unpackM = do
2✔
747
    !a <- unpackM
2✔
748
    !b <- unpackM
2✔
749
    when (b == 0) $ F.fail $ "Zero denominator was detected when unpacking " ++ typeName @(Ratio a)
1✔
750
    pure (a % b)
2✔
751
  {-# INLINE unpackM #-}
752

753
instance (MemPack a, MemPack b) => MemPack (a, b) where
754
  typeName = "(" ++ typeName @a ++ "," ++ typeName @b ++ ")"
2✔
755
  packedByteCount (a, b) = packedByteCount a + packedByteCount b
1✔
756
  {-# INLINE packedByteCount #-}
757
  packM (a, b) = packM a >> packM b
2✔
758
  {-# INLINEABLE packM #-}
759
  unpackM = do
2✔
760
    !a <- unpackM
2✔
761
    !b <- unpackM
2✔
762
    pure (a, b)
2✔
763
  {-# INLINEABLE unpackM #-}
764

765
instance (MemPack a, MemPack b, MemPack c) => MemPack (a, b, c) where
766
  typeName = "(" ++ typeName @a ++ "," ++ typeName @b ++ "," ++ typeName @c ++ ")"
2✔
767
  packedByteCount (a, b, c) = packedByteCount a + packedByteCount b + packedByteCount c
1✔
768
  {-# INLINE packedByteCount #-}
769
  packM (a, b, c) = packM a >> packM b >> packM c
2✔
770
  {-# INLINEABLE packM #-}
771
  unpackM = do
2✔
772
    !a <- unpackM
2✔
773
    !b <- unpackM
2✔
774
    !c <- unpackM
2✔
775
    pure (a, b, c)
2✔
776
  {-# INLINEABLE unpackM #-}
777

778
instance (MemPack a, MemPack b, MemPack c, MemPack d) => MemPack (a, b, c, d) where
779
  typeName = "(" ++ typeName @a ++ "," ++ typeName @b ++ "," ++ typeName @c ++ "," ++ typeName @d ++ ")"
2✔
780
  packedByteCount (a, b, c, d) = packedByteCount a + packedByteCount b + packedByteCount c + packedByteCount d
1✔
781
  {-# INLINE packedByteCount #-}
782
  packM (a, b, c, d) =
2✔
783
    packM a >> packM b >> packM c >> packM d
2✔
784
  {-# INLINEABLE packM #-}
785
  unpackM = do
2✔
786
    !a <- unpackM
2✔
787
    !b <- unpackM
2✔
788
    !c <- unpackM
2✔
789
    !d <- unpackM
2✔
790
    pure (a, b, c, d)
2✔
791
  {-# INLINEABLE unpackM #-}
792

793
instance (MemPack a, MemPack b, MemPack c, MemPack d, MemPack e) => MemPack (a, b, c, d, e) where
794
  typeName =
2✔
795
    "("
2✔
796
      ++ intercalate
2✔
797
        ","
2✔
798
        [ typeName @a
2✔
799
        , typeName @b
2✔
800
        , typeName @c
2✔
801
        , typeName @d
2✔
802
        , typeName @e
2✔
803
        ]
804
      ++ ")"
2✔
805
  packedByteCount (a, b, c, d, e) =
2✔
806
    packedByteCount a + packedByteCount b + packedByteCount c + packedByteCount d + packedByteCount e
1✔
807
  {-# INLINE packedByteCount #-}
808
  packM (a, b, c, d, e) =
2✔
809
    packM a >> packM b >> packM c >> packM d >> packM e
2✔
810
  {-# INLINEABLE packM #-}
811
  unpackM = do
2✔
812
    !a <- unpackM
2✔
813
    !b <- unpackM
2✔
814
    !c <- unpackM
2✔
815
    !d <- unpackM
2✔
816
    !e <- unpackM
2✔
817
    pure (a, b, c, d, e)
2✔
818
  {-# INLINEABLE unpackM #-}
819

820
instance (MemPack a, MemPack b, MemPack c, MemPack d, MemPack e, MemPack f) => MemPack (a, b, c, d, e, f) where
821
  typeName =
2✔
822
    "("
2✔
823
      ++ intercalate
2✔
824
        ","
2✔
825
        [ typeName @a
2✔
826
        , typeName @b
2✔
827
        , typeName @c
2✔
828
        , typeName @d
2✔
829
        , typeName @e
2✔
830
        , typeName @f
2✔
831
        ]
832
      ++ ")"
2✔
833
  packedByteCount (a, b, c, d, e, f) =
2✔
834
    packedByteCount a
1✔
835
      + packedByteCount b
1✔
836
      + packedByteCount c
2✔
837
      + packedByteCount d
2✔
838
      + packedByteCount e
1✔
839
      + packedByteCount f
2✔
840
  {-# INLINE packedByteCount #-}
841
  packM (a, b, c, d, e, f) =
2✔
842
    packM a >> packM b >> packM c >> packM d >> packM e >> packM f
2✔
843
  {-# INLINEABLE packM #-}
844
  unpackM = do
2✔
845
    !a <- unpackM
2✔
846
    !b <- unpackM
2✔
847
    !c <- unpackM
2✔
848
    !d <- unpackM
2✔
849
    !e <- unpackM
2✔
850
    !f <- unpackM
2✔
851
    pure (a, b, c, d, e, f)
2✔
852
  {-# INLINEABLE unpackM #-}
853

854
instance
855
  (MemPack a, MemPack b, MemPack c, MemPack d, MemPack e, MemPack f, MemPack g) =>
856
  MemPack (a, b, c, d, e, f, g)
857
  where
858
  typeName =
2✔
859
    "("
2✔
860
      ++ intercalate
2✔
861
        ","
2✔
862
        [ typeName @a
2✔
863
        , typeName @b
2✔
864
        , typeName @c
2✔
865
        , typeName @d
2✔
866
        , typeName @e
2✔
867
        , typeName @f
2✔
868
        , typeName @g
2✔
869
        ]
870
      ++ ")"
2✔
871
  packedByteCount (a, b, c, d, e, f, g) =
2✔
872
    packedByteCount a
1✔
873
      + packedByteCount b
1✔
874
      + packedByteCount c
1✔
875
      + packedByteCount d
1✔
876
      + packedByteCount e
1✔
877
      + packedByteCount f
1✔
878
      + packedByteCount g
2✔
879
  {-# INLINE packedByteCount #-}
880
  packM (a, b, c, d, e, f, g) =
2✔
881
    packM a >> packM b >> packM c >> packM d >> packM e >> packM f >> packM g
2✔
882
  {-# INLINEABLE packM #-}
883
  unpackM = do
2✔
884
    !a <- unpackM
2✔
885
    !b <- unpackM
2✔
886
    !c <- unpackM
2✔
887
    !d <- unpackM
2✔
888
    !e <- unpackM
2✔
889
    !f <- unpackM
2✔
890
    !g <- unpackM
2✔
891
    pure (a, b, c, d, e, f, g)
2✔
892
  {-# INLINEABLE unpackM #-}
893

894
instance MemPack a => MemPack [a] where
895
  typeName = "[" ++ typeName @a ++ "]"
2✔
896
  packedByteCount es =
2✔
897
    let go [] (# listLen#, elemsLen# #) = packedByteCount (Length (I# listLen#)) + (I# elemsLen#)
2✔
898
        go (x : xs) (# listLen#, elemsLen# #) =
899
          let !(I# bc#) = packedByteCount x
2✔
900
           in go xs (# 1# +# listLen#, bc# +# elemsLen# #)
2✔
901
     in go es (# 0#, 0# #)
2✔
902
  {-# INLINE packedByteCount #-}
903
  packM as = do
2✔
904
    packM (Length (length as))
2✔
905
    mapM_ packM as
2✔
906
  {-# INLINE packM #-}
907
  unpackM = do
2✔
908
    Length n <- unpackM
2✔
909
    replicateTailM n unpackM
2✔
910
  {-# INLINE unpackM #-}
911

912
instance MemPack a => MemPack (Array a) where
913
  typeName = "(Array " ++ typeName @a ++ ")"
2✔
914
  packedByteCount arr =
2✔
915
    packedByteCount (Length (sizeofArray arr))
2✔
916
      + F.foldl' (\acc e -> acc + packedByteCount e) 0 arr
2✔
917
  {-# INLINE packedByteCount #-}
918
  packM as = do
2✔
919
    packM (Length (length as))
2✔
920
    mapM_ packM as
2✔
921
  {-# INLINE packM #-}
922
  unpackM = do
2✔
923
    Length n <- unpackM
2✔
924
    marr <- unpackLiftST (newArray n (error "Uninitialized"))
1✔
925
    let fill !i = when (i < n) $ do
2✔
926
          e <- unpackM
2✔
927
          unpackLiftST (writeArray marr i e)
2✔
928
          fill (i + 1)
2✔
929
    fill 0
2✔
930
    unpackLiftST (unsafeFreezeArray marr)
2✔
931
  {-# INLINE unpackM #-}
932

933
-- | Tail recursive version of `replicateM`
934
replicateTailM :: Monad m => Int -> m a -> m [a]
935
replicateTailM n f = go n []
2✔
936
  where
937
    go i !acc
2✔
938
      | i <= 0 = pure $ reverse acc
2✔
939
      | otherwise = f >>= \x -> go (i - 1) (x : acc)
1✔
940
{-# INLINE replicateTailM #-}
941

942
instance MemPack ByteArray where
2✔
943
  packedByteCount ba =
2✔
944
    let len = bufferByteCount ba
2✔
945
     in packedByteCount (Length len) + len
2✔
946
  {-# INLINE packedByteCount #-}
947
  packM ba@(ByteArray ba#) = do
2✔
948
    let !len@(I# len#) = bufferByteCount ba
2✔
949
    packM (Length len)
2✔
950
    I# curPos# <- state $ \i -> (i, i + len)
2✔
951
    MutableByteArray mba# <- ask
2✔
952
    lift_# (copyByteArray# ba# 0# mba# curPos# len#)
2✔
953
  {-# INLINE packM #-}
954
  unpackM = unpackByteArray False
2✔
955
  {-# INLINE unpackM #-}
956

957
instance (Typeable a, Prim a) => MemPack (PrimArray a) where
2✔
958
  packedByteCount pa =
2✔
959
    let len = I# (sizeOf# (undefined :: a)) * sizeofPrimArray pa
1✔
960
     in packedByteCount (Length len) + len
2✔
961
  {-# INLINE packedByteCount #-}
962
  packM pa@(PrimArray ba#) = do
2✔
963
    let !len@(I# len#) = I# (sizeOf# (undefined :: a)) * sizeofPrimArray pa
1✔
964
    packM (Length len)
2✔
965
    I# curPos# <- state $ \i -> (i, i + len)
2✔
966
    MutableByteArray mba# <- ask
2✔
967
    lift_# (copyByteArray# ba# 0# mba# curPos# len#)
2✔
968
  {-# INLINE packM #-}
969
  unpackM = (\(ByteArray ba#) -> PrimArray ba#) <$> unpackByteArray False
2✔
970
  {-# INLINE unpackM #-}
971

972
#if !MIN_VERSION_primitive(0,8,0)
973
instance MemPack Prim.ByteArray where
974
  packedByteCount ba =
975
    let len = bufferByteCount ba
976
     in packedByteCount (Length len) + len
977
  {-# INLINE packedByteCount #-}
978
  packM ba@(Prim.ByteArray ba#) = do
979
    let !len@(I# len#) = bufferByteCount ba
980
    packM (Length len)
981
    I# curPos# <- state $ \i -> (i, i + len)
982
    MutableByteArray mba# <- ask
983
    lift_# (copyByteArray# ba# 0# mba# curPos# len#)
984
  {-# INLINE packM #-}
985
  unpackM = (\(ByteArray ba#) -> Prim.ByteArray ba#) <$> unpackByteArray False
986
  {-# INLINE unpackM #-}
987
#endif
988

989
instance MemPack ShortByteString where
×
990
  packedByteCount ba =
×
991
    let len = bufferByteCount ba
×
992
     in packedByteCount (Length len) + len
×
993
  {-# INLINE packedByteCount #-}
UNCOV
994
  packM = packM . byteArrayFromShortByteString
×
995
  {-# INLINE packM #-}
UNCOV
996
  unpackM = byteArrayToShortByteString <$> unpackByteArray False
×
997
  {-# INLINE unpackM #-}
998

999
instance MemPack ByteString where
2✔
1000
  packedByteCount ba =
2✔
1001
    let len = bufferByteCount ba
2✔
1002
     in packedByteCount (Length len) + len
2✔
1003
  {-# INLINE packedByteCount #-}
1004
  packM bs = packM (Length (bufferByteCount bs)) >> packByteStringM bs
2✔
1005
  {-# INLINE packM #-}
1006
  unpackM = pinnedByteArrayToByteString <$> unpackByteArray True
2✔
1007
  {-# INLINE unpackM #-}
1008

1009
{- FOURMOLU_DISABLE -}
1010
instance MemPack BSL.ByteString where
2✔
1011
#if WORD_SIZE_IN_BITS == 32
1012
  packedByteCount bsl =
1013
    let len64 = BSL.length bsl
1014
        len = fromIntegral len64
1015
     in if len64 <= fromIntegral (maxBound :: Int)
1016
        then packedByteCount (Length len) + len
1017
        else error $ mconcat [ "Cannot pack more that '2 ^ 31 - 1' bytes on a 32bit architecture, "
1018
                             , "but tried to pack a lazy ByteString with "
1019
                             , show len64
1020
                             , " bytes"
1021
                             ]
1022
#elif WORD_SIZE_IN_BITS == 64
1023
  packedByteCount bsl =
2✔
1024
    let len = fromIntegral (BSL.length bsl)
2✔
1025
     in packedByteCount (Length len) + len
2✔
1026
#else
1027
#error "Only 32bit and 64bit systems are supported"
1028
#endif
1029
  {-# INLINE packedByteCount #-}
1030
  packM bsl = do
2✔
1031
    let !len = fromIntegral (BSL.length bsl)
2✔
1032
        go BSL.Empty = pure ()
1✔
1033
        go (BSL.Chunk bs rest) = packByteStringM bs >> go rest
2✔
1034
    packM (Length len)
2✔
1035
    go bsl
2✔
1036
  {-# INLINE packM #-}
1037
  unpackM = do
2✔
1038
    Length len <- unpackM
2✔
1039
    let c = BSL.defaultChunkSize
2✔
1040
        go n
2✔
1041
          | n == 0 = pure BSL.Empty
2✔
1042
          | n <= c = BSL.Chunk <$> unpackByteStringM n <*> pure BSL.Empty
1✔
UNCOV
1043
          | otherwise = BSL.Chunk <$> unpackByteStringM c <*> go (n - c)
×
1044
    go len
2✔
1045
  {-# INLINE unpackM #-}
1046

1047
instance MemPack Text where
2✔
1048
#if MIN_VERSION_text(2,0,0)
1049
  packedByteCount (Text _ _ byteCount) = packedByteCount (Length byteCount) + byteCount
2✔
1050
  packM (Text (T.ByteArray ba#) (I# offset#) len@(I# len#)) = do
2✔
1051
    packM (Length len)
2✔
1052
    I# curPos# <- state $ \i -> (i, i + len)
2✔
1053
    MutableByteArray mba# <- ask
2✔
1054
    lift_# (copyByteArray# ba# offset# mba# curPos# len#)
2✔
1055
#else
1056
  -- FIXME: This is very inefficient and hopefully will be fixed at some point.  It requires some
1057
  -- clever change to the MemPack interface in order to allow memoization between `packedByteCount`
1058
  -- and `packM`
1059
  packedByteCount = packedByteCount . T.encodeUtf8
1060
  packM = packM . T.encodeUtf8
1061
#endif
1062
  {-# INLINE packedByteCount #-}
1063
  {-# INLINE packM #-}
1064
  unpackM = do
2✔
1065
    bs <- unpackM
2✔
1066
    case T.decodeUtf8' bs of
2✔
1067
      Right txt -> pure txt
2✔
UNCOV
1068
      Left exc -> F.fail $ show exc
×
1069
  {-# INLINE unpackM #-}
1070
{- FOURMOLU_ENABLE -}
1071

1072
-- | This is the implementation of `unpackM` for `ByteArray`, `ByteString` and `ShortByteString`
1073
unpackByteArray :: Buffer b => Bool -> Unpack s b ByteArray
1074
unpackByteArray isPinned = unpackByteArrayLen isPinned . unLength =<< unpackM
2✔
1075
{-# INLINE unpackByteArray #-}
1076

1077
-- | Unpack a `ByteArray` with supplied number of bytes.
1078
--
1079
-- Similar to `unpackByteArray`, except it does not unpack a length.
1080
--
1081
-- @since 0.1.1
1082
unpackByteArrayLen :: Buffer b => Bool -> Int -> Unpack s b ByteArray
1083
unpackByteArrayLen isPinned len@(I# len#) = do
2✔
1084
  I# curPos# <- guardAdvanceUnpack len
2✔
1085
  buf <- ask
2✔
1086
  pure $! runST $ do
2✔
1087
    mba@(MutableByteArray mba#) <- newMutableByteArray isPinned len
2✔
1088
    buffer
2✔
1089
      buf
2✔
1090
      (\ba# off# -> st_ (copyByteArray# ba# (curPos# +# off#) mba# 0# len#))
2✔
1091
      (\addr# -> st_ (copyAddrToByteArray# (addr# `plusAddr#` curPos#) mba# 0# len#))
2✔
1092
    freezeMutableByteArray mba
2✔
1093
{-# INLINE unpackByteArrayLen #-}
1094

1095
-- | Increment the offset counter of `Pack` monad by then number of `packedByteCount` and
1096
-- return the starting offset.
1097
packIncrement :: MemPack a => a -> Pack s Int
1098
packIncrement a =
2✔
1099
  state $ \i ->
2✔
1100
    let !n = i + packedByteCount a
1✔
1101
     in (i, n)
2✔
1102
{-# INLINE packIncrement #-}
1103

1104
-- | Increment the offset counter of `Unpack` monad by the supplied number of
1105
-- bytes. Returns the original offset or fails with `RanOutOfBytesError` whenever there is
1106
-- not enough bytes in the `Buffer`.
1107
guardAdvanceUnpack :: Buffer b => Int -> Unpack s b Int
1108
guardAdvanceUnpack n@(I# n#) = do
2✔
1109
  buf <- ask
2✔
1110
  let !len = bufferByteCount buf
2✔
1111
  -- Check that we still have enough bytes, while guarding against integer overflow.
1112
  join $ state $ \i@(I# i#) ->
2✔
1113
    case addIntC# i# n# of
2✔
1114
      (# adv#, 0# #)
1115
        | len >= I# adv# -> (pure i, I# adv#)
2✔
1116
      _ -> (failOutOfBytes i len n, i)
1✔
1117
{-# INLINE guardAdvanceUnpack #-}
1118

1119
failOutOfBytes :: Int -> Int -> Int -> Unpack s b a
1120
failOutOfBytes i len n =
2✔
1121
  failUnpack $
2✔
1122
    toSomeError $
2✔
1123
      RanOutOfBytesError
2✔
1124
        { ranOutOfBytesRead = i
2✔
1125
        , ranOutOfBytesAvailable = len
2✔
1126
        , ranOutOfBytesRequested = n
2✔
1127
        }
1128
{-# NOINLINE failOutOfBytes #-}
1129

1130
-- | Serialize a type into an unpinned `ByteArray`
1131
--
1132
-- ====__Examples__
1133
--
1134
-- >>> :set -XTypeApplications
1135
-- >>> unpack @[Int] $ pack ([1,2,3,4,5] :: [Int])
1136
-- Right [1,2,3,4,5]
1137
pack :: forall a. (MemPack a, HasCallStack) => a -> ByteArray
1138
pack = packByteArray False
2✔
1139
{-# INLINE pack #-}
1140

1141
-- | Serialize a type into a pinned `ByteString`
1142
packByteString :: forall a. (MemPack a, HasCallStack) => a -> ByteString
1143
packByteString = pinnedByteArrayToByteString . packByteArray True
2✔
1144
{-# INLINE packByteString #-}
1145

1146
-- | Serialize a type into any `Buffer`
1147
--
1148
-- prop> pack xs == packBuffer xs
1149
--
1150
-- prop> packByteString xs == packBuffer xs
1151
--
1152
-- ====__Examples__
1153
--
1154
-- >>> :set -XTypeApplications
1155
-- >>> import qualified Data.Vector.Primitive as VP
1156
-- >>> import Data.Word (Word8)
1157
-- >>> unpack @[Int] $ packBuffer @[Int] @(VP.Vector Word8) [1,2,3,4,5]
1158
-- Right [1,2,3,4,5]
1159
--
1160
-- @since 0.2.0
1161
packBuffer :: forall a b. (MemPack a, Buffer b, HasCallStack) => a -> b
NEW
1162
packBuffer a =
×
NEW
1163
  case packByteArray (bufferHasToBePinned @b) a of
×
NEW
1164
    ByteArray ba -> mkBuffer ba
×
1165
{-# INLINE packBuffer #-}
1166

1167
-- | Serialize a type into an unpinned `ShortByteString`
1168
packShortByteString :: forall a. (MemPack a, HasCallStack) => a -> ShortByteString
UNCOV
1169
packShortByteString = byteArrayToShortByteString . pack
×
1170
{-# INLINE packShortByteString #-}
1171

1172
-- | Same as `pack`, but allows controlling the pinnedness of allocated memory
1173
packByteArray ::
1174
  forall a.
1175
  (MemPack a, HasCallStack) =>
1176
  -- | Should the array be allocated in pinned memory?
1177
  Bool ->
1178
  a ->
1179
  ByteArray
1180
packByteArray isPinned a =
2✔
1181
  packWithByteArray isPinned (typeName @a) (packedByteCount a) (packM a)
1✔
1182
{-# INLINE packByteArray #-}
1183

1184
-- | Allocate a `MutableByteArray` and run the supplied `Pack` action on it. Freezes the
1185
-- allocated `MutableByteArray` at the end yielding the immutable `ByteArray` with
1186
-- serialization packed into it.
1187
packWithByteArray ::
1188
  HasCallStack =>
1189
  -- | Should the array be allocated in pinned memory?
1190
  Bool ->
1191
  -- | Name of the type that is being serialized. Used for error reporting
1192
  String ->
1193
  -- | Size of the array to be allocated
1194
  Int ->
1195
  (forall s. Pack s ()) ->
1196
  ByteArray
1197
packWithByteArray isPinned name len packerM =
2✔
1198
  runST $ packWithMutableByteArray isPinned name len packerM >>= freezeMutableByteArray
1✔
1199
{-# INLINE packWithByteArray #-}
1200

1201
-- | Same as `packByteArray`, but produces a mutable array instead
1202
packMutableByteArray ::
1203
  forall a s.
1204
  (MemPack a, HasCallStack) =>
1205
  -- | Should the array be allocated in pinned memory?
1206
  Bool ->
1207
  a ->
1208
  ST s (MutableByteArray s)
UNCOV
1209
packMutableByteArray isPinned a =
×
1210
  packWithMutableByteArray isPinned (typeName @a) (packedByteCount a) (packM a)
×
1211
{-# INLINE packMutableByteArray #-}
1212

1213
-- | Allocate a `MutableByteArray` and run the supplied `Pack` action on it.
1214
packWithMutableByteArray ::
1215
  forall s.
1216
  HasCallStack =>
1217
  -- | Should the array be allocated in pinned memory?
1218
  Bool ->
1219
  -- | Name of the type that is being serialized. Used for error reporting
1220
  String ->
1221
  -- | Size of the mutable array to be allocated
1222
  Int ->
1223
  -- | Packing action to be executed on the mutable buffer
1224
  Pack s () ->
1225
  ST s (MutableByteArray s)
1226
packWithMutableByteArray isPinned name len packerM = do
2✔
1227
  mba <- newMutableByteArray isPinned len
2✔
1228
  filledBytes <- execStateT (runPack packerM mba) 0
2✔
1229
  when (filledBytes /= len) $ errorFilledBytes name filledBytes len
1✔
1230
  pure mba
2✔
1231
{-# INLINEABLE packWithMutableByteArray #-}
1232

1233
-- | This is a critical error, therefore we are not gracefully failing this unpacking
1234
errorFilledBytes :: HasCallStack => [Char] -> Int -> Int -> a
UNCOV
1235
errorFilledBytes name filledBytes len =
×
1236
  if filledBytes < len
×
1237
    then
UNCOV
1238
      error $
×
1239
        "Some bug in 'packM' was detected. Buffer of length " <> showBytes len
×
1240
          ++ " was not fully filled while packing " <> name
×
1241
          ++ ". Unfilled " <> showBytes (len - filledBytes) <> "."
×
1242
    else
UNCOV
1243
      error $
×
1244
        "Potential buffer overflow. Some bug in 'packM' was detected while packing " <> name
×
1245
          ++ ". Filled " <> showBytes (filledBytes - len) <> " more than allowed into a buffer of length "
×
1246
          ++ show len
×
1247
{-# NOINLINE errorFilledBytes #-}
1248

1249
-- | Helper function for packing a `ByteString` without its length being packed first.
1250
--
1251
-- @since 0.1.1
1252
packByteStringM :: ByteString -> Pack s ()
1253
packByteStringM bs = do
2✔
1254
  let !len@(I# len#) = bufferByteCount bs
2✔
1255
  I# curPos# <- state $ \i -> (i, i + len)
2✔
1256
  Pack $ \(MutableByteArray mba#) -> lift $ withAddrByteStringST bs $ \addr# ->
2✔
1257
    st_ (copyAddrToByteArray# addr# mba# curPos# len#)
2✔
1258
{-# INLINE packByteStringM #-}
1259

1260
-- | Unpack a `ByteString` of a specified size.
1261
--
1262
-- @since 0.1.1
1263
unpackByteStringM ::
1264
  Buffer b =>
1265
  -- | number of bytes to unpack
1266
  Int ->
1267
  Unpack s b ByteString
1268
unpackByteStringM len = pinnedByteArrayToByteString <$> unpackByteArrayLen True len
2✔
1269
{-# INLINE unpackByteStringM #-}
1270

1271
-- | Unpack a memory `Buffer` into a type using its `MemPack` instance. Besides the
1272
-- unpacked type it also returns an index into a buffer where unpacked has stopped.
1273
unpackLeftOver :: forall a b. (MemPack a, Buffer b, HasCallStack) => b -> Fail SomeError (a, Int)
1274
unpackLeftOver b = FailT $ pure $ runST $ runFailAggT $ unpackLeftOverST b
2✔
1275
{-# INLINE unpackLeftOver #-}
1276

1277
-- | Unpack a memory `Buffer` into a type using its `MemPack` instance. Besides the
1278
-- unpacked type it also returns an index into a buffer where unpacked has stopped.
1279
unpackLeftOverST ::
1280
  forall a b s. (MemPack a, Buffer b, HasCallStack) => b -> FailT SomeError (ST s) (a, Int)
1281
unpackLeftOverST b = do
2✔
1282
  let len = bufferByteCount b
2✔
1283
  res@(_, consumedBytes) <- runStateT (runUnpack unpackM b) 0
2✔
1284
  when (consumedBytes > len) $ errorLeftOver (typeName @a) consumedBytes len
1✔
1285
  pure res
2✔
1286
{-# INLINEABLE unpackLeftOverST #-}
1287

1288
-- | This is a critical error, therefore we are not gracefully failing this unpacking
1289
errorLeftOver :: HasCallStack => String -> Int -> Int -> a
UNCOV
1290
errorLeftOver name consumedBytes len =
×
1291
  error $
×
1292
    "Potential buffer overflow. Some bug in 'unpackM' was detected while unpacking " <> name
×
1293
      ++ ". Consumed " <> showBytes (consumedBytes - len) <> " more than allowed from a buffer of length "
×
1294
      ++ show len
×
1295
{-# NOINLINE errorLeftOver #-}
1296

1297
-- | Unpack a memory `Buffer` into a type using its `MemPack` instance. Besides potential
1298
-- unpacking failures due to a malformed buffer it will also fail the supplied `Buffer`
1299
-- was not fully consumed. Use `unpackLeftOver`, whenever a partially consumed buffer is
1300
-- possible.
1301
unpack :: forall a b. (MemPack a, Buffer b, HasCallStack) => b -> Either SomeError a
1302
unpack = first fromMultipleErrors . runFailAgg . unpackFail
2✔
1303
{-# INLINEABLE unpack #-}
1304

1305
-- | Same as `unpack` except fails in a `Fail` monad, instead of `Either`.
1306
unpackFail :: forall a b. (MemPack a, Buffer b, HasCallStack) => b -> Fail SomeError a
1307
unpackFail b = do
2✔
1308
  let len = bufferByteCount b
2✔
1309
  (a, consumedBytes) <- unpackLeftOver b
2✔
1310
  when (consumedBytes /= len) $ unpackFailNotFullyConsumed (typeName @a) consumedBytes len
2✔
1311
  pure a
2✔
1312
{-# INLINEABLE unpackFail #-}
1313

1314
unpackFailNotFullyConsumed :: Applicative m => String -> Int -> Int -> FailT SomeError m a
1315
unpackFailNotFullyConsumed name consumedBytes len =
2✔
1316
  failT $
2✔
1317
    toSomeError $
2✔
1318
      NotFullyConsumedError
2✔
1319
        { notFullyConsumedRead = consumedBytes
2✔
1320
        , notFullyConsumedAvailable = len
2✔
1321
        , notFullyConsumedTypeName = name
2✔
1322
        }
1323
{-# NOINLINE unpackFailNotFullyConsumed #-}
1324

1325
-- | Same as `unpackFail` except fails in any `MonadFail`, instead of `Fail`.
1326
unpackMonadFail :: forall a b m. (MemPack a, Buffer b, F.MonadFail m) => b -> m a
UNCOV
1327
unpackMonadFail = either (F.fail . show) pure . unpack
×
1328
{-# INLINEABLE unpackMonadFail #-}
1329

1330
-- | Same as `unpack` except throws a runtime exception upon a failure
1331
unpackError :: forall a b. (MemPack a, Buffer b, HasCallStack) => b -> a
1332
unpackError = errorFail . unpackFail
2✔
1333
{-# INLINEABLE unpackError #-}
1334

1335
-- | Variable length encoding for bounded types. This type of encoding will use less
1336
-- memory for small values, but for larger values it will consume more memory and will be
1337
-- slower during packing/unpacking.
UNCOV
1338
newtype VarLen a = VarLen {unVarLen :: a}
×
1339
  deriving (Eq, Ord, Show, Bounded, Enum, Num, Real, Integral, Bits, FiniteBits)
1✔
1340

1341
instance MemPack (VarLen Word16) where
2✔
1342
  packedByteCount = packedVarLenByteCount
2✔
1343
  {-# INLINE packedByteCount #-}
1344
  packM v@(VarLen x) = p7 (p7 (p7 (errorTooManyBits "Word16"))) (numBits - 7)
1✔
1345
    where
1346
      p7 = packIntoCont7 x
2✔
1347
      {-# INLINE p7 #-}
1348
      numBits = packedVarLenByteCount v * 7
2✔
1349
  {-# INLINE packM #-}
1350
  unpackM = do
2✔
1351
    let d7 = unpack7BitVarLen
2✔
1352
        {-# INLINE d7 #-}
1353
    VarLen <$> d7 (d7 (unpack7BitVarLenLast 0b_1111_1100)) 0 0
2✔
1354
  {-# INLINE unpackM #-}
1355

1356
instance MemPack (VarLen Word32) where
2✔
1357
  packedByteCount = packedVarLenByteCount
2✔
1358
  {-# INLINE packedByteCount #-}
1359
  packM v@(VarLen x) = p7 (p7 (p7 (p7 (p7 (errorTooManyBits "Word32"))))) (numBits - 7)
1✔
1360
    where
1361
      p7 = packIntoCont7 x
2✔
1362
      {-# INLINE p7 #-}
1363
      numBits = packedVarLenByteCount v * 7
2✔
1364
  {-# INLINE packM #-}
1365
  unpackM = do
2✔
1366
    let d7 = unpack7BitVarLen
2✔
1367
        {-# INLINE d7 #-}
1368
    VarLen <$> d7 (d7 (d7 (d7 (unpack7BitVarLenLast 0b_1111_0000)))) 0 0
2✔
1369
  {-# INLINE unpackM #-}
1370

1371
instance MemPack (VarLen Word64) where
2✔
1372
  packedByteCount = packedVarLenByteCount
2✔
1373
  {-# INLINE packedByteCount #-}
1374
  packM v@(VarLen x) =
2✔
1375
    p7 (p7 (p7 (p7 (p7 (p7 (p7 (p7 (p7 (p7 (errorTooManyBits "Word64")))))))))) (numBits - 7)
1✔
1376
    where
1377
      p7 = packIntoCont7 x
2✔
1378
      {-# INLINE p7 #-}
1379
      numBits = packedVarLenByteCount v * 7
2✔
1380
  {-# INLINE packM #-}
1381
  unpackM = do
2✔
1382
    let d7 = unpack7BitVarLen
2✔
1383
        {-# INLINE d7 #-}
1384
    VarLen <$> d7 (d7 (d7 (d7 (d7 (d7 (d7 (d7 (d7 (unpack7BitVarLenLast 0b_1111_1110))))))))) 0 0
2✔
1385
  {-# INLINE unpackM #-}
1386

1387
instance MemPack (VarLen Word) where
2✔
1388
  packedByteCount = packedVarLenByteCount
2✔
1389
  {-# INLINE packedByteCount #-}
1390
#if WORD_SIZE_IN_BITS == 32
1391
  packM v@(VarLen x) = p7 (p7 (p7 (p7 (p7 (errorTooManyBits "Word"))))) (numBits - 7)
1392
    where
1393
      p7 = packIntoCont7 x
1394
      {-# INLINE p7 #-}
1395
      numBits = packedVarLenByteCount v * 7
1396
  {-# INLINE packM #-}
1397
  unpackM = do
1398
    let d7 = unpack7BitVarLen
1399
        {-# INLINE d7 #-}
1400
    VarLen <$> d7 (d7 (d7 (d7 (unpack7BitVarLenLast 0b_1111_0000)))) 0 0
1401
  {-# INLINE unpackM #-}
1402
#elif WORD_SIZE_IN_BITS == 64
1403
  packM v@(VarLen x) =
2✔
1404
    p7 (p7 (p7 (p7 (p7 (p7 (p7 (p7 (p7 (p7 (errorTooManyBits "Word")))))))))) (numBits - 7)
1✔
1405
    where
1406
      p7 = packIntoCont7 x
2✔
1407
      {-# INLINE p7 #-}
1408
      numBits = packedVarLenByteCount v * 7
2✔
1409
  {-# INLINE packM #-}
1410
  unpackM = do
2✔
1411
    let d7 = unpack7BitVarLen
2✔
1412
        {-# INLINE d7 #-}
1413
    VarLen <$> d7 (d7 (d7 (d7 (d7 (d7 (d7 (d7 (d7 (unpack7BitVarLenLast 0b_1111_1110))))))))) 0 0
2✔
1414
  {-# INLINE unpackM #-}
1415
#else
1416
#error "Only 32bit and 64bit systems are supported"
1417
#endif
1418

1419
packedVarLenByteCount :: FiniteBits b => VarLen b -> Int
1420
packedVarLenByteCount (VarLen x) =
2✔
1421
  case (finiteBitSize x - countLeadingZeros x) `quotRem` 7 of
1✔
1422
    (0, 0) -> 1
2✔
1423
    (q, 0) -> q
2✔
1424
    (q, _) -> q + 1
2✔
1425
{-# INLINE packedVarLenByteCount #-}
1426

1427
errorTooManyBits :: HasCallStack => String -> a
UNCOV
1428
errorTooManyBits name =
×
1429
  error $ "Bug detected. Trying to pack more bits for " ++ name ++ " than it should be posssible"
×
1430
{-# NOINLINE errorTooManyBits #-}
1431

1432
packIntoCont7 ::
1433
  (Bits t, Integral t) => t -> (Int -> Pack s ()) -> Int -> Pack s ()
1434
packIntoCont7 x cont n
2✔
1435
  | n <= 0 = packM (fromIntegral @_ @Word8 x .&. complement topBit8)
2✔
1436
  | otherwise = do
1✔
1437
      packM (fromIntegral @_ @Word8 (x `shiftR` n) .|. topBit8)
2✔
1438
      cont (n - 7)
2✔
1439
  where
1440
    topBit8 :: Word8
1441
    !topBit8 = 0b_1000_0000
2✔
1442
{-# INLINE packIntoCont7 #-}
1443

1444
-- | Decode a variable length integral value that is encoded with 7 bits of data
1445
-- and the most significant bit (MSB), the 8th bit is set whenever there are
1446
-- more bits following. Continuation style allows us to avoid
1447
-- recursion. Removing loops is good for performance.
1448
unpack7BitVarLen ::
1449
  (Num a, Bits a, Buffer b) =>
1450
  -- | Continuation that will be invoked if MSB is set
1451
  (Word8 -> a -> Unpack s b a) ->
1452
  -- | Will be set either to 0 initially or to the very first unmodified byte, which is
1453
  -- guaranteed to have the first bit set.
1454
  Word8 ->
1455
  -- | Accumulator
1456
  a ->
1457
  Unpack s b a
1458
unpack7BitVarLen cont firstByte !acc = do
2✔
1459
  b8 :: Word8 <- unpackM
2✔
1460
  if b8 `testBit` 7
2✔
1461
    then
1462
      cont (if firstByte == 0 then b8 else firstByte) (acc `shiftL` 7 .|. fromIntegral (b8 `clearBit` 7))
2✔
1463
    else pure (acc `shiftL` 7 .|. fromIntegral b8)
2✔
1464
{-# INLINE unpack7BitVarLen #-}
1465

1466
unpack7BitVarLenLast ::
1467
  forall t b s.
1468
  (Num t, Bits t, MemPack t, Buffer b) =>
1469
  Word8 ->
1470
  Word8 ->
1471
  t ->
1472
  Unpack s b t
1473
unpack7BitVarLenLast mask firstByte acc = do
2✔
1474
  res <- unpack7BitVarLen (\_ _ -> F.fail "Too many bytes.") firstByte acc
1✔
1475
  -- Only while decoding the last 7bits we check if there was too many
1476
  -- bits supplied at the beginning.
1477
  unless (firstByte .&. mask == 0b_1000_0000) $ unpack7BitVarLenLastFail (typeName @t) firstByte
1✔
1478
  pure res
2✔
1479
{-# INLINE unpack7BitVarLenLast #-}
1480

1481
unpack7BitVarLenLastFail :: F.MonadFail m => String -> Word8 -> m a
UNCOV
1482
unpack7BitVarLenLastFail name firstByte =
×
1483
  F.fail $
×
1484
    "Unexpected bits for "
×
1485
      ++ name
×
1486
      ++ " were set in the first byte of 'VarLen': 0x" <> showHex firstByte ""
×
1487
{-# NOINLINE unpack7BitVarLenLastFail #-}
1488

1489
-- | This is a helper type useful for serializing number of elements in data
1490
-- structures. It uses `VarLen` underneath, since sizes of common data structures aren't
1491
-- too big. It also prevents negative values from being serialized and deserialized.
1492
newtype Length = Length {unLength :: Int}
2✔
UNCOV
1493
  deriving (Eq, Show, Num)
×
1494

1495
instance Bounded Length where
1496
  minBound = 0
2✔
1497
  maxBound = Length maxBound
2✔
1498

1499
instance Enum Length where
1✔
1500
  toEnum n
2✔
1501
    | n < 0 = error $ "toEnum: Length cannot be negative: " ++ show n
1✔
1502
    | otherwise = Length n
1✔
1503
  fromEnum = unLength
2✔
1504

1505
instance MemPack Length where
2✔
1506
  packedByteCount = packedByteCount . VarLen . fromIntegral @Int @Word . unLength
2✔
1507
  packM (Length n)
2✔
1508
    | n < 0 = packLengthError n
1✔
1509
    | otherwise = packM (VarLen (fromIntegral @Int @Word n))
1✔
1510
  {-# INLINE packM #-}
1511
  unpackM = do
2✔
1512
    VarLen (w :: Word) <- unpackM
2✔
1513
    when (testBit w (finiteBitSize w - 1)) $ upackLengthFail w
1✔
1514
    pure $ Length $ fromIntegral @Word @Int w
2✔
1515
  {-# INLINE unpackM #-}
1516

1517
packLengthError :: Int -> a
UNCOV
1518
packLengthError n = error $ "Length cannot be negative. Supplied: " ++ show n
×
1519
{-# NOINLINE packLengthError #-}
1520

1521
upackLengthFail :: F.MonadFail m => Word -> m a
1522
upackLengthFail w =
2✔
1523
  F.fail $ "Attempt to unpack negative length was detected: " ++ show (fromIntegral @Word @Int w)
1✔
1524
{-# NOINLINE upackLengthFail #-}
1525

1526
-- | This is a helper type that is useful for creating `MemPack` instances for sum types.
1527
newtype Tag = Tag {unTag :: Word8}
2✔
1528
  deriving (Eq, Ord, Show, Num, Enum, Bounded)
1✔
1529

1530
-- Manually defined instance, since ghc-8.6 has issues with deriving MemPack
1531
instance MemPack Tag where
2✔
1532
  packedByteCount _ = packedTagByteCount
2✔
1533
  {-# INLINE packedByteCount #-}
1534
  unpackM = unpackTagM
2✔
1535
  {-# INLINE unpackM #-}
1536
  packM = packTagM
2✔
1537
  {-# INLINE packM #-}
1538

1539
packedTagByteCount :: Int
1540
packedTagByteCount = SIZEOF_WORD8
2✔
1541
{-# INLINE packedTagByteCount #-}
1542

1543
unpackTagM :: Buffer b => Unpack s b Tag
1544
unpackTagM = Tag <$> unpackM
2✔
1545
{-# INLINE unpackTagM #-}
1546

1547
packTagM :: Tag -> Pack s ()
1548
packTagM = packM . unTag
2✔
1549
{-# INLINE packTagM #-}
1550

1551
unknownTagM :: forall a m b. (MemPack a, F.MonadFail m) => Tag -> m b
UNCOV
1552
unknownTagM (Tag t) = F.fail $ "Unrecognized Tag: " ++ show t ++ " while decoding " ++ typeName @a
×
1553

1554
lift_# :: (State# s -> State# s) -> Pack s ()
1555
lift_# f = Pack $ \_ -> lift $ st_ f
2✔
1556
{-# INLINE lift_# #-}
1557

1558
st_ :: (State# s -> State# s) -> ST s ()
1559
st_ f = ST $ \s# -> (# f s#, () #)
2✔
1560
{-# INLINE st_ #-}
1561

1562
-- | Lift an `ST` action into the `Pack` monad
1563
--
1564
-- @since 0.2.0
1565
packLiftST :: ST s a -> Pack s a
NEW
1566
packLiftST st = Pack (\_ -> StateT (\i -> (,i) <$> st))
×
1567
{-# INLINE packLiftST #-}
1568

1569
-- | Lift an `ST` action into the `Unpack` monad
1570
--
1571
-- @since 0.2.0
1572
unpackLiftST :: ST s a -> Unpack s b a
1573
unpackLiftST st = Unpack (\_ -> StateT (\i -> FailT (Right . (,i) <$> st)))
2✔
1574
{-# INLINE unpackLiftST #-}
STATUS · Troubleshooting · Open an Issue · Sales · Support · CAREERS · ENTERPRISE · START FREE · SCHEDULE DEMO
ANNOUNCEMENTS · TWITTER · TOS & SLA · Supported CI Services · What's a CI service? · Automated Testing

© 2026 Coveralls, Inc