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

lehins / mempack / 29

19 Sep 2024 04:15PM UTC coverage: 87.079%. Remained the same
29

push

github

lehins
Improve haddock a bit

647 of 743 relevant lines covered (87.08%)

1.66 hits per line

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

90.36
/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 ScopedTypeVariables #-}
13
{-# LANGUAGE TypeApplications #-}
14
{-# LANGUAGE UnboxedTuples #-}
15

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

28
  -- * Packing
29
  pack,
30
  packByteArray,
31
  packByteString,
32
  packShortByteString,
33
  packMutableByteArray,
34

35
  -- ** Helpers
36
  packIncrement,
37
  guardAdvanceUnpack,
38

39
  -- * Unpacking
40
  unpack,
41
  unpackFail,
42
  unpackMonadFail,
43
  unpackError,
44
  unpackLeftOver,
45

46
  -- ** Helpers
47
  failUnpack,
48
  unpackByteArray,
49

50
  -- * Helper packers
51
  VarLen (..),
52
  Length (..),
53
  Tag (..),
54
  packTagM,
55
  unpackTagM,
56
  unknownTagM,
57
  packedTagByteCount,
58

59
  -- * Internal utilities
60
  replicateTailM,
61
  lift_#,
62
  st_,
63

64
  -- * Re-exports for @GeneralizedNewtypeDeriving@
65
  StateT (..),
66
  FailT (..),
67
) where
68

69
#include "MachDeps.h"
70

71
import Control.Applicative (Alternative (..))
72
import Control.Monad (join, unless, when)
73
import qualified Control.Monad.Fail as F
74
import Control.Monad.Reader (MonadReader (..), lift)
75
import Control.Monad.State.Strict (MonadState (..), StateT (..), execStateT)
76
import Control.Monad.Trans.Fail (Fail, FailT (..), errorFail, failT, runFailAgg)
77
import Data.Array.Byte (ByteArray (..), MutableByteArray (..))
78
import Data.Bifunctor (first)
79
import Data.Bits (Bits (..), FiniteBits (..))
80
import Data.ByteString (ByteString)
81
import Data.ByteString.Short (ShortByteString)
82
import Data.Char (ord)
83
import Data.Complex (Complex (..))
84
import Data.List (intercalate)
85
import Data.MemPack.Buffer
86
import Data.MemPack.Error
87
import Data.Ratio
88
import Data.Semigroup (Sum (..))
89
import Data.Typeable
90
import GHC.Exts
91
import GHC.Int
92
import GHC.ST (ST (..), runST)
93
import GHC.Stable (StablePtr (..))
94
import GHC.Stack (HasCallStack)
95
import GHC.Word
96
import Numeric (showHex)
97
import Prelude hiding (fail)
98
#if __GLASGOW_HASKELL__ >= 900
99
import GHC.Num.Integer (Integer (..), integerCheck)
100
import GHC.Num.Natural (Natural (..), naturalCheck)
101
#elif defined(MIN_VERSION_integer_gmp)
102
import GHC.Integer.GMP.Internals (Integer (..), BigNat(BN#), isValidInteger#)
103
import GHC.Natural (Natural (..), isValidNatural)
104
#else
105
#error "Only integer-gmp is supported for now for older compilers"
106
#endif
107
#if !(MIN_VERSION_base(4,13,0))
108
import Prelude (fail)
109
#endif
110

111
-- | Monad that is used for serializing data into a `MutableByteArray`. It is based on
112
-- `StateT` that tracks the current index into the `MutableByteArray` where next write is
113
-- expected to happen.
114
newtype Pack s a = Pack
115
  { runPack :: MutableByteArray s -> StateT Int (ST s) a
2✔
116
  }
117

118
instance Functor (Pack s) where
×
119
  fmap f (Pack p) = Pack $ \buf -> fmap f (p buf)
×
120
  {-# INLINE fmap #-}
121
instance Applicative (Pack s) where
×
122
  pure = Pack . const . pure
2✔
123
  {-# INLINE pure #-}
124
  Pack a1 <*> Pack a2 =
×
125
    Pack $ \buf -> a1 buf <*> a2 buf
×
126
  {-# INLINE (<*>) #-}
127
  Pack a1 *> Pack a2 =
×
128
    Pack $ \buf -> a1 buf *> a2 buf
×
129
  {-# INLINE (*>) #-}
130
instance Monad (Pack s) where
2✔
131
  Pack m1 >>= p =
2✔
132
    Pack $ \buf -> m1 buf >>= \res -> runPack (p res) buf
2✔
133
  {-# INLINE (>>=) #-}
134
instance MonadReader (MutableByteArray s) (Pack s) where
135
  ask = Pack pure
2✔
136
  {-# INLINE ask #-}
137
  local f (Pack p) = Pack (p . f)
×
138
  {-# INLINE local #-}
139
  reader f = Pack (pure . f)
×
140
  {-# INLINE reader #-}
141
instance MonadState Int (Pack s) where
142
  get = Pack $ const get
×
143
  {-# INLINE get #-}
144
  put = Pack . const . put
×
145
  {-# INLINE put #-}
146
  state = Pack . const . state
2✔
147
  {-# INLINE state #-}
148

149
-- | Monad that is used for deserializing data from a memory `Buffer`. It is based on
150
-- `StateT` that tracks the current index into the @`Buffer` a@, from where the next read
151
-- suppose to happen. Unpacking can `F.fail` with `F.MonadFail` instance or with
152
-- `failUnpack` that provides a more type safe way of failing using `Error` interface.
153
newtype Unpack b a = Unpack
154
  { runUnpack :: b -> StateT Int (Fail SomeError) a
2✔
155
  }
156

157
instance Functor (Unpack s) where
×
158
  fmap f (Unpack p) = Unpack $ \buf -> fmap f (p buf)
2✔
159
  {-# INLINE fmap #-}
160
instance Applicative (Unpack b) where
×
161
  pure = Unpack . const . pure
2✔
162
  {-# INLINE pure #-}
163
  Unpack a1 <*> Unpack a2 =
×
164
    Unpack $ \buf -> a1 buf <*> a2 buf
×
165
  {-# INLINE (<*>) #-}
166
  Unpack a1 *> Unpack a2 =
×
167
    Unpack $ \buf -> a1 buf *> a2 buf
×
168
  {-# INLINE (*>) #-}
169
instance Monad (Unpack b) where
×
170
  Unpack m1 >>= p =
2✔
171
    Unpack $ \buf -> m1 buf >>= \res -> runUnpack (p res) buf
2✔
172
  {-# INLINE (>>=) #-}
173
#if !(MIN_VERSION_base(4,13,0))
174
  fail = Unpack . const . F.fail
175
#endif
176
instance F.MonadFail (Unpack b) where
177
  fail = Unpack . const . F.fail
2✔
178
instance MonadReader b (Unpack b) where
179
  ask = Unpack pure
2✔
180
  {-# INLINE ask #-}
181
  local f (Unpack p) = Unpack (p . f)
×
182
  {-# INLINE local #-}
183
  reader f = Unpack (pure . f)
×
184
  {-# INLINE reader #-}
185
instance MonadState Int (Unpack b) where
186
  get = Unpack $ const get
×
187
  {-# INLINE get #-}
188
  put = Unpack . const . put
×
189
  {-# INLINE put #-}
190
  state = Unpack . const . state
2✔
191
  {-# INLINE state #-}
192

193
instance Alternative (Unpack b) where
×
194
  empty = Unpack $ \_ -> lift empty
×
195
  {-# INLINE empty #-}
196
  Unpack r1 <|> Unpack r2 =
2✔
197
    Unpack $ \buf ->
2✔
198
      case r1 buf of
2✔
199
        StateT m1 ->
200
          case r2 buf of
2✔
201
            StateT m2 -> StateT $ \s -> m1 s <|> m2 s
2✔
202
  {-# INLINE (<|>) #-}
203

204
-- | Failing unpacking with an `Error`.
205
failUnpack :: Error e => e -> Unpack b a
206
failUnpack e = Unpack $ \_ -> lift $ failT (toSomeError e)
2✔
207

208
-- | Efficient serialization interface that operates directly on memory buffers.
209
class MemPack a where
210
  -- | Name of the type that is being deserialized for error reporting. Default
211
  -- implementation relies on `Typeable`.
212
  typeName :: String
213
  default typeName :: Typeable a => String
214
  typeName = show (typeRep (Proxy @a))
1✔
215

216
  -- | Report the exact size in number of bytes that packed version of this type will
217
  -- occupy. It is very important to get this right, otherwise `packM` will result in a
218
  -- runtime exception. Another words this is the expected property that it should hold:
219
  --
220
  -- prop> packedByteCount a == bufferByteCount (pack a)
221
  packedByteCount :: a -> Int
222

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

227
  -- | Read binary representation of the type directly from the buffer, which can be
228
  -- accessed with `ask` when necessary. Direct reads from the buffer should be preceded
229
  -- with advancing the buffer offset with `MonadState` by the number of bytes that will
230
  -- be consumed from the buffer and making sure that no reads outside of the buffer can
231
  -- happen. Violation of these rules will lead to segfaults.
232
  unpackM :: Buffer b => Unpack b a
233

234
instance MemPack () where
×
235
  packedByteCount _ = 0
2✔
236
  {-# INLINE packedByteCount #-}
237
  packM _ = pure ()
1✔
238
  {-# INLINE packM #-}
239
  unpackM = pure ()
2✔
240
  {-# INLINE unpackM #-}
241

242
instance MemPack Bool where
2✔
243
  packedByteCount _ = packedTagByteCount
2✔
244
  {-# INLINE packedByteCount #-}
245
  packM x = packTagM $ if x then 1 else 0
2✔
246
  {-# INLINE packM #-}
247
  unpackM =
2✔
248
    unpackTagM >>= \case
2✔
249
      0 -> pure False
2✔
250
      1 -> pure True
2✔
251
      n -> F.fail $ "Invalid value detected for Bool: " ++ show n
×
252
  {-# INLINE unpackM #-}
253

254
instance MemPack a => MemPack (Maybe a) where
255
  typeName = "Maybe " ++ typeName @a
2✔
256
  packedByteCount = \case
2✔
257
    Nothing -> packedTagByteCount
2✔
258
    Just a -> packedTagByteCount + packedByteCount a
2✔
259
  {-# INLINE packedByteCount #-}
260
  packM = \case
2✔
261
    Nothing -> packTagM 0
2✔
262
    Just a -> packTagM 1 >> packM a
2✔
263
  {-# INLINE packM #-}
264
  unpackM =
2✔
265
    unpackTagM >>= \case
2✔
266
      0 -> pure Nothing
2✔
267
      1 -> Just <$> unpackM
2✔
268
      n -> unknownTagM @(Maybe a) n
×
269
  {-# INLINE unpackM #-}
270

271
instance (MemPack a, MemPack b) => MemPack (Either a b) where
272
  typeName = "Either " ++ typeName @a ++ " " ++ typeName @b
2✔
273
  packedByteCount = \case
2✔
274
    Left a -> packedTagByteCount + packedByteCount a
1✔
275
    Right b -> packedTagByteCount + packedByteCount b
1✔
276
  {-# INLINE packedByteCount #-}
277
  packM = \case
2✔
278
    Left a -> packTagM 0 >> packM a
2✔
279
    Right b -> packTagM 1 >> packM b
2✔
280
  {-# INLINE packM #-}
281
  unpackM =
2✔
282
    unpackTagM >>= \case
2✔
283
      0 -> Left <$> unpackM
2✔
284
      1 -> Right <$> unpackM
2✔
285
      n -> unknownTagM @(Either a b) n
×
286
  {-# INLINE unpackM #-}
287

288
instance MemPack Char where
2✔
289
  packedByteCount _ = SIZEOF_HSCHAR
2✔
290
  {-# INLINE packedByteCount #-}
291
  packM a@(C# a#) = do
2✔
292
    MutableByteArray mba# <- ask
2✔
293
    I# i# <- packIncrement a
1✔
294
    lift_# (writeWord8ArrayAsWideChar# mba# i# a#)
2✔
295
  {-# INLINE packM #-}
296
  unpackM = do
2✔
297
    I# i# <- guardAdvanceUnpack SIZEOF_HSCHAR
2✔
298
    buf <- ask
2✔
299
    let c =
2✔
300
          buffer
2✔
301
            buf
2✔
302
            (\ba# -> C# (indexWord8ArrayAsWideChar# ba# i#))
2✔
303
            (\addr# -> C# (indexWideCharOffAddr# (addr# `plusAddr#` i#) 0#))
2✔
304
    when (ord c > 0x10FFFF) $
2✔
305
      F.fail $
2✔
306
        "Out of bounds Char was detected: '\\x" ++ showHex (fromEnum c) "'"
×
307
    pure c
2✔
308
  {-# INLINE unpackM #-}
309

310
instance MemPack Float where
2✔
311
  packedByteCount _ = SIZEOF_FLOAT
2✔
312
  {-# INLINE packedByteCount #-}
313
  packM a@(F# a#) = do
2✔
314
    MutableByteArray mba# <- ask
2✔
315
    I# i# <- packIncrement a
1✔
316
    lift_# (writeWord8ArrayAsFloat# mba# i# a#)
2✔
317
  {-# INLINE packM #-}
318
  unpackM = do
2✔
319
    I# i# <- guardAdvanceUnpack SIZEOF_FLOAT
2✔
320
    buf <- ask
2✔
321
    pure $!
2✔
322
      buffer
2✔
323
        buf
2✔
324
        (\ba# -> F# (indexWord8ArrayAsFloat# ba# i#))
2✔
325
        (\addr# -> F# (indexFloatOffAddr# (addr# `plusAddr#` i#) 0#))
2✔
326
  {-# INLINE unpackM #-}
327

328
instance MemPack Double where
2✔
329
  packedByteCount _ = SIZEOF_DOUBLE
2✔
330
  {-# INLINE packedByteCount #-}
331
  packM a@(D# a#) = do
2✔
332
    MutableByteArray mba# <- ask
2✔
333
    I# i# <- packIncrement a
1✔
334
    lift_# (writeWord8ArrayAsDouble# mba# i# a#)
2✔
335
  {-# INLINE packM #-}
336
  unpackM = do
2✔
337
    I# i# <- guardAdvanceUnpack SIZEOF_DOUBLE
2✔
338
    buf <- ask
2✔
339
    pure $!
2✔
340
      buffer
2✔
341
        buf
2✔
342
        (\ba# -> D# (indexWord8ArrayAsDouble# ba# i#))
2✔
343
        (\addr# -> D# (indexDoubleOffAddr# (addr# `plusAddr#` i#) 0#))
2✔
344
  {-# INLINE unpackM #-}
345

346
instance MemPack (Ptr a) where
347
  typeName = "Ptr"
2✔
348
  packedByteCount _ = SIZEOF_HSPTR
2✔
349
  {-# INLINE packedByteCount #-}
350
  packM a@(Ptr a#) = do
2✔
351
    MutableByteArray mba# <- ask
2✔
352
    I# i# <- packIncrement a
1✔
353
    lift_# (writeWord8ArrayAsAddr# mba# i# a#)
2✔
354
  {-# INLINE packM #-}
355
  unpackM = do
2✔
356
    I# i# <- guardAdvanceUnpack SIZEOF_HSPTR
2✔
357
    buf <- ask
2✔
358
    pure $!
2✔
359
      buffer
2✔
360
        buf
2✔
361
        (\ba# -> Ptr (indexWord8ArrayAsAddr# ba# i#))
2✔
362
        (\addr# -> Ptr (indexAddrOffAddr# (addr# `plusAddr#` i#) 0#))
2✔
363
  {-# INLINE unpackM #-}
364

365
instance MemPack (StablePtr a) where
366
  typeName = "StablePtr"
2✔
367
  packedByteCount _ = SIZEOF_HSSTABLEPTR
2✔
368
  {-# INLINE packedByteCount #-}
369
  packM a@(StablePtr a#) = do
2✔
370
    MutableByteArray mba# <- ask
2✔
371
    I# i# <- packIncrement a
1✔
372
    lift_# (writeWord8ArrayAsStablePtr# mba# i# a#)
2✔
373
  {-# INLINE packM #-}
374
  unpackM = do
2✔
375
    I# i# <- guardAdvanceUnpack SIZEOF_HSSTABLEPTR
2✔
376
    buf <- ask
2✔
377
    pure $!
2✔
378
      buffer
2✔
379
        buf
2✔
380
        (\ba# -> StablePtr (indexWord8ArrayAsStablePtr# ba# i#))
2✔
381
        (\addr# -> StablePtr (indexStablePtrOffAddr# (addr# `plusAddr#` i#) 0#))
2✔
382
  {-# INLINE unpackM #-}
383

384
instance MemPack Int where
2✔
385
  packedByteCount _ = SIZEOF_HSINT
2✔
386
  {-# INLINE packedByteCount #-}
387
  packM a@(I# a#) = do
2✔
388
    MutableByteArray mba# <- ask
2✔
389
    I# i# <- packIncrement a
1✔
390
    lift_# (writeWord8ArrayAsInt# mba# i# a#)
2✔
391
  {-# INLINE packM #-}
392
  unpackM = do
2✔
393
    I# i# <- guardAdvanceUnpack SIZEOF_HSINT
2✔
394
    buf <- ask
2✔
395
    pure $!
2✔
396
      buffer
2✔
397
        buf
2✔
398
        (\ba# -> I# (indexWord8ArrayAsInt# ba# i#))
2✔
399
        (\addr# -> I# (indexIntOffAddr# (addr# `plusAddr#` i#) 0#))
2✔
400
  {-# INLINE unpackM #-}
401

402
instance MemPack Int8 where
2✔
403
  packedByteCount _ = SIZEOF_INT8
2✔
404
  {-# INLINE packedByteCount #-}
405
  packM a@(I8# a#) = do
2✔
406
    MutableByteArray mba# <- ask
2✔
407
    I# i# <- packIncrement a
1✔
408
    lift_# (writeInt8Array# mba# i# a#)
2✔
409
  {-# INLINE packM #-}
410
  unpackM = do
2✔
411
    I# i# <- guardAdvanceUnpack SIZEOF_INT8
2✔
412
    buf <- ask
2✔
413
    pure $!
2✔
414
      buffer
2✔
415
        buf
2✔
416
        (\ba# -> I8# (indexInt8Array# ba# i#))
2✔
417
        (\addr# -> I8# (indexInt8OffAddr# (addr# `plusAddr#` i#) 0#))
2✔
418
  {-# INLINE unpackM #-}
419

420
instance MemPack Int16 where
2✔
421
  packedByteCount _ = SIZEOF_INT16
2✔
422
  {-# INLINE packedByteCount #-}
423
  packM a@(I16# a#) = do
2✔
424
    MutableByteArray mba# <- ask
2✔
425
    I# i# <- packIncrement a
1✔
426
    lift_# (writeWord8ArrayAsInt16# mba# i# a#)
2✔
427
  {-# INLINE packM #-}
428
  unpackM = do
2✔
429
    buf <- ask
2✔
430
    I# i# <- guardAdvanceUnpack SIZEOF_INT16
2✔
431
    pure $!
2✔
432
      buffer
2✔
433
        buf
2✔
434
        (\ba# -> I16# (indexWord8ArrayAsInt16# ba# i#))
2✔
435
        (\addr# -> I16# (indexInt16OffAddr# (addr# `plusAddr#` i#) 0#))
2✔
436
  {-# INLINE unpackM #-}
437

438
instance MemPack Int32 where
2✔
439
  packedByteCount _ = SIZEOF_INT32
2✔
440
  {-# INLINE packedByteCount #-}
441
  packM a@(I32# a#) = do
2✔
442
    MutableByteArray mba# <- ask
2✔
443
    I# i# <- packIncrement a
1✔
444
    lift_# (writeWord8ArrayAsInt32# mba# i# a#)
2✔
445
  {-# INLINE packM #-}
446
  unpackM = do
2✔
447
    buf <- ask
2✔
448
    I# i# <- guardAdvanceUnpack SIZEOF_INT32
2✔
449
    pure $!
2✔
450
      buffer
2✔
451
        buf
2✔
452
        (\ba# -> I32# (indexWord8ArrayAsInt32# ba# i#))
2✔
453
        (\addr# -> I32# (indexInt32OffAddr# (addr# `plusAddr#` i#) 0#))
2✔
454
  {-# INLINE unpackM #-}
455

456
instance MemPack Int64 where
2✔
457
  packedByteCount _ = SIZEOF_INT64
2✔
458
  {-# INLINE packedByteCount #-}
459
  packM a@(I64# a#) = do
2✔
460
    MutableByteArray mba# <- ask
2✔
461
    I# i# <- packIncrement a
1✔
462
    lift_# (writeWord8ArrayAsInt64# mba# i# a#)
2✔
463
  {-# INLINE packM #-}
464
  unpackM = do
2✔
465
    buf <- ask
2✔
466
    I# i# <- guardAdvanceUnpack SIZEOF_INT64
2✔
467
    pure $!
2✔
468
      buffer
2✔
469
        buf
2✔
470
        (\ba# -> I64# (indexWord8ArrayAsInt64# ba# i#))
2✔
471
        (\addr# -> I64# (indexInt64OffAddr# (addr# `plusAddr#` i#) 0#))
2✔
472
  {-# INLINE unpackM #-}
473

474
instance MemPack Word where
2✔
475
  packedByteCount _ = SIZEOF_HSWORD
2✔
476
  {-# INLINE packedByteCount #-}
477
  packM a@(W# a#) = do
2✔
478
    MutableByteArray mba# <- ask
2✔
479
    I# i# <- packIncrement a
1✔
480
    lift_# (writeWord8ArrayAsWord# mba# i# a#)
2✔
481
  {-# INLINE packM #-}
482
  unpackM = do
2✔
483
    I# i# <- guardAdvanceUnpack SIZEOF_HSWORD
2✔
484
    buf <- ask
2✔
485
    pure $!
2✔
486
      buffer
2✔
487
        buf
2✔
488
        (\ba# -> W# (indexWord8ArrayAsWord# ba# i#))
2✔
489
        (\addr# -> W# (indexWordOffAddr# (addr# `plusAddr#` i#) 0#))
2✔
490
  {-# INLINE unpackM #-}
491

492
instance MemPack Word8 where
2✔
493
  packedByteCount _ = SIZEOF_WORD8
2✔
494
  {-# INLINE packedByteCount #-}
495
  packM a@(W8# a#) = do
2✔
496
    MutableByteArray mba# <- ask
2✔
497
    I# i# <- packIncrement a
1✔
498
    lift_# (writeWord8Array# mba# i# a#)
2✔
499
  {-# INLINE packM #-}
500
  unpackM = do
2✔
501
    I# i# <- guardAdvanceUnpack SIZEOF_WORD8
2✔
502
    buf <- ask
2✔
503
    pure $!
2✔
504
      buffer
2✔
505
        buf
2✔
506
        (\ba# -> W8# (indexWord8Array# ba# i#))
2✔
507
        (\addr# -> W8# (indexWord8OffAddr# addr# i#))
2✔
508
  {-# INLINE unpackM #-}
509

510
instance MemPack Word16 where
2✔
511
  packedByteCount _ = SIZEOF_WORD16
2✔
512
  {-# INLINE packedByteCount #-}
513
  packM a@(W16# a#) = do
2✔
514
    MutableByteArray mba# <- ask
2✔
515
    I# i# <- packIncrement a
1✔
516
    lift_# (writeWord8ArrayAsWord16# mba# i# a#)
2✔
517
  {-# INLINE packM #-}
518
  unpackM = do
2✔
519
    buf <- ask
2✔
520
    I# i# <- guardAdvanceUnpack SIZEOF_WORD16
2✔
521
    pure $!
2✔
522
      buffer
2✔
523
        buf
2✔
524
        (\ba# -> W16# (indexWord8ArrayAsWord16# ba# i#))
2✔
525
        (\addr# -> W16# (indexWord16OffAddr# (addr# `plusAddr#` i#) 0#))
2✔
526
  {-# INLINE unpackM #-}
527

528
instance MemPack Word32 where
2✔
529
  packedByteCount _ = SIZEOF_WORD32
2✔
530
  {-# INLINE packedByteCount #-}
531
  packM a@(W32# a#) = do
2✔
532
    MutableByteArray mba# <- ask
2✔
533
    I# i# <- packIncrement a
1✔
534
    lift_# (writeWord8ArrayAsWord32# mba# i# a#)
2✔
535
  {-# INLINE packM #-}
536
  unpackM = do
2✔
537
    I# i# <- guardAdvanceUnpack SIZEOF_WORD32
2✔
538
    buf <- ask
2✔
539
    pure $!
2✔
540
      buffer
2✔
541
        buf
2✔
542
        (\ba# -> W32# (indexWord8ArrayAsWord32# ba# i#))
2✔
543
        (\addr# -> W32# (indexWord32OffAddr# (addr# `plusAddr#` i#) 0#))
2✔
544
  {-# INLINE unpackM #-}
545

546
instance MemPack Word64 where
2✔
547
  packedByteCount _ = SIZEOF_WORD64
2✔
548
  {-# INLINE packedByteCount #-}
549
  packM a@(W64# a#) = do
2✔
550
    MutableByteArray mba# <- ask
2✔
551
    I# i# <- packIncrement a
1✔
552
    lift_# (writeWord8ArrayAsWord64# mba# i# a#)
2✔
553
  {-# INLINE packM #-}
554
  unpackM = do
2✔
555
    I# i# <- guardAdvanceUnpack SIZEOF_WORD64
2✔
556
    buf <- ask
2✔
557
    pure $!
2✔
558
      buffer
2✔
559
        buf
2✔
560
        (\ba# -> W64# (indexWord8ArrayAsWord64# ba# i#))
2✔
561
        (\addr# -> W64# (indexWord64OffAddr# (addr# `plusAddr#` i#) 0#))
2✔
562
  {-# INLINE unpackM #-}
563

564
#if __GLASGOW_HASKELL__ >= 900
565
instance MemPack Integer where
2✔
566
  packedByteCount =
2✔
567
    (+ packedTagByteCount) . \case
2✔
568
      IS i# -> packedByteCount (I# i#)
1✔
569
      IP ba# -> packedByteCount (ByteArray ba#)
2✔
570
      IN ba# -> packedByteCount (ByteArray ba#)
2✔
571
  {-# INLINE packedByteCount #-}
572
  packM = \case
2✔
573
    IS i# -> packTagM 0 >> packM (I# i#)
2✔
574
    IP ba# -> packTagM 1 >> packM (ByteArray ba#)
2✔
575
    IN ba# -> packTagM 2 >> packM (ByteArray ba#)
2✔
576
  {-# INLINE packM #-}
577
  unpackM = do
2✔
578
    i <-
579
      unpackTagM >>= \case
2✔
580
        0 -> do
2✔
581
          I# i# <- unpackM
2✔
582
          pure $ IS i#
2✔
583
        1 -> do
2✔
584
          ByteArray ba# <- unpackM
2✔
585
          pure $ IP ba#
2✔
586
        2 -> do
2✔
587
          ByteArray ba# <- unpackM
2✔
588
          pure $ IN ba#
2✔
589
        t -> unknownTagM @Integer t
×
590
    unless (integerCheck i) $ F.fail $ "Invalid Integer decoded " ++ showInteger i
1✔
591
    pure i
2✔
592
    where
593
      showInteger = \case
×
594
        IS i# -> "IS " ++ show (I# i#)
×
595
        IP ba# -> "IP " ++ show (ByteArray ba#)
×
596
        IN ba# -> "IN " ++ show (ByteArray ba#)
×
597
  {-# INLINE unpackM #-}
598

599
instance MemPack Natural where
2✔
600
  packedByteCount =
2✔
601
    (+ packedTagByteCount) . \case
2✔
602
      NS w# -> packedByteCount (W# w#)
1✔
603
      NB ba# -> packedByteCount (ByteArray ba#)
2✔
604
  {-# INLINE packedByteCount #-}
605
  packM = \case
2✔
606
    NS w# -> packTagM 0 >> packM (W# w#)
2✔
607
    NB ba# -> packTagM 1 >> packM (ByteArray ba#)
2✔
608
  {-# INLINE packM #-}
609
  unpackM = do
2✔
610
    n <-
611
      unpackTagM >>= \case
2✔
612
        0 -> do
2✔
613
          W# w# <- unpackM
2✔
614
          pure $ NS w#
2✔
615
        1 -> do
2✔
616
          ByteArray ba# <- unpackM
2✔
617
          pure $ NB ba#
2✔
618
        t -> unknownTagM @Natural t
×
619
    unless (naturalCheck n) $ F.fail $ "Invalid Natural decoded " ++ showNatural n
1✔
620
    pure n
2✔
621
    where
622
      showNatural = \case
×
623
        NS w# -> "NS " ++ show (W# w#)
×
624
        NB ba# -> "NB " ++ show (ByteArray ba#)
×
625
  {-# INLINE unpackM #-}
626

627
#elif defined(MIN_VERSION_integer_gmp)
628

629
instance MemPack Integer where
630
  packedByteCount =
631
    (+ packedTagByteCount) . \case
632
      S# i# -> packedByteCount (I# i#)
633
      Jp# (BN# ba#) -> packedByteCount (ByteArray ba#)
634
      Jn# (BN# ba#) -> packedByteCount (ByteArray ba#)
635
  {-# INLINE packedByteCount #-}
636
  packM = \case
637
    S# i# -> packTagM 0 >> packM (I# i#)
638
    Jp# (BN# ba#) -> packTagM 1 >> packM (ByteArray ba#)
639
    Jn# (BN# ba#) -> packTagM 2 >> packM (ByteArray ba#)
640
  {-# INLINE packM #-}
641
  unpackM = do
642
    i <-
643
      unpackTagM >>= \case
644
        0 -> do
645
          I# i# <- unpackM
646
          pure $ S# i#
647
        1 -> do
648
          ByteArray ba# <- unpackM
649
          pure $ Jp# (BN# ba#)
650
        2 -> do
651
          ByteArray ba# <- unpackM
652
          pure $ Jn# (BN# ba#)
653
        t -> unknownTagM @Integer t
654
    unless (isTrue# (isValidInteger# i)) $ F.fail $ "Invalid Integer decoded " ++ showInteger i
655
    pure i
656
    where
657
      showInteger = \case
658
        S# i# -> "S# " ++ show (I# i#)
659
        Jp# (BN# ba#) -> "Jp# " ++ show (ByteArray ba#)
660
        Jn# (BN# ba#) -> "Jn# " ++ show (ByteArray ba#)
661
  {-# INLINE unpackM #-}
662

663
instance MemPack Natural where
664
  packedByteCount =
665
    (+ packedTagByteCount) . \case
666
      NatS# w# -> packedByteCount (W# w#)
667
      NatJ# (BN# ba#) -> packedByteCount (ByteArray ba#)
668
  {-# INLINE packedByteCount #-}
669
  packM = \case
670
    NatS# w# -> packTagM 0 >> packM (W# w#)
671
    NatJ# (BN# ba#) -> packTagM 1 >> packM (ByteArray ba#)
672
  {-# INLINE packM #-}
673
  unpackM = do
674
    n <-
675
      unpackTagM >>= \case
676
        0 -> do
677
          W# w# <- unpackM
678
          pure $ NatS# w#
679
        1 -> do
680
          ByteArray ba# <- unpackM
681
          pure $ NatJ# (BN# ba#)
682
        t -> unknownTagM @Natural t
683
    unless (isValidNatural n) $ F.fail $ "Invalid Natural decoded " ++ showNatural n
684
    pure n
685
    where
686
      showNatural = \case
687
        NatS# w# -> "NatS# " ++ show (W# w#)
688
        NatJ# (BN#  ba#) -> "NatJ# " ++ show (ByteArray ba#)
689
  {-# INLINE unpackM #-}
690

691
#endif
692

693
instance MemPack a => MemPack (Complex a) where
694
  typeName = "Complex " ++ typeName @a
2✔
695
  packedByteCount (a :+ b) = packedByteCount a + packedByteCount b
1✔
696
  {-# INLINE packedByteCount #-}
697
  packM (a :+ b) = packM a >> packM b
2✔
698
  {-# INLINE packM #-}
699
  unpackM = do
2✔
700
    !a <- unpackM
2✔
701
    !b <- unpackM
2✔
702
    pure (a :+ b)
2✔
703
  {-# INLINE unpackM #-}
704

705
instance (MemPack a, Integral a) => MemPack (Ratio a) where
706
  typeName = "Ratio " ++ typeName @a
2✔
707
  packedByteCount r = packedByteCount (numerator r) + packedByteCount (denominator r)
1✔
708
  {-# INLINE packedByteCount #-}
709
  packM r = packM (numerator r) >> packM (denominator r)
2✔
710
  {-# INLINE packM #-}
711
  unpackM = do
2✔
712
    !a <- unpackM
2✔
713
    !b <- unpackM
2✔
714
    when (b == 0) $ F.fail $ "Zero denominator was detected when unpacking " ++ typeName @(Ratio a)
1✔
715
    pure (a % b)
2✔
716
  {-# INLINE unpackM #-}
717

718
instance (MemPack a, MemPack b) => MemPack (a, b) where
719
  typeName = "(" ++ typeName @a ++ "," ++ typeName @b ++ ")"
2✔
720
  packedByteCount (a, b) = packedByteCount a + packedByteCount b
1✔
721
  {-# INLINE packedByteCount #-}
722
  packM (a, b) = packM a >> packM b
2✔
723
  {-# INLINE packM #-}
724
  unpackM = do
2✔
725
    !a <- unpackM
2✔
726
    !b <- unpackM
2✔
727
    pure (a, b)
2✔
728
  {-# INLINE unpackM #-}
729

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

743
instance (MemPack a, MemPack b, MemPack c, MemPack d) => MemPack (a, b, c, d) where
744
  typeName = "(" ++ typeName @a ++ "," ++ typeName @b ++ "," ++ typeName @c ++ "," ++ typeName @d ++ ")"
2✔
745
  packedByteCount (a, b, c, d) = packedByteCount a + packedByteCount b + packedByteCount c + packedByteCount d
1✔
746
  {-# INLINE packedByteCount #-}
747
  packM (a, b, c, d) =
2✔
748
    packM a >> packM b >> packM c >> packM d
2✔
749
  {-# INLINE packM #-}
750
  unpackM = do
2✔
751
    !a <- unpackM
2✔
752
    !b <- unpackM
2✔
753
    !c <- unpackM
2✔
754
    !d <- unpackM
2✔
755
    pure (a, b, c, d)
2✔
756
  {-# INLINE unpackM #-}
757

758
instance (MemPack a, MemPack b, MemPack c, MemPack d, MemPack e) => MemPack (a, b, c, d, e) where
759
  typeName =
2✔
760
    "("
2✔
761
      ++ intercalate
2✔
762
        ","
2✔
763
        [ typeName @a
2✔
764
        , typeName @b
2✔
765
        , typeName @c
2✔
766
        , typeName @d
2✔
767
        , typeName @e
2✔
768
        ]
769
      ++ ")"
2✔
770
  packedByteCount (a, b, c, d, e) =
2✔
771
    packedByteCount a + packedByteCount b + packedByteCount c + packedByteCount d + packedByteCount e
1✔
772
  {-# INLINE packedByteCount #-}
773
  packM (a, b, c, d, e) =
2✔
774
    packM a >> packM b >> packM c >> packM d >> packM e
2✔
775
  {-# INLINE packM #-}
776
  unpackM = do
2✔
777
    !a <- unpackM
2✔
778
    !b <- unpackM
2✔
779
    !c <- unpackM
2✔
780
    !d <- unpackM
2✔
781
    !e <- unpackM
2✔
782
    pure (a, b, c, d, e)
2✔
783
  {-# INLINE unpackM #-}
784

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

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

859
instance MemPack a => MemPack [a] where
860
  typeName = "[" ++ typeName @a ++ "]"
2✔
861
  packedByteCount es = packedByteCount (Length (length es)) + getSum (foldMap (Sum . packedByteCount) es)
2✔
862
  {-# INLINE packedByteCount #-}
863
  packM as = do
2✔
864
    packM (Length (length as))
2✔
865
    mapM_ packM as
2✔
866
  {-# INLINE packM #-}
867
  unpackM = do
2✔
868
    Length n <- unpackM
2✔
869
    replicateTailM n unpackM
2✔
870
  {-# INLINE unpackM #-}
871

872
-- | Tail recursive version of `replicateM`
873
replicateTailM :: Monad m => Int -> m a -> m [a]
874
replicateTailM n f = go n []
2✔
875
  where
876
    go i !acc
2✔
877
      | i <= 0 = pure $ reverse acc
2✔
878
      | otherwise = f >>= \x -> go (i - 1) (x : acc)
1✔
879
{-# INLINE replicateTailM #-}
880

881
instance MemPack ByteArray where
2✔
882
  packedByteCount ba =
2✔
883
    let len = bufferByteCount ba
2✔
884
     in packedByteCount (Length len) + len
2✔
885
  {-# INLINE packedByteCount #-}
886
  packM ba@(ByteArray ba#) = do
2✔
887
    let !len@(I# len#) = bufferByteCount ba
2✔
888
    packM (Length len)
2✔
889
    I# curPos# <- state $ \i -> (i, i + len)
2✔
890
    MutableByteArray mba# <- ask
2✔
891
    lift_# (copyByteArray# ba# 0# mba# curPos# len#)
2✔
892
  {-# INLINE packM #-}
893
  unpackM = unpackByteArray False
2✔
894
  {-# INLINE unpackM #-}
895

896
instance MemPack ShortByteString where
2✔
897
  packedByteCount ba =
2✔
898
    let len = bufferByteCount ba
2✔
899
     in packedByteCount (Length len) + len
2✔
900
  {-# INLINE packedByteCount #-}
901
  packM = packM . byteArrayFromShortByteString
2✔
902
  {-# INLINE packM #-}
903
  unpackM = byteArrayToShortByteString <$> unpackByteArray False
2✔
904
  {-# INLINE unpackM #-}
905

906
instance MemPack ByteString where
2✔
907
  packedByteCount ba =
2✔
908
    let len = bufferByteCount ba
2✔
909
     in packedByteCount (Length len) + len
2✔
910
  {-# INLINE packedByteCount #-}
911
  packM bs = do
2✔
912
    let !len@(I# len#) = bufferByteCount bs
2✔
913
    packM (Length len)
2✔
914
    I# curPos# <- state $ \i -> (i, i + len)
2✔
915
    Pack $ \(MutableByteArray mba#) -> lift $ withPtrByteStringST bs $ \(Ptr addr#) ->
2✔
916
      st_ (copyAddrToByteArray# addr# mba# curPos# len#)
2✔
917
  {-# INLINE packM #-}
918
  unpackM = pinnedByteArrayToByteString <$> unpackByteArray True
2✔
919
  {-# INLINE unpackM #-}
920

921
-- | This is the implementation of `unpackM` for `ByteArray` and `ByteString`
922
unpackByteArray :: Buffer b => Bool -> Unpack b ByteArray
923
unpackByteArray isPinned = do
2✔
924
  Length len@(I# len#) <- unpackM
2✔
925
  I# curPos# <- guardAdvanceUnpack len
2✔
926
  buf <- ask
2✔
927
  pure $! runST $ do
2✔
928
    mba@(MutableByteArray mba#) <- newMutableByteArray isPinned len
2✔
929
    buffer
2✔
930
      buf
2✔
931
      (\ba# -> st_ (copyByteArray# ba# curPos# mba# 0# len#))
2✔
932
      (\addr# -> st_ (copyAddrToByteArray# (addr# `plusAddr#` curPos#) mba# 0# len#))
2✔
933
    freezeMutableByteArray mba
2✔
934
{-# INLINE unpackByteArray #-}
935

936
-- | Increment the offset counter of `Pack` monad by then number of `packedByteCount` and
937
-- return the starting offset.
938
packIncrement :: MemPack a => a -> Pack s Int
939
packIncrement a =
2✔
940
  state $ \i ->
2✔
941
    let !n = i + packedByteCount a
1✔
942
     in (i, n)
2✔
943
{-# INLINE packIncrement #-}
944

945
-- | Increment the offset counter of `Unpack` monad by the supplied number of
946
-- bytes. Returns the original offset or fails with `RanOutOfBytesError` whenever there is
947
-- not enough bytes in the `Buffer`.
948
guardAdvanceUnpack :: Buffer b => Int -> Unpack b Int
949
guardAdvanceUnpack n@(I# n#) = do
2✔
950
  buf <- ask
2✔
951
  let len = bufferByteCount buf
2✔
952
      failOutOfBytes i =
2✔
953
        failUnpack $
2✔
954
          toSomeError $
2✔
955
            RanOutOfBytesError
2✔
956
              { ranOutOfBytesRead = i
2✔
957
              , ranOutOfBytesAvailable = len
2✔
958
              , ranOutOfBytesRequested = n
2✔
959
              }
960
  -- Check that we still have enough bytes, while guarding against integer overflow.
961
  join $ state $ \i@(I# i#) ->
2✔
962
    case addIntC# i# n# of
2✔
963
      (# adv#, 0# #) ->
964
        if len < I# adv#
2✔
965
          then (failOutOfBytes i, i)
1✔
966
          else (pure i, I# adv#)
2✔
967
      _ -> (failOutOfBytes i, i)
×
968
{-# INLINE guardAdvanceUnpack #-}
969

970
-- | Serialize a type into an unpinned `ByteArray`
971
--
972
-- ====__Examples__
973
--
974
-- >>> :set -XTypeApplications
975
-- >>> unpack @[Int] $ pack ([1,2,3,4,5] :: [Int])
976
-- Right [1,2,3,4,5]
977
pack :: forall a. (MemPack a, HasCallStack) => a -> ByteArray
978
pack = packByteArray False
2✔
979
{-# INLINE pack #-}
980

981
-- | Serialize a type into a pinned `ByteString`
982
packByteString :: forall a. (MemPack a, HasCallStack) => a -> ByteString
983
packByteString = pinnedByteArrayToByteString . packByteArray True
2✔
984
{-# INLINE packByteString #-}
985

986
-- | Serialize a type into an unpinned `ShortByteString`
987
packShortByteString :: forall a. (MemPack a, HasCallStack) => a -> ShortByteString
988
packShortByteString = byteArrayToShortByteString . pack
×
989
{-# INLINE packShortByteString #-}
990

991
-- | Same as `pack`, but allows controlling the pinnedness of allocated memory
992
packByteArray ::
993
  forall a.
994
  (MemPack a, HasCallStack) =>
995
  -- | Should the array be allocated in pinned memory?
996
  Bool ->
997
  a ->
998
  ByteArray
999
packByteArray isPinned a =
2✔
1000
  runST $ packMutableByteArray isPinned a >>= freezeMutableByteArray
2✔
1001
{-# INLINE packByteArray #-}
1002

1003
-- | Same as `packByteArray`, but produces a mutable array instead
1004
packMutableByteArray ::
1005
  forall a s.
1006
  (MemPack a, HasCallStack) =>
1007
  -- | Should the array be allocated in pinned memory?
1008
  Bool ->
1009
  a ->
1010
  ST s (MutableByteArray s)
1011
packMutableByteArray isPinned a = do
2✔
1012
  let len = packedByteCount a
2✔
1013
  mba <- newMutableByteArray isPinned len
2✔
1014
  filledBytes <- execStateT (runPack (packM a) mba) 0
2✔
1015
  when (filledBytes /= len) $
2✔
1016
    if (filledBytes < len)
×
1017
      then
1018
        error $
×
1019
          "Some bug in 'packM' was detected. Buffer of length " <> showBytes len
×
1020
            ++ " was not fully filled while packing " <> typeName @a
×
1021
            ++ ". Unfilled " <> showBytes (len - filledBytes) <> "."
×
1022
      else
1023
        -- This is a critical error, therefore we are not gracefully failing this unpacking
1024
        error $
×
1025
          "Potential buffer overflow. Some bug in 'packM' was detected while packing " <> typeName @a
×
1026
            ++ ". Filled " <> showBytes (filledBytes - len) <> " more than allowed into a buffer of length "
×
1027
            ++ show len
×
1028
  pure mba
2✔
1029
{-# INLINEABLE packMutableByteArray #-}
1030

1031
-- | Unpack a memory `Buffer` into a type using its `MemPack` instance. Besides the
1032
-- unpacked type it also returns an index into a buffer where unpacked has stopped.
1033
unpackLeftOver :: forall a b. (MemPack a, Buffer b, HasCallStack) => b -> Fail SomeError (a, Int)
1034
unpackLeftOver b = do
2✔
1035
  let len = bufferByteCount b
2✔
1036
  res@(_, consumedBytes) <- runStateT (runUnpack unpackM b) 0
2✔
1037
  when (consumedBytes > len) $
2✔
1038
    -- This is a critical error, therefore we are not gracefully failing this unpacking
1039
    error $
×
1040
      "Potential buffer overflow. Some bug in 'unpackM' was detected while unpacking " <> typeName @a
×
1041
        ++ ". Consumed " <> showBytes (consumedBytes - len) <> " more than allowed from a buffer of length "
×
1042
        ++ show len
×
1043
  pure res
2✔
1044
{-# INLINEABLE unpackLeftOver #-}
1045

1046
-- | Unpack a memory `Buffer` into a type using its `MemPack` instance. Besides potential
1047
-- unpacking failures due to a malformed buffer it will also fail the supplied `Buffer`
1048
-- was not fully consumed. Use `unpackLeftOver`, whenever a partially consumed buffer is
1049
-- possible.
1050
unpack :: forall a b. (MemPack a, Buffer b, HasCallStack) => b -> Either SomeError a
1051
unpack = first fromMultipleErrors . runFailAgg . unpackFail
2✔
1052
{-# INLINE unpack #-}
1053

1054
-- | Same as `unpack` except fails in a `Fail` monad, instead of `Either`.
1055
unpackFail :: forall a b. (MemPack a, Buffer b, HasCallStack) => b -> Fail SomeError a
1056
unpackFail b = do
2✔
1057
  let len = bufferByteCount b
2✔
1058
  (a, consumedBytes) <- unpackLeftOver b
2✔
1059
  when (consumedBytes /= len) $
2✔
1060
    failT $
2✔
1061
      toSomeError $
2✔
1062
        NotFullyConsumedError
2✔
1063
          { notFullyConsumedRead = consumedBytes
2✔
1064
          , notFullyConsumedAvailable = len
2✔
1065
          , notFullyConsumedTypeName = typeName @a
2✔
1066
          }
1067
  pure a
2✔
1068
{-# INLINEABLE unpackFail #-}
1069

1070
-- | Same as `unpackFail` except fails in any `MonadFail`, instead of `Fail`.
1071
unpackMonadFail :: forall a b m. (MemPack a, Buffer b, F.MonadFail m) => b -> m a
1072
unpackMonadFail = either (F.fail . show) pure . unpack
×
1073
{-# INLINE unpackMonadFail #-}
1074

1075
-- | Same as `unpack` except throws a runtime exception upon a failure
1076
unpackError :: forall a b. (MemPack a, Buffer b, HasCallStack) => b -> a
1077
unpackError = errorFail . unpackFail
2✔
1078
{-# INLINE unpackError #-}
1079

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

1086
instance MemPack (VarLen Word16) where
2✔
1087
  packedByteCount = packedVarLenByteCount
2✔
1088
  {-# INLINE packedByteCount #-}
1089
  packM v@(VarLen x) = p7 (p7 (p7 (errorTooManyBits "Word16"))) (numBits - 7)
1✔
1090
    where
1091
      p7 = packIntoCont7 x
2✔
1092
      {-# INLINE p7 #-}
1093
      numBits = packedVarLenByteCount v * 7
2✔
1094
  {-# INLINE packM #-}
1095
  unpackM = do
2✔
1096
    let d7 = unpack7BitVarLen
2✔
1097
        {-# INLINE d7 #-}
1098
    VarLen <$> d7 (d7 (unpack7BitVarLenLast 0b_1111_1100)) 0 0
2✔
1099
  {-# INLINE unpackM #-}
1100

1101
instance MemPack (VarLen Word32) where
2✔
1102
  packedByteCount = packedVarLenByteCount
2✔
1103
  {-# INLINE packedByteCount #-}
1104
  packM v@(VarLen x) = p7 (p7 (p7 (p7 (p7 (errorTooManyBits "Word32"))))) (numBits - 7)
1✔
1105
    where
1106
      p7 = packIntoCont7 x
2✔
1107
      {-# INLINE p7 #-}
1108
      numBits = packedVarLenByteCount v * 7
2✔
1109
  {-# INLINE packM #-}
1110
  unpackM = do
2✔
1111
    let d7 = unpack7BitVarLen
2✔
1112
        {-# INLINE d7 #-}
1113
    VarLen <$> d7 (d7 (d7 (d7 (unpack7BitVarLenLast 0b_1111_0000)))) 0 0
2✔
1114
  {-# INLINE unpackM #-}
1115

1116
instance MemPack (VarLen Word64) where
2✔
1117
  packedByteCount = packedVarLenByteCount
2✔
1118
  {-# INLINE packedByteCount #-}
1119
  packM v@(VarLen x) =
2✔
1120
    p7 (p7 (p7 (p7 (p7 (p7 (p7 (p7 (p7 (p7 (errorTooManyBits "Word64")))))))))) (numBits - 7)
1✔
1121
    where
1122
      p7 = packIntoCont7 x
2✔
1123
      {-# INLINE p7 #-}
1124
      numBits = packedVarLenByteCount v * 7
2✔
1125
  {-# INLINE packM #-}
1126
  unpackM = do
2✔
1127
    let d7 = unpack7BitVarLen
2✔
1128
        {-# INLINE d7 #-}
1129
    VarLen <$> d7 (d7 (d7 (d7 (d7 (d7 (d7 (d7 (d7 (unpack7BitVarLenLast 0b_1111_1110))))))))) 0 0
2✔
1130
  {-# INLINE unpackM #-}
1131

1132
instance MemPack (VarLen Word) where
2✔
1133
  packedByteCount = packedVarLenByteCount
2✔
1134
  {-# INLINE packedByteCount #-}
1135
#if WORD_SIZE_IN_BITS == 32
1136
  packM mba v@(VarLen x) = p7 (p7 (p7 (p7 (p7 (errorTooManyBits "Word"))))) (numBits - 7)
1137
    where
1138
      p7 = packIntoCont7 mba x
1139
      {-# INLINE p7 #-}
1140
      numBits = packedVarLenByteCount v * 7
1141
  {-# INLINE packM #-}
1142
  unpackM buf = do
1143
    let d7 = unpack7BitVarLen buf
1144
        {-# INLINE d7 #-}
1145
    VarLen <$> d7 (d7 (d7 (d7 (unpack7BitVarLenLast buf 0b_1111_0000)))) 0 0
1146
  {-# INLINE unpackM #-}
1147
#elif WORD_SIZE_IN_BITS == 64
1148
  packM v@(VarLen x) =
2✔
1149
    p7 (p7 (p7 (p7 (p7 (p7 (p7 (p7 (p7 (p7 (errorTooManyBits "Word")))))))))) (numBits - 7)
1✔
1150
    where
1151
      p7 = packIntoCont7 x
2✔
1152
      {-# INLINE p7 #-}
1153
      numBits = packedVarLenByteCount v * 7
2✔
1154
  {-# INLINE packM #-}
1155
  unpackM = do
2✔
1156
    let d7 = unpack7BitVarLen
2✔
1157
        {-# INLINE d7 #-}
1158
    VarLen <$> d7 (d7 (d7 (d7 (d7 (d7 (d7 (d7 (d7 (unpack7BitVarLenLast 0b_1111_1110))))))))) 0 0
2✔
1159
  {-# INLINE unpackM #-}
1160
#else
1161
#error "Only 32bit and 64bit systems are supported"
1162
#endif
1163

1164
packedVarLenByteCount :: FiniteBits b => VarLen b -> Int
1165
packedVarLenByteCount (VarLen x) =
2✔
1166
  case (finiteBitSize x - countLeadingZeros x) `quotRem` 7 of
1✔
1167
    (0, 0) -> 1
2✔
1168
    (q, 0) -> q
2✔
1169
    (q, _) -> q + 1
2✔
1170
{-# INLINE packedVarLenByteCount #-}
1171

1172
errorTooManyBits :: [Char] -> a
1173
errorTooManyBits name =
×
1174
  error $ "Bug detected. Trying to pack more bits for " ++ name ++ " than it should be posssible"
×
1175

1176
packIntoCont7 ::
1177
  (Bits t, Integral t) => t -> (Int -> Pack s ()) -> Int -> Pack s ()
1178
packIntoCont7 x cont n
2✔
1179
  | n <= 0 = packM (fromIntegral @_ @Word8 x .&. complement topBit8)
2✔
1180
  | otherwise = do
1✔
1181
      packM (fromIntegral @_ @Word8 (x `shiftR` n) .|. topBit8)
2✔
1182
      cont (n - 7)
2✔
1183
  where
1184
    topBit8 :: Word8
1185
    topBit8 = 0b_1000_0000
2✔
1186
{-# INLINE packIntoCont7 #-}
1187

1188
-- | Decode a variable length integral value that is encoded with 7 bits of data
1189
-- and the most significant bit (MSB), the 8th bit is set whenever there are
1190
-- more bits following. Continuation style allows us to avoid
1191
-- recursion. Removing loops is good for performance.
1192
unpack7BitVarLen ::
1193
  (Num a, Bits a, Buffer b) =>
1194
  -- | Continuation that will be invoked if MSB is set
1195
  (Word8 -> a -> Unpack b a) ->
1196
  -- | Will be set either to 0 initially or to the very first unmodified byte, which is
1197
  -- guaranteed to have the first bit set.
1198
  Word8 ->
1199
  -- | Accumulator
1200
  a ->
1201
  Unpack b a
1202
unpack7BitVarLen cont firstByte !acc = do
2✔
1203
  b8 :: Word8 <- unpackM
2✔
1204
  if b8 `testBit` 7
2✔
1205
    then
1206
      cont (if firstByte == 0 then b8 else firstByte) (acc `shiftL` 7 .|. fromIntegral (b8 `clearBit` 7))
2✔
1207
    else pure (acc `shiftL` 7 .|. fromIntegral b8)
2✔
1208
{-# INLINE unpack7BitVarLen #-}
1209

1210
unpack7BitVarLenLast ::
1211
  forall t b.
1212
  (Num t, Bits t, MemPack t, Buffer b) =>
1213
  Word8 ->
1214
  Word8 ->
1215
  t ->
1216
  Unpack b t
1217
unpack7BitVarLenLast mask firstByte acc = do
2✔
1218
  res <- unpack7BitVarLen (\_ _ -> F.fail "Too many bytes.") firstByte acc
1✔
1219
  -- Only while decoding the last 7bits we check if there was too many
1220
  -- bits supplied at the beginning.
1221
  unless (firstByte .&. mask == 0b_1000_0000) $
2✔
1222
    F.fail $
×
1223
      "Unexpected bits for "
×
1224
        ++ typeName @t
×
1225
        ++ " were set in the first byte of 'VarLen': 0x" <> showHex firstByte ""
×
1226
  pure res
2✔
1227
{-# INLINE unpack7BitVarLenLast #-}
1228

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

1235
instance Bounded Length where
1236
  minBound = 0
2✔
1237
  maxBound = Length maxBound
2✔
1238

1239
instance Enum Length where
1✔
1240
  toEnum n
2✔
1241
    | n < 0 = error $ "toEnum: Length cannot be negative: " ++ show n
1✔
1242
    | otherwise = Length n
1✔
1243
  fromEnum = unLength
2✔
1244

1245
instance MemPack Length where
2✔
1246
  packedByteCount = packedByteCount . VarLen . fromIntegral @Int @Word . unLength
2✔
1247
  packM (Length n)
2✔
1248
    | n < 0 = error $ "Length cannot be negative. Supplied: " ++ show n
1✔
1249
    | otherwise = packM (VarLen (fromIntegral @Int @Word n))
1✔
1250
  {-# INLINE packM #-}
1251
  unpackM = do
2✔
1252
    VarLen (w :: Word) <- unpackM
2✔
1253
    when (testBit w (finiteBitSize w)) $
1✔
1254
      F.fail $
×
1255
        "Attempt to unpack negative length was detected: " ++ show (fromIntegral @Word @Int w)
×
1256
    pure $ Length $ fromIntegral @Word @Int w
2✔
1257
  {-# INLINE unpackM #-}
1258

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

1263
-- Manually defined instance, since ghc-8.6 has issues with deriving MemPack
1264
instance MemPack Tag where
2✔
1265
  packedByteCount _ = packedTagByteCount
2✔
1266
  {-# INLINE packedByteCount #-}
1267
  unpackM = unpackTagM
2✔
1268
  {-# INLINE unpackM #-}
1269
  packM = packTagM
2✔
1270
  {-# INLINE packM #-}
1271

1272
packedTagByteCount :: Int
1273
packedTagByteCount = SIZEOF_WORD8
2✔
1274
{-# INLINE packedTagByteCount #-}
1275

1276
unpackTagM :: Buffer b => Unpack b Tag
1277
unpackTagM = Tag <$> unpackM
2✔
1278
{-# INLINE unpackTagM #-}
1279

1280
packTagM :: Tag -> Pack s ()
1281
packTagM = packM . unTag
2✔
1282
{-# INLINE packTagM #-}
1283

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

1287
lift_# :: (State# s -> State# s) -> Pack s ()
1288
lift_# f = Pack $ \_ -> lift $ st_ f
2✔
1289
{-# INLINE lift_# #-}
1290

1291
st_ :: (State# s -> State# s) -> ST s ()
1292
st_ f = ST $ \s# -> (# f s#, () #)
2✔
1293
{-# INLINE st_ #-}
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