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

lehins / mempack / 3

13 Sep 2025 05:06PM UTC coverage: 85.645% (-0.3%) from 85.987%
3

push

github

web-flow
Merge 6129a4177 into 072e28fea

60 of 74 new or added lines in 2 files covered. (81.08%)

56 existing lines in 3 files now uncovered.

710 of 829 relevant lines covered (85.65%)

1.63 hits per line

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

89.21
/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
  packByteString,
33
  packShortByteString,
34

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

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

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

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

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

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

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

80
#include "MachDeps.h"
81

82
import Control.Applicative (Alternative (..))
83
import Control.Monad (join, unless, when)
84
import qualified Control.Monad.Fail as F
85
import Control.Monad.Reader (MonadReader (..), lift)
86
import Control.Monad.State.Strict (MonadState (..), StateT (..), execStateT)
87
import Control.Monad.Trans.Fail (Fail, FailT (..), errorFail, failT, runFailAgg, runFailAggT)
88
import Data.Array.Byte (ByteArray (..), MutableByteArray (..))
89
import Data.Bifunctor (first)
90
import Data.Bits (Bits (..), FiniteBits (..))
91
import Data.ByteString (ByteString)
92
import qualified Data.ByteString.Lazy as BSL
93
import qualified Data.ByteString.Lazy.Internal as BSL
94
import Data.ByteString.Short (ShortByteString)
95
import Data.Char (ord)
96
import Data.Complex (Complex (..))
97
import Data.Foldable (foldMap')
98
import Data.List (intercalate)
99
import Data.MemPack.Buffer
100
import Data.MemPack.Error
101
import Data.Primitive.Array (Array (..), newArray, sizeofArray, unsafeFreezeArray, writeArray)
102
import Data.Primitive.PrimArray (PrimArray (..), sizeofPrimArray)
103
import Data.Primitive.Types (Prim (sizeOf#))
104
import Data.Ratio
105
import Data.Semigroup (Sum (..))
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
#if !MIN_VERSION_base(4,13,0)
138
foldMap' :: (Foldable t, Monoid m) => (a -> m) -> t a -> m
139
foldMap' = foldMap
140
#endif
141

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

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

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

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

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

235
-- | Failing unpacking with an `Error`.
236
failUnpack :: Error e => e -> Unpack s b a
237
failUnpack e = Unpack $ \_ -> lift $ failT (toSomeError e)
2✔
238

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

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

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

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

UNCOV
267
instance MemPack () where
×
268
  packedByteCount _ = 0
2✔
269
  {-# INLINE packedByteCount #-}
270
  packM () = pure ()
1✔
271
  {-# INLINE packM #-}
272
  unpackM = pure ()
2✔
273
  {-# INLINE unpackM #-}
274

UNCOV
275
instance MemPack Void where
×
276
  packedByteCount _ = 0
×
277
  packM = absurd
×
278
  unpackM = F.fail "Void is unpackable"
×
279

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

667
#elif defined(MIN_VERSION_integer_gmp)
668

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

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

731
#endif
732

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

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

758
instance (MemPack a, MemPack b) => MemPack (a, b) where
759
  typeName = "(" ++ typeName @a ++ "," ++ typeName @b ++ ")"
2✔
760
  packedByteCount (a, b) = packedByteCount a + packedByteCount b
1✔
761
  {-# INLINE packedByteCount #-}
762
  packM (a, b) = packM a >> packM b
2✔
763
  {-# INLINEABLE packM #-}
764
  unpackM = do
2✔
765
    !a <- unpackM
2✔
766
    !b <- unpackM
2✔
767
    pure (a, b)
2✔
768
  {-# INLINEABLE unpackM #-}
769

770
instance (MemPack a, MemPack b, MemPack c) => MemPack (a, b, c) where
771
  typeName = "(" ++ typeName @a ++ "," ++ typeName @b ++ "," ++ typeName @c ++ ")"
2✔
772
  packedByteCount (a, b, c) = packedByteCount a + packedByteCount b + packedByteCount c
1✔
773
  {-# INLINE packedByteCount #-}
774
  packM (a, b, c) = packM a >> packM b >> packM c
2✔
775
  {-# INLINEABLE packM #-}
776
  unpackM = do
2✔
777
    !a <- unpackM
2✔
778
    !b <- unpackM
2✔
779
    !c <- unpackM
2✔
780
    pure (a, b, c)
2✔
781
  {-# INLINEABLE unpackM #-}
782

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

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

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

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

899
data T2 a b = T2 !a !b
900

NEW
901
instance (Semigroup a, Semigroup b) => Semigroup (T2 a b) where
×
902
  T2 a1 b1 <> T2 a2 b2 = T2 (a1 <> a2) (b1 <> b2)
2✔
903

NEW
904
instance (Monoid a, Monoid b) => Monoid (T2 a b) where
×
905
  mempty = T2 mempty mempty
2✔
906

907
instance MemPack a => MemPack [a] where
908
  typeName = "[" ++ typeName @a ++ "]"
2✔
909
  packedByteCount es =
2✔
910
    let T2 (Sum listLen) (Sum elemsLen) = foldMap' (\e -> T2 (Sum 1) (Sum (packedByteCount e))) es
2✔
911
     in packedByteCount (Length listLen) + elemsLen
2✔
912
  {-# INLINE packedByteCount #-}
913
  packM as = do
2✔
914
    packM (Length (length as))
2✔
915
    mapM_ packM as
2✔
916
  {-# INLINE packM #-}
917
  unpackM = do
2✔
918
    Length n <- unpackM
2✔
919
    replicateTailM n unpackM
2✔
920
  {-# INLINE unpackM #-}
921

922
instance MemPack a => MemPack (Array a) where
923
  typeName = "(Array " ++ typeName @a ++ ")"
2✔
924
  packedByteCount arr =
2✔
925
    packedByteCount (Length (sizeofArray arr)) + getSum (foldMap' (Sum . packedByteCount) arr)
2✔
926
  {-# INLINE packedByteCount #-}
927
  packM as = do
2✔
928
    packM (Length (length as))
2✔
929
    mapM_ packM as
2✔
930
  {-# INLINE packM #-}
931
  unpackM = do
2✔
932
    Length n <- unpackM
2✔
933
    marr <- unpackLiftST (newArray n (error "Uninitialized"))
1✔
934
    let fill !i = when (i < n) $ do
2✔
935
          e <- unpackM
2✔
936
          unpackLiftST (writeArray marr i e)
2✔
937
          fill (i + 1)
2✔
938
    fill 0
2✔
939
    unpackLiftST (unsafeFreezeArray marr)
2✔
940
  {-# INLINE unpackM #-}
941

942
-- | Tail recursive version of `replicateM`
943
replicateTailM :: Monad m => Int -> m a -> m [a]
944
replicateTailM n f = go n []
2✔
945
  where
946
    go i !acc
2✔
947
      | i <= 0 = pure $ reverse acc
2✔
948
      | otherwise = f >>= \x -> go (i - 1) (x : acc)
1✔
949
{-# INLINE replicateTailM #-}
950

951
instance MemPack ByteArray where
2✔
952
  packedByteCount ba =
2✔
953
    let len = bufferByteCount ba
2✔
954
     in packedByteCount (Length len) + len
2✔
955
  {-# INLINE packedByteCount #-}
956
  packM ba@(ByteArray ba#) = do
2✔
957
    let !len@(I# len#) = bufferByteCount ba
2✔
958
    packM (Length len)
2✔
959
    I# curPos# <- state $ \i -> (i, i + len)
2✔
960
    MutableByteArray mba# <- ask
2✔
961
    lift_# (copyByteArray# ba# 0# mba# curPos# len#)
2✔
962
  {-# INLINE packM #-}
963
  unpackM = unpackByteArray False
2✔
964
  {-# INLINE unpackM #-}
965

966
instance (Typeable a, Prim a) => MemPack (PrimArray a) where
2✔
967
  packedByteCount pa =
2✔
968
    let len = I# (sizeOf# (undefined :: a)) * sizeofPrimArray pa
1✔
969
     in packedByteCount (Length len) + len
2✔
970
  {-# INLINE packedByteCount #-}
971
  packM pa@(PrimArray ba#) = do
2✔
972
    let !len@(I# len#) = I# (sizeOf# (undefined :: a)) * sizeofPrimArray pa
1✔
973
    packM (Length len)
2✔
974
    I# curPos# <- state $ \i -> (i, i + len)
2✔
975
    MutableByteArray mba# <- ask
2✔
976
    lift_# (copyByteArray# ba# 0# mba# curPos# len#)
2✔
977
  {-# INLINE packM #-}
978
  unpackM = (\(ByteArray ba#) -> PrimArray ba#) <$> unpackByteArray False
2✔
979
  {-# INLINE unpackM #-}
980

981
#if !MIN_VERSION_primitive(0,8,0)
982
instance MemPack Prim.ByteArray where
983
  packedByteCount ba =
984
    let len = bufferByteCount ba
985
     in packedByteCount (Length len) + len
986
  {-# INLINE packedByteCount #-}
987
  packM ba@(Prim.ByteArray ba#) = do
988
    let !len@(I# len#) = bufferByteCount ba
989
    packM (Length len)
990
    I# curPos# <- state $ \i -> (i, i + len)
991
    MutableByteArray mba# <- ask
992
    lift_# (copyByteArray# ba# 0# mba# curPos# len#)
993
  {-# INLINE packM #-}
994
  unpackM = (\(ByteArray ba#) -> Prim.ByteArray ba#) <$> unpackByteArray False
995
  {-# INLINE unpackM #-}
996
#endif
997

998
instance MemPack ShortByteString where
×
999
  packedByteCount ba =
×
1000
    let len = bufferByteCount ba
×
1001
     in packedByteCount (Length len) + len
×
1002
  {-# INLINE packedByteCount #-}
UNCOV
1003
  packM = packM . byteArrayFromShortByteString
×
1004
  {-# INLINE packM #-}
UNCOV
1005
  unpackM = byteArrayToShortByteString <$> unpackByteArray False
×
1006
  {-# INLINE unpackM #-}
1007

1008
instance MemPack ByteString where
2✔
1009
  packedByteCount ba =
2✔
1010
    let len = bufferByteCount ba
2✔
1011
     in packedByteCount (Length len) + len
2✔
1012
  {-# INLINE packedByteCount #-}
1013
  packM bs = packM (Length (bufferByteCount bs)) >> packByteStringM bs
2✔
1014
  {-# INLINE packM #-}
1015
  unpackM = pinnedByteArrayToByteString <$> unpackByteArray True
2✔
1016
  {-# INLINE unpackM #-}
1017

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

1056
instance MemPack Text where
2✔
1057
#if MIN_VERSION_text(2,0,0)
1058
  packedByteCount (Text _ _ byteCount) = packedByteCount (Length byteCount) + byteCount
2✔
1059
  packM (Text (T.ByteArray ba#) (I# offset#) len@(I# len#)) = do
2✔
1060
    packM (Length len)
2✔
1061
    I# curPos# <- state $ \i -> (i, i + len)
2✔
1062
    MutableByteArray mba# <- ask
2✔
1063
    lift_# (copyByteArray# ba# offset# mba# curPos# len#)
2✔
1064
#else
1065
  -- FIXME: This is very inefficient and shall be fixed in the next major version
1066
  packedByteCount = packedByteCount . T.encodeUtf8
1067
  packM = packM . T.encodeUtf8
1068
#endif
1069
  {-# INLINE packedByteCount #-}
1070
  {-# INLINE packM #-}
1071
  unpackM = do
2✔
1072
    bs <- unpackM
2✔
1073
    case T.decodeUtf8' bs of
2✔
1074
      Right txt -> pure txt
2✔
UNCOV
1075
      Left exc -> F.fail $ show exc
×
1076
  {-# INLINE unpackM #-}
1077
{- FOURMOLU_ENABLE -}
1078

1079
-- | This is the implementation of `unpackM` for `ByteArray`, `ByteString` and `ShortByteString`
1080
unpackByteArray :: Buffer b => Bool -> Unpack s b ByteArray
1081
unpackByteArray isPinned = unpackByteArrayLen isPinned . unLength =<< unpackM
2✔
1082
{-# INLINE unpackByteArray #-}
1083

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

1102
-- | Increment the offset counter of `Pack` monad by then number of `packedByteCount` and
1103
-- return the starting offset.
1104
packIncrement :: MemPack a => a -> Pack s Int
1105
packIncrement a =
2✔
1106
  state $ \i ->
2✔
1107
    let !n = i + packedByteCount a
1✔
1108
     in (i, n)
2✔
1109
{-# INLINE packIncrement #-}
1110

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

1126
failOutOfBytes :: Int -> Int -> Int -> Unpack s b a
1127
failOutOfBytes i len n =
2✔
1128
  failUnpack $
2✔
1129
    toSomeError $
2✔
1130
      RanOutOfBytesError
2✔
1131
        { ranOutOfBytesRead = i
2✔
1132
        , ranOutOfBytesAvailable = len
2✔
1133
        , ranOutOfBytesRequested = n
2✔
1134
        }
1135
{-# NOINLINE failOutOfBytes #-}
1136

1137
-- | Serialize a type into an unpinned `ByteArray`
1138
--
1139
-- ====__Examples__
1140
--
1141
-- >>> :set -XTypeApplications
1142
-- >>> unpack @[Int] $ pack ([1,2,3,4,5] :: [Int])
1143
-- Right [1,2,3,4,5]
1144
pack :: forall a. (MemPack a, HasCallStack) => a -> ByteArray
1145
pack = packByteArray False
2✔
1146
{-# INLINE pack #-}
1147

1148
-- | Serialize a type into a pinned `ByteString`
1149
packByteString :: forall a. (MemPack a, HasCallStack) => a -> ByteString
1150
packByteString = pinnedByteArrayToByteString . packByteArray True
2✔
1151
{-# INLINE packByteString #-}
1152

1153
-- | Serialize a type into an unpinned `ShortByteString`
1154
packShortByteString :: forall a. (MemPack a, HasCallStack) => a -> ShortByteString
UNCOV
1155
packShortByteString = byteArrayToShortByteString . pack
×
1156
{-# INLINE packShortByteString #-}
1157

1158
-- | Same as `pack`, but allows controlling the pinnedness of allocated memory
1159
packByteArray ::
1160
  forall a.
1161
  (MemPack a, HasCallStack) =>
1162
  -- | Should the array be allocated in pinned memory?
1163
  Bool ->
1164
  a ->
1165
  ByteArray
1166
packByteArray isPinned a =
2✔
1167
  packWithByteArray isPinned (typeName @a) (packedByteCount a) (packM a)
1✔
1168
{-# INLINE packByteArray #-}
1169

1170
-- | Allocate a `MutableByteArray` and run the supplied `Pack` action on it. Freezes the
1171
-- allocated `MutableByteArray` at the end yielding the immutable `ByteArray` with
1172
-- serialization packed into it.
1173
packWithByteArray ::
1174
  HasCallStack =>
1175
  -- | Should the array be allocated in pinned memory?
1176
  Bool ->
1177
  -- | Name of the type that is being serialized. Used for error reporting
1178
  String ->
1179
  -- | Size of the array to be allocated
1180
  Int ->
1181
  (forall s. Pack s ()) ->
1182
  ByteArray
1183
packWithByteArray isPinned name len packerM =
2✔
1184
  runST $ packWithMutableByteArray isPinned name len packerM >>= freezeMutableByteArray
1✔
1185
{-# INLINE packWithByteArray #-}
1186

1187
-- | Same as `packByteArray`, but produces a mutable array instead
1188
packMutableByteArray ::
1189
  forall a s.
1190
  (MemPack a, HasCallStack) =>
1191
  -- | Should the array be allocated in pinned memory?
1192
  Bool ->
1193
  a ->
1194
  ST s (MutableByteArray s)
UNCOV
1195
packMutableByteArray isPinned a =
×
1196
  packWithMutableByteArray isPinned (typeName @a) (packedByteCount a) (packM a)
×
1197
{-# INLINE packMutableByteArray #-}
1198

1199
-- | Allocate a `MutableByteArray` and run the supplied `Pack` action on it.
1200
packWithMutableByteArray ::
1201
  forall s.
1202
  HasCallStack =>
1203
  -- | Should the array be allocated in pinned memory?
1204
  Bool ->
1205
  -- | Name of the type that is being serialized. Used for error reporting
1206
  String ->
1207
  -- | Size of the mutable array to be allocated
1208
  Int ->
1209
  -- | Packing action to be executed on the mutable buffer
1210
  Pack s () ->
1211
  ST s (MutableByteArray s)
1212
packWithMutableByteArray isPinned name len packerM = do
2✔
1213
  mba <- newMutableByteArray isPinned len
2✔
1214
  filledBytes <- execStateT (runPack packerM mba) 0
2✔
1215
  when (filledBytes /= len) $ errorFilledBytes name filledBytes len
1✔
1216
  pure mba
2✔
1217
{-# INLINEABLE packWithMutableByteArray #-}
1218

1219
-- | This is a critical error, therefore we are not gracefully failing this unpacking
1220
errorFilledBytes :: HasCallStack => [Char] -> Int -> Int -> a
UNCOV
1221
errorFilledBytes name filledBytes len =
×
1222
  if filledBytes < len
×
1223
    then
UNCOV
1224
      error $
×
1225
        "Some bug in 'packM' was detected. Buffer of length " <> showBytes len
×
1226
          ++ " was not fully filled while packing " <> name
×
1227
          ++ ". Unfilled " <> showBytes (len - filledBytes) <> "."
×
1228
    else
UNCOV
1229
      error $
×
1230
        "Potential buffer overflow. Some bug in 'packM' was detected while packing " <> name
×
1231
          ++ ". Filled " <> showBytes (filledBytes - len) <> " more than allowed into a buffer of length "
×
1232
          ++ show len
×
1233
{-# NOINLINE errorFilledBytes #-}
1234

1235
-- | Helper function for packing a `ByteString` without its length being packed first.
1236
--
1237
-- @since 0.1.1
1238
packByteStringM :: ByteString -> Pack s ()
1239
packByteStringM bs = do
2✔
1240
  let !len@(I# len#) = bufferByteCount bs
2✔
1241
  I# curPos# <- state $ \i -> (i, i + len)
2✔
1242
  Pack $ \(MutableByteArray mba#) -> lift $ withAddrByteStringST bs $ \addr# ->
2✔
1243
    st_ (copyAddrToByteArray# addr# mba# curPos# len#)
2✔
1244
{-# INLINE packByteStringM #-}
1245

1246
-- | Unpack a `ByteString` of a specified size.
1247
--
1248
-- @since 0.1.1
1249
unpackByteStringM ::
1250
  Buffer b =>
1251
  -- | number of bytes to unpack
1252
  Int ->
1253
  Unpack s b ByteString
1254
unpackByteStringM len = pinnedByteArrayToByteString <$> unpackByteArrayLen True len
2✔
1255
{-# INLINE unpackByteStringM #-}
1256

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

1263
-- | Unpack a memory `Buffer` into a type using its `MemPack` instance. Besides the
1264
-- unpacked type it also returns an index into a buffer where unpacked has stopped.
1265
unpackLeftOverST ::
1266
  forall a b s. (MemPack a, Buffer b, HasCallStack) => b -> FailT SomeError (ST s) (a, Int)
1267
unpackLeftOverST b = do
2✔
1268
  let len = bufferByteCount b
2✔
1269
  res@(_, consumedBytes) <- runStateT (runUnpack unpackM b) 0
2✔
1270
  when (consumedBytes > len) $ errorLeftOver (typeName @a) consumedBytes len
1✔
1271
  pure res
2✔
1272
{-# INLINEABLE unpackLeftOverST #-}
1273

1274
-- | This is a critical error, therefore we are not gracefully failing this unpacking
1275
errorLeftOver :: HasCallStack => String -> Int -> Int -> a
UNCOV
1276
errorLeftOver name consumedBytes len =
×
1277
  error $
×
1278
    "Potential buffer overflow. Some bug in 'unpackM' was detected while unpacking " <> name
×
1279
      ++ ". Consumed " <> showBytes (consumedBytes - len) <> " more than allowed from a buffer of length "
×
1280
      ++ show len
×
1281
{-# NOINLINE errorLeftOver #-}
1282

1283
-- | Unpack a memory `Buffer` into a type using its `MemPack` instance. Besides potential
1284
-- unpacking failures due to a malformed buffer it will also fail the supplied `Buffer`
1285
-- was not fully consumed. Use `unpackLeftOver`, whenever a partially consumed buffer is
1286
-- possible.
1287
unpack :: forall a b. (MemPack a, Buffer b, HasCallStack) => b -> Either SomeError a
1288
unpack = first fromMultipleErrors . runFailAgg . unpackFail
2✔
1289
{-# INLINEABLE unpack #-}
1290

1291
-- | Same as `unpack` except fails in a `Fail` monad, instead of `Either`.
1292
unpackFail :: forall a b. (MemPack a, Buffer b, HasCallStack) => b -> Fail SomeError a
1293
unpackFail b = do
2✔
1294
  let len = bufferByteCount b
2✔
1295
  (a, consumedBytes) <- unpackLeftOver b
2✔
1296
  when (consumedBytes /= len) $ unpackFailNotFullyConsumed (typeName @a) consumedBytes len
2✔
1297
  pure a
2✔
1298
{-# INLINEABLE unpackFail #-}
1299

1300
unpackFailNotFullyConsumed :: Applicative m => String -> Int -> Int -> FailT SomeError m a
1301
unpackFailNotFullyConsumed name consumedBytes len =
2✔
1302
  failT $
2✔
1303
    toSomeError $
2✔
1304
      NotFullyConsumedError
2✔
1305
        { notFullyConsumedRead = consumedBytes
2✔
1306
        , notFullyConsumedAvailable = len
2✔
1307
        , notFullyConsumedTypeName = name
2✔
1308
        }
1309
{-# NOINLINE unpackFailNotFullyConsumed #-}
1310

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

1316
-- | Same as `unpack` except throws a runtime exception upon a failure
1317
unpackError :: forall a b. (MemPack a, Buffer b, HasCallStack) => b -> a
1318
unpackError = errorFail . unpackFail
2✔
1319
{-# INLINEABLE unpackError #-}
1320

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

1327
instance MemPack (VarLen Word16) where
2✔
1328
  packedByteCount = packedVarLenByteCount
2✔
1329
  {-# INLINE packedByteCount #-}
1330
  packM v@(VarLen x) = p7 (p7 (p7 (errorTooManyBits "Word16"))) (numBits - 7)
1✔
1331
    where
1332
      p7 = packIntoCont7 x
2✔
1333
      {-# INLINE p7 #-}
1334
      numBits = packedVarLenByteCount v * 7
2✔
1335
  {-# INLINE packM #-}
1336
  unpackM = do
2✔
1337
    let d7 = unpack7BitVarLen
2✔
1338
        {-# INLINE d7 #-}
1339
    VarLen <$> d7 (d7 (unpack7BitVarLenLast 0b_1111_1100)) 0 0
2✔
1340
  {-# INLINE unpackM #-}
1341

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

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

1373
instance MemPack (VarLen Word) where
2✔
1374
  packedByteCount = packedVarLenByteCount
2✔
1375
  {-# INLINE packedByteCount #-}
1376
#if WORD_SIZE_IN_BITS == 32
1377
  packM v@(VarLen x) = p7 (p7 (p7 (p7 (p7 (errorTooManyBits "Word"))))) (numBits - 7)
1378
    where
1379
      p7 = packIntoCont7 x
1380
      {-# INLINE p7 #-}
1381
      numBits = packedVarLenByteCount v * 7
1382
  {-# INLINE packM #-}
1383
  unpackM = do
1384
    let d7 = unpack7BitVarLen
1385
        {-# INLINE d7 #-}
1386
    VarLen <$> d7 (d7 (d7 (d7 (unpack7BitVarLenLast 0b_1111_0000)))) 0 0
1387
  {-# INLINE unpackM #-}
1388
#elif WORD_SIZE_IN_BITS == 64
1389
  packM v@(VarLen x) =
2✔
1390
    p7 (p7 (p7 (p7 (p7 (p7 (p7 (p7 (p7 (p7 (errorTooManyBits "Word")))))))))) (numBits - 7)
1✔
1391
    where
1392
      p7 = packIntoCont7 x
2✔
1393
      {-# INLINE p7 #-}
1394
      numBits = packedVarLenByteCount v * 7
2✔
1395
  {-# INLINE packM #-}
1396
  unpackM = do
2✔
1397
    let d7 = unpack7BitVarLen
2✔
1398
        {-# INLINE d7 #-}
1399
    VarLen <$> d7 (d7 (d7 (d7 (d7 (d7 (d7 (d7 (d7 (unpack7BitVarLenLast 0b_1111_1110))))))))) 0 0
2✔
1400
  {-# INLINE unpackM #-}
1401
#else
1402
#error "Only 32bit and 64bit systems are supported"
1403
#endif
1404

1405
packedVarLenByteCount :: FiniteBits b => VarLen b -> Int
1406
packedVarLenByteCount (VarLen x) =
2✔
1407
  case (finiteBitSize x - countLeadingZeros x) `quotRem` 7 of
1✔
1408
    (0, 0) -> 1
2✔
1409
    (q, 0) -> q
2✔
1410
    (q, _) -> q + 1
2✔
1411
{-# INLINE packedVarLenByteCount #-}
1412

1413
errorTooManyBits :: HasCallStack => String -> a
UNCOV
1414
errorTooManyBits name =
×
1415
  error $ "Bug detected. Trying to pack more bits for " ++ name ++ " than it should be posssible"
×
1416
{-# NOINLINE errorTooManyBits #-}
1417

1418
packIntoCont7 ::
1419
  (Bits t, Integral t) => t -> (Int -> Pack s ()) -> Int -> Pack s ()
1420
packIntoCont7 x cont n
2✔
1421
  | n <= 0 = packM (fromIntegral @_ @Word8 x .&. complement topBit8)
2✔
1422
  | otherwise = do
1✔
1423
      packM (fromIntegral @_ @Word8 (x `shiftR` n) .|. topBit8)
2✔
1424
      cont (n - 7)
2✔
1425
  where
1426
    topBit8 :: Word8
1427
    !topBit8 = 0b_1000_0000
2✔
1428
{-# INLINE packIntoCont7 #-}
1429

1430
-- | Decode a variable length integral value that is encoded with 7 bits of data
1431
-- and the most significant bit (MSB), the 8th bit is set whenever there are
1432
-- more bits following. Continuation style allows us to avoid
1433
-- recursion. Removing loops is good for performance.
1434
unpack7BitVarLen ::
1435
  (Num a, Bits a, Buffer b) =>
1436
  -- | Continuation that will be invoked if MSB is set
1437
  (Word8 -> a -> Unpack s b a) ->
1438
  -- | Will be set either to 0 initially or to the very first unmodified byte, which is
1439
  -- guaranteed to have the first bit set.
1440
  Word8 ->
1441
  -- | Accumulator
1442
  a ->
1443
  Unpack s b a
1444
unpack7BitVarLen cont firstByte !acc = do
2✔
1445
  b8 :: Word8 <- unpackM
2✔
1446
  if b8 `testBit` 7
2✔
1447
    then
1448
      cont (if firstByte == 0 then b8 else firstByte) (acc `shiftL` 7 .|. fromIntegral (b8 `clearBit` 7))
2✔
1449
    else pure (acc `shiftL` 7 .|. fromIntegral b8)
2✔
1450
{-# INLINE unpack7BitVarLen #-}
1451

1452
unpack7BitVarLenLast ::
1453
  forall t b s.
1454
  (Num t, Bits t, MemPack t, Buffer b) =>
1455
  Word8 ->
1456
  Word8 ->
1457
  t ->
1458
  Unpack s b t
1459
unpack7BitVarLenLast mask firstByte acc = do
2✔
1460
  res <- unpack7BitVarLen (\_ _ -> F.fail "Too many bytes.") firstByte acc
1✔
1461
  -- Only while decoding the last 7bits we check if there was too many
1462
  -- bits supplied at the beginning.
1463
  unless (firstByte .&. mask == 0b_1000_0000) $ unpack7BitVarLenLastFail (typeName @t) firstByte
1✔
1464
  pure res
2✔
1465
{-# INLINE unpack7BitVarLenLast #-}
1466

1467
unpack7BitVarLenLastFail :: F.MonadFail m => String -> Word8 -> m a
UNCOV
1468
unpack7BitVarLenLastFail name firstByte =
×
1469
  F.fail $
×
1470
    "Unexpected bits for "
×
1471
      ++ name
×
1472
      ++ " were set in the first byte of 'VarLen': 0x" <> showHex firstByte ""
×
1473
{-# NOINLINE unpack7BitVarLenLastFail #-}
1474

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

1481
instance Bounded Length where
1482
  minBound = 0
2✔
1483
  maxBound = Length maxBound
2✔
1484

1485
instance Enum Length where
1✔
1486
  toEnum n
2✔
1487
    | n < 0 = error $ "toEnum: Length cannot be negative: " ++ show n
1✔
1488
    | otherwise = Length n
1✔
1489
  fromEnum = unLength
2✔
1490

1491
instance MemPack Length where
2✔
1492
  packedByteCount = packedByteCount . VarLen . fromIntegral @Int @Word . unLength
2✔
1493
  packM (Length n)
2✔
1494
    | n < 0 = packLengthError n
1✔
1495
    | otherwise = packM (VarLen (fromIntegral @Int @Word n))
1✔
1496
  {-# INLINE packM #-}
1497
  unpackM = do
2✔
1498
    VarLen (w :: Word) <- unpackM
2✔
1499
    when (testBit w (finiteBitSize w - 1)) $ upackLengthFail w
1✔
1500
    pure $ Length $ fromIntegral @Word @Int w
2✔
1501
  {-# INLINE unpackM #-}
1502

1503
packLengthError :: Int -> a
UNCOV
1504
packLengthError n = error $ "Length cannot be negative. Supplied: " ++ show n
×
1505
{-# NOINLINE packLengthError #-}
1506

1507
upackLengthFail :: F.MonadFail m => Word -> m a
1508
upackLengthFail w =
2✔
1509
  F.fail $ "Attempt to unpack negative length was detected: " ++ show (fromIntegral @Word @Int w)
1✔
1510
{-# NOINLINE upackLengthFail #-}
1511

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

1516
-- Manually defined instance, since ghc-8.6 has issues with deriving MemPack
1517
instance MemPack Tag where
2✔
1518
  packedByteCount _ = packedTagByteCount
2✔
1519
  {-# INLINE packedByteCount #-}
1520
  unpackM = unpackTagM
2✔
1521
  {-# INLINE unpackM #-}
1522
  packM = packTagM
2✔
1523
  {-# INLINE packM #-}
1524

1525
packedTagByteCount :: Int
1526
packedTagByteCount = SIZEOF_WORD8
2✔
1527
{-# INLINE packedTagByteCount #-}
1528

1529
unpackTagM :: Buffer b => Unpack s b Tag
1530
unpackTagM = Tag <$> unpackM
2✔
1531
{-# INLINE unpackTagM #-}
1532

1533
packTagM :: Tag -> Pack s ()
1534
packTagM = packM . unTag
2✔
1535
{-# INLINE packTagM #-}
1536

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

1540
lift_# :: (State# s -> State# s) -> Pack s ()
1541
lift_# f = Pack $ \_ -> lift $ st_ f
2✔
1542
{-# INLINE lift_# #-}
1543

1544
st_ :: (State# s -> State# s) -> ST s ()
1545
st_ f = ST $ \s# -> (# f s#, () #)
2✔
1546
{-# INLINE st_ #-}
1547

1548
-- | Lift an `ST` action into the `Pack` monad
1549
--
1550
-- @since 0.2.0
1551
packLiftST :: ST s a -> Pack s a
NEW
1552
packLiftST st = Pack (\_ -> StateT (\i -> (,i) <$> st))
×
1553
{-# INLINE packLiftST #-}
1554

1555
-- | Lift an `ST` action into the `Unpack` monad
1556
--
1557
-- @since 0.2.0
1558
unpackLiftST :: ST s a -> Unpack s b a
1559
unpackLiftST st = Unpack (\_ -> StateT (\i -> FailT (Right . (,i) <$> st)))
2✔
1560
{-# 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