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

lehins / mempack / 75

08 Jan 2025 12:05AM UTC coverage: 85.969% (-1.0%) from 86.997%
75

push

github

web-flow
Merge pull request #8 from lehins/more-instances

Instance for `Text` and `Void`

63 of 90 new or added lines in 1 file covered. (70.0%)

27 existing lines in 3 files now uncovered.

674 of 784 relevant lines covered (85.97%)

1.63 hits per line

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

89.09
/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 TypeApplications #-}
15
{-# LANGUAGE UnboxedTuples #-}
16

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

29
  -- * Packing
30
  pack,
31
  packByteString,
32
  packShortByteString,
33

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

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

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

51
  -- ** Helpers
52
  failUnpack,
53
  unpackByteArray,
54
  unpackByteArrayLen,
55
  packByteStringM,
56
  unpackByteStringM,
57

58
  -- * Helper packers
59
  VarLen (..),
60
  Length (..),
61
  Tag (..),
62
  packTagM,
63
  unpackTagM,
64
  unknownTagM,
65
  packedTagByteCount,
66

67
  -- * Internal utilities
68
  replicateTailM,
69
  lift_#,
70
  st_,
71

72
  -- * Re-exports for @GeneralizedNewtypeDeriving@
73
  StateT (..),
74
  FailT (..),
75
) where
76

77
#include "MachDeps.h"
78

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

127
-- | Monad that is used for serializing data into a `MutableByteArray`. It is based on
128
-- `StateT` that tracks the current index into the `MutableByteArray` where next write is
129
-- expected to happen.
130
newtype Pack s a = Pack
131
  { runPack :: MutableByteArray s -> StateT Int (ST s) a
2✔
132
  }
133

134
instance Functor (Pack s) where
×
135
  fmap f (Pack p) = Pack $ \buf -> fmap f (p buf)
×
136
  {-# INLINE fmap #-}
137
instance Applicative (Pack s) where
×
138
  pure = Pack . const . pure
2✔
139
  {-# INLINE pure #-}
140
  Pack a1 <*> Pack a2 =
×
141
    Pack $ \buf -> a1 buf <*> a2 buf
×
142
  {-# INLINE (<*>) #-}
143
  Pack a1 *> Pack a2 =
×
144
    Pack $ \buf -> a1 buf *> a2 buf
×
145
  {-# INLINE (*>) #-}
146
instance Monad (Pack s) where
2✔
147
  Pack m1 >>= p =
2✔
148
    Pack $ \buf -> m1 buf >>= \res -> runPack (p res) buf
2✔
149
  {-# INLINE (>>=) #-}
150
instance MonadReader (MutableByteArray s) (Pack s) where
151
  ask = Pack pure
2✔
152
  {-# INLINE ask #-}
153
  local f (Pack p) = Pack (p . f)
×
154
  {-# INLINE local #-}
155
  reader f = Pack (pure . f)
×
156
  {-# INLINE reader #-}
157
instance MonadState Int (Pack s) where
158
  get = Pack $ const get
×
159
  {-# INLINE get #-}
160
  put = Pack . const . put
×
161
  {-# INLINE put #-}
162
  state = Pack . const . state
2✔
163
  {-# INLINE state #-}
164

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

173
instance Functor (Unpack s) where
×
174
  fmap f (Unpack p) = Unpack $ \buf -> fmap f (p buf)
2✔
175
  {-# INLINE fmap #-}
176
instance Applicative (Unpack b) where
×
177
  pure = Unpack . const . pure
2✔
178
  {-# INLINE pure #-}
179
  Unpack a1 <*> Unpack a2 =
2✔
180
    Unpack $ \buf -> a1 buf <*> a2 buf
1✔
181
  {-# INLINE (<*>) #-}
182
  Unpack a1 *> Unpack a2 =
×
183
    Unpack $ \buf -> a1 buf *> a2 buf
×
184
  {-# INLINE (*>) #-}
185
instance Monad (Unpack b) where
×
186
  Unpack m1 >>= p =
2✔
187
    Unpack $ \buf -> m1 buf >>= \res -> runUnpack (p res) buf
2✔
188
  {-# INLINE (>>=) #-}
189
#if !(MIN_VERSION_base(4,13,0))
190
  fail = Unpack . const . F.fail
191
#endif
192
instance F.MonadFail (Unpack b) where
193
  fail = Unpack . const . F.fail
2✔
194
instance MonadReader b (Unpack b) where
195
  ask = Unpack pure
2✔
196
  {-# INLINE ask #-}
197
  local f (Unpack p) = Unpack (p . f)
×
198
  {-# INLINE local #-}
199
  reader f = Unpack (pure . f)
×
200
  {-# INLINE reader #-}
201
instance MonadState Int (Unpack b) where
202
  get = Unpack $ const get
×
203
  {-# INLINE get #-}
204
  put = Unpack . const . put
×
205
  {-# INLINE put #-}
206
  state = Unpack . const . state
2✔
207
  {-# INLINE state #-}
208

209
instance Alternative (Unpack b) where
×
210
  empty = Unpack $ \_ -> lift empty
×
211
  {-# INLINE empty #-}
212
  Unpack r1 <|> Unpack r2 =
2✔
213
    Unpack $ \buf ->
2✔
214
      case r1 buf of
2✔
215
        StateT m1 ->
216
          case r2 buf of
2✔
217
            StateT m2 -> StateT $ \s -> m1 s <|> m2 s
2✔
218
  {-# INLINE (<|>) #-}
219

220
-- | Failing unpacking with an `Error`.
221
failUnpack :: Error e => e -> Unpack b a
222
failUnpack e = Unpack $ \_ -> lift $ failT (toSomeError e)
2✔
223

224
-- | Efficient serialization interface that operates directly on memory buffers.
225
class MemPack a where
226
  -- | Name of the type that is being deserialized for error reporting. Default
227
  -- implementation relies on `Typeable`.
228
  typeName :: String
229
  default typeName :: Typeable a => String
230
  typeName = show (typeRep (Proxy @a))
1✔
231

232
  -- | Report the exact size in number of bytes that packed version of this type will
233
  -- occupy. It is very important to get this right, otherwise `packM` will result in a
234
  -- runtime exception. Another words this is the expected property that it should hold:
235
  --
236
  -- prop> packedByteCount a == bufferByteCount (pack a)
237
  packedByteCount :: a -> Int
238

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

243
  -- | Read binary representation of the type directly from the buffer, which can be
244
  -- accessed with `ask` when necessary. Direct reads from the buffer should be preceded
245
  -- with advancing the buffer offset with `MonadState` by the number of bytes that will
246
  -- be consumed from the buffer and making sure that no reads outside of the buffer can
247
  -- happen. Violation of these rules will lead to segfaults.
248
  unpackM :: Buffer b => Unpack b a
249

250
instance MemPack () where
×
251
  packedByteCount _ = 0
2✔
252
  {-# INLINE packedByteCount #-}
253
  packM () = pure ()
1✔
254
  {-# INLINE packM #-}
255
  unpackM = pure ()
2✔
256
  {-# INLINE unpackM #-}
257

NEW
258
instance MemPack Void where
×
NEW
259
  packedByteCount _ = 0
×
NEW
260
  packM = absurd
×
NEW
261
  unpackM = F.fail "Void is unpackable"
×
262

263
instance MemPack Bool where
2✔
264
  packedByteCount _ = packedTagByteCount
2✔
265
  {-# INLINE packedByteCount #-}
266
  packM x = packTagM $ if x then 1 else 0
2✔
267
  {-# INLINE packM #-}
268
  unpackM =
2✔
269
    unpackTagM >>= \case
2✔
270
      0 -> pure False
2✔
271
      1 -> pure True
2✔
272
      n -> F.fail $ "Invalid value detected for Bool: " ++ show n
×
273
  {-# INLINE unpackM #-}
274

275
instance MemPack a => MemPack (Maybe a) where
276
  typeName = "Maybe " ++ typeName @a
2✔
277
  packedByteCount = \case
2✔
278
    Nothing -> packedTagByteCount
2✔
279
    Just a -> packedTagByteCount + packedByteCount a
2✔
280
  {-# INLINE packedByteCount #-}
281
  packM = \case
2✔
282
    Nothing -> packTagM 0
2✔
283
    Just a -> packTagM 1 >> packM a
2✔
284
  {-# INLINE packM #-}
285
  unpackM =
2✔
286
    unpackTagM >>= \case
2✔
287
      0 -> pure Nothing
2✔
288
      1 -> Just <$> unpackM
2✔
289
      n -> unknownTagM @(Maybe a) n
×
290
  {-# INLINE unpackM #-}
291

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

309
instance MemPack Char where
2✔
310
  packedByteCount _ = SIZEOF_HSCHAR
2✔
311
  {-# INLINE packedByteCount #-}
312
  packM a@(C# a#) = do
2✔
313
    MutableByteArray mba# <- ask
2✔
314
    I# i# <- packIncrement a
1✔
315
    lift_# (writeWord8ArrayAsWideChar# mba# i# a#)
2✔
316
  {-# INLINE packM #-}
317
  unpackM = do
2✔
318
    I# i# <- guardAdvanceUnpack SIZEOF_HSCHAR
2✔
319
    buf <- ask
2✔
320
    let c =
2✔
321
          buffer
2✔
322
            buf
2✔
323
            (\ba# -> C# (indexWord8ArrayAsWideChar# ba# i#))
2✔
324
            (\addr# -> C# (indexWideCharOffAddr# (addr# `plusAddr#` i#) 0#))
2✔
325
    when (ord c > 0x10FFFF) $
2✔
326
      F.fail $
2✔
327
        "Out of bounds Char was detected: '\\x" ++ showHex (fromEnum c) "'"
×
328
    pure c
2✔
329
  {-# INLINE unpackM #-}
330

331
instance MemPack Float where
2✔
332
  packedByteCount _ = SIZEOF_FLOAT
2✔
333
  {-# INLINE packedByteCount #-}
334
  packM a@(F# a#) = do
2✔
335
    MutableByteArray mba# <- ask
2✔
336
    I# i# <- packIncrement a
1✔
337
    lift_# (writeWord8ArrayAsFloat# mba# i# a#)
2✔
338
  {-# INLINE packM #-}
339
  unpackM = do
2✔
340
    I# i# <- guardAdvanceUnpack SIZEOF_FLOAT
2✔
341
    buf <- ask
2✔
342
    pure $!
2✔
343
      buffer
2✔
344
        buf
2✔
345
        (\ba# -> F# (indexWord8ArrayAsFloat# ba# i#))
2✔
346
        (\addr# -> F# (indexFloatOffAddr# (addr# `plusAddr#` i#) 0#))
2✔
347
  {-# INLINE unpackM #-}
348

349
instance MemPack Double where
2✔
350
  packedByteCount _ = SIZEOF_DOUBLE
2✔
351
  {-# INLINE packedByteCount #-}
352
  packM a@(D# a#) = do
2✔
353
    MutableByteArray mba# <- ask
2✔
354
    I# i# <- packIncrement a
1✔
355
    lift_# (writeWord8ArrayAsDouble# mba# i# a#)
2✔
356
  {-# INLINE packM #-}
357
  unpackM = do
2✔
358
    I# i# <- guardAdvanceUnpack SIZEOF_DOUBLE
2✔
359
    buf <- ask
2✔
360
    pure $!
2✔
361
      buffer
2✔
362
        buf
2✔
363
        (\ba# -> D# (indexWord8ArrayAsDouble# ba# i#))
2✔
364
        (\addr# -> D# (indexDoubleOffAddr# (addr# `plusAddr#` i#) 0#))
2✔
365
  {-# INLINE unpackM #-}
366

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

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

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

423
instance MemPack Int8 where
2✔
424
  packedByteCount _ = SIZEOF_INT8
2✔
425
  {-# INLINE packedByteCount #-}
426
  packM a@(I8# a#) = do
2✔
427
    MutableByteArray mba# <- ask
2✔
428
    I# i# <- packIncrement a
1✔
429
    lift_# (writeInt8Array# mba# i# a#)
2✔
430
  {-# INLINE packM #-}
431
  unpackM = do
2✔
432
    I# i# <- guardAdvanceUnpack SIZEOF_INT8
2✔
433
    buf <- ask
2✔
434
    pure $!
2✔
435
      buffer
2✔
436
        buf
2✔
437
        (\ba# -> I8# (indexInt8Array# ba# i#))
2✔
438
        (\addr# -> I8# (indexInt8OffAddr# (addr# `plusAddr#` i#) 0#))
2✔
439
  {-# INLINE unpackM #-}
440

441
instance MemPack Int16 where
2✔
442
  packedByteCount _ = SIZEOF_INT16
2✔
443
  {-# INLINE packedByteCount #-}
444
  packM a@(I16# a#) = do
2✔
445
    MutableByteArray mba# <- ask
2✔
446
    I# i# <- packIncrement a
1✔
447
    lift_# (writeWord8ArrayAsInt16# mba# i# a#)
2✔
448
  {-# INLINE packM #-}
449
  unpackM = do
2✔
450
    buf <- ask
2✔
451
    I# i# <- guardAdvanceUnpack SIZEOF_INT16
2✔
452
    pure $!
2✔
453
      buffer
2✔
454
        buf
2✔
455
        (\ba# -> I16# (indexWord8ArrayAsInt16# ba# i#))
2✔
456
        (\addr# -> I16# (indexInt16OffAddr# (addr# `plusAddr#` i#) 0#))
2✔
457
  {-# INLINE unpackM #-}
458

459
instance MemPack Int32 where
2✔
460
  packedByteCount _ = SIZEOF_INT32
2✔
461
  {-# INLINE packedByteCount #-}
462
  packM a@(I32# a#) = do
2✔
463
    MutableByteArray mba# <- ask
2✔
464
    I# i# <- packIncrement a
1✔
465
    lift_# (writeWord8ArrayAsInt32# mba# i# a#)
2✔
466
  {-# INLINE packM #-}
467
  unpackM = do
2✔
468
    buf <- ask
2✔
469
    I# i# <- guardAdvanceUnpack SIZEOF_INT32
2✔
470
    pure $!
2✔
471
      buffer
2✔
472
        buf
2✔
473
        (\ba# -> I32# (indexWord8ArrayAsInt32# ba# i#))
2✔
474
        (\addr# -> I32# (indexInt32OffAddr# (addr# `plusAddr#` i#) 0#))
2✔
475
  {-# INLINE unpackM #-}
476

477
instance MemPack Int64 where
2✔
478
  packedByteCount _ = SIZEOF_INT64
2✔
479
  {-# INLINE packedByteCount #-}
480
  packM a@(I64# a#) = do
2✔
481
    MutableByteArray mba# <- ask
2✔
482
    I# i# <- packIncrement a
1✔
483
    lift_# (writeWord8ArrayAsInt64# mba# i# a#)
2✔
484
  {-# INLINE packM #-}
485
  unpackM = do
2✔
486
    buf <- ask
2✔
487
    I# i# <- guardAdvanceUnpack SIZEOF_INT64
2✔
488
    pure $!
2✔
489
      buffer
2✔
490
        buf
2✔
491
        (\ba# -> I64# (indexWord8ArrayAsInt64# ba# i#))
2✔
492
        (\addr# -> I64# (indexInt64OffAddr# (addr# `plusAddr#` i#) 0#))
2✔
493
  {-# INLINE unpackM #-}
494

495
instance MemPack Word where
2✔
496
  packedByteCount _ = SIZEOF_HSWORD
2✔
497
  {-# INLINE packedByteCount #-}
498
  packM a@(W# a#) = do
2✔
499
    MutableByteArray mba# <- ask
2✔
500
    I# i# <- packIncrement a
1✔
501
    lift_# (writeWord8ArrayAsWord# mba# i# a#)
2✔
502
  {-# INLINE packM #-}
503
  unpackM = do
2✔
504
    I# i# <- guardAdvanceUnpack SIZEOF_HSWORD
2✔
505
    buf <- ask
2✔
506
    pure $!
2✔
507
      buffer
2✔
508
        buf
2✔
509
        (\ba# -> W# (indexWord8ArrayAsWord# ba# i#))
2✔
510
        (\addr# -> W# (indexWordOffAddr# (addr# `plusAddr#` i#) 0#))
2✔
511
  {-# INLINE unpackM #-}
512

513
instance MemPack Word8 where
2✔
514
  packedByteCount _ = SIZEOF_WORD8
2✔
515
  {-# INLINE packedByteCount #-}
516
  packM a@(W8# a#) = do
2✔
517
    MutableByteArray mba# <- ask
2✔
518
    I# i# <- packIncrement a
1✔
519
    lift_# (writeWord8Array# mba# i# a#)
2✔
520
  {-# INLINE packM #-}
521
  unpackM = do
2✔
522
    I# i# <- guardAdvanceUnpack SIZEOF_WORD8
2✔
523
    buf <- ask
2✔
524
    pure $!
2✔
525
      buffer
2✔
526
        buf
2✔
527
        (\ba# -> W8# (indexWord8Array# ba# i#))
2✔
528
        (\addr# -> W8# (indexWord8OffAddr# addr# i#))
2✔
529
  {-# INLINE unpackM #-}
530

531
instance MemPack Word16 where
2✔
532
  packedByteCount _ = SIZEOF_WORD16
2✔
533
  {-# INLINE packedByteCount #-}
534
  packM a@(W16# a#) = do
2✔
535
    MutableByteArray mba# <- ask
2✔
536
    I# i# <- packIncrement a
1✔
537
    lift_# (writeWord8ArrayAsWord16# mba# i# a#)
2✔
538
  {-# INLINE packM #-}
539
  unpackM = do
2✔
540
    buf <- ask
2✔
541
    I# i# <- guardAdvanceUnpack SIZEOF_WORD16
2✔
542
    pure $!
2✔
543
      buffer
2✔
544
        buf
2✔
545
        (\ba# -> W16# (indexWord8ArrayAsWord16# ba# i#))
2✔
546
        (\addr# -> W16# (indexWord16OffAddr# (addr# `plusAddr#` i#) 0#))
2✔
547
  {-# INLINE unpackM #-}
548

549
instance MemPack Word32 where
2✔
550
  packedByteCount _ = SIZEOF_WORD32
2✔
551
  {-# INLINE packedByteCount #-}
552
  packM a@(W32# a#) = do
2✔
553
    MutableByteArray mba# <- ask
2✔
554
    I# i# <- packIncrement a
1✔
555
    lift_# (writeWord8ArrayAsWord32# mba# i# a#)
2✔
556
  {-# INLINE packM #-}
557
  unpackM = do
2✔
558
    I# i# <- guardAdvanceUnpack SIZEOF_WORD32
2✔
559
    buf <- ask
2✔
560
    pure $!
2✔
561
      buffer
2✔
562
        buf
2✔
563
        (\ba# -> W32# (indexWord8ArrayAsWord32# ba# i#))
2✔
564
        (\addr# -> W32# (indexWord32OffAddr# (addr# `plusAddr#` i#) 0#))
2✔
565
  {-# INLINE unpackM #-}
566

567
instance MemPack Word64 where
2✔
568
  packedByteCount _ = SIZEOF_WORD64
2✔
569
  {-# INLINE packedByteCount #-}
570
  packM a@(W64# a#) = do
2✔
571
    MutableByteArray mba# <- ask
2✔
572
    I# i# <- packIncrement a
1✔
573
    lift_# (writeWord8ArrayAsWord64# mba# i# a#)
2✔
574
  {-# INLINE packM #-}
575
  unpackM = do
2✔
576
    I# i# <- guardAdvanceUnpack SIZEOF_WORD64
2✔
577
    buf <- ask
2✔
578
    pure $!
2✔
579
      buffer
2✔
580
        buf
2✔
581
        (\ba# -> W64# (indexWord8ArrayAsWord64# ba# i#))
2✔
582
        (\addr# -> W64# (indexWord64OffAddr# (addr# `plusAddr#` i#) 0#))
2✔
583
  {-# INLINE unpackM #-}
584

585
#if __GLASGOW_HASKELL__ >= 900
586
instance MemPack Integer where
2✔
587
  packedByteCount =
2✔
588
    (+ packedTagByteCount) . \case
2✔
589
      IS i# -> packedByteCount (I# i#)
1✔
590
      IP ba# -> packedByteCount (ByteArray ba#)
2✔
591
      IN ba# -> packedByteCount (ByteArray ba#)
2✔
592
  {-# INLINE packedByteCount #-}
593
  packM = \case
2✔
594
    IS i# -> packTagM 0 >> packM (I# i#)
2✔
595
    IP ba# -> packTagM 1 >> packM (ByteArray ba#)
2✔
596
    IN ba# -> packTagM 2 >> packM (ByteArray ba#)
2✔
597
  {-# INLINE packM #-}
598
  unpackM = do
2✔
599
    i <-
600
      unpackTagM >>= \case
2✔
601
        0 -> do
2✔
602
          I# i# <- unpackM
2✔
603
          pure $ IS i#
2✔
604
        1 -> do
2✔
605
          ByteArray ba# <- unpackM
2✔
606
          pure $ IP ba#
2✔
607
        2 -> do
2✔
608
          ByteArray ba# <- unpackM
2✔
609
          pure $ IN ba#
2✔
610
        t -> unknownTagM @Integer t
×
611
    unless (integerCheck i) $ F.fail $ "Invalid Integer decoded " ++ showInteger i
1✔
612
    pure i
2✔
613
    where
614
      showInteger = \case
×
615
        IS i# -> "IS " ++ show (I# i#)
×
616
        IP ba# -> "IP " ++ show (ByteArray ba#)
×
617
        IN ba# -> "IN " ++ show (ByteArray ba#)
×
618
  {-# INLINE unpackM #-}
619

620
instance MemPack Natural where
2✔
621
  packedByteCount =
2✔
622
    (+ packedTagByteCount) . \case
2✔
623
      NS w# -> packedByteCount (W# w#)
1✔
624
      NB ba# -> packedByteCount (ByteArray ba#)
2✔
625
  {-# INLINE packedByteCount #-}
626
  packM = \case
2✔
627
    NS w# -> packTagM 0 >> packM (W# w#)
2✔
628
    NB ba# -> packTagM 1 >> packM (ByteArray ba#)
2✔
629
  {-# INLINE packM #-}
630
  unpackM = do
2✔
631
    n <-
632
      unpackTagM >>= \case
2✔
633
        0 -> do
2✔
634
          W# w# <- unpackM
2✔
635
          pure $ NS w#
2✔
636
        1 -> do
2✔
637
          ByteArray ba# <- unpackM
2✔
638
          pure $ NB ba#
2✔
639
        t -> unknownTagM @Natural t
×
640
    unless (naturalCheck n) $ F.fail $ "Invalid Natural decoded " ++ showNatural n
1✔
641
    pure n
2✔
642
    where
643
      showNatural = \case
×
644
        NS w# -> "NS " ++ show (W# w#)
×
645
        NB ba# -> "NB " ++ show (ByteArray ba#)
×
646
  {-# INLINE unpackM #-}
647

648
#elif defined(MIN_VERSION_integer_gmp)
649

650
instance MemPack Integer where
651
  packedByteCount =
652
    (+ packedTagByteCount) . \case
653
      S# i# -> packedByteCount (I# i#)
654
      Jp# (BN# ba#) -> packedByteCount (ByteArray ba#)
655
      Jn# (BN# ba#) -> packedByteCount (ByteArray ba#)
656
  {-# INLINE packedByteCount #-}
657
  packM = \case
658
    S# i# -> packTagM 0 >> packM (I# i#)
659
    Jp# (BN# ba#) -> packTagM 1 >> packM (ByteArray ba#)
660
    Jn# (BN# ba#) -> packTagM 2 >> packM (ByteArray ba#)
661
  {-# INLINE packM #-}
662
  unpackM = do
663
    i <-
664
      unpackTagM >>= \case
665
        0 -> do
666
          I# i# <- unpackM
667
          pure $ S# i#
668
        1 -> do
669
          ByteArray ba# <- unpackM
670
          pure $ Jp# (BN# ba#)
671
        2 -> do
672
          ByteArray ba# <- unpackM
673
          pure $ Jn# (BN# ba#)
674
        t -> unknownTagM @Integer t
675
    unless (isTrue# (isValidInteger# i)) $ F.fail $ "Invalid Integer decoded " ++ showInteger i
676
    pure i
677
    where
678
      showInteger = \case
679
        S# i# -> "S# " ++ show (I# i#)
680
        Jp# (BN# ba#) -> "Jp# " ++ show (ByteArray ba#)
681
        Jn# (BN# ba#) -> "Jn# " ++ show (ByteArray ba#)
682
  {-# INLINE unpackM #-}
683

684
instance MemPack Natural where
685
  packedByteCount =
686
    (+ packedTagByteCount) . \case
687
      NatS# w# -> packedByteCount (W# w#)
688
      NatJ# (BN# ba#) -> packedByteCount (ByteArray ba#)
689
  {-# INLINE packedByteCount #-}
690
  packM = \case
691
    NatS# w# -> packTagM 0 >> packM (W# w#)
692
    NatJ# (BN# ba#) -> packTagM 1 >> packM (ByteArray ba#)
693
  {-# INLINE packM #-}
694
  unpackM = do
695
    n <-
696
      unpackTagM >>= \case
697
        0 -> do
698
          W# w# <- unpackM
699
          pure $ NatS# w#
700
        1 -> do
701
          ByteArray ba# <- unpackM
702
          pure $ NatJ# (BN# ba#)
703
        t -> unknownTagM @Natural t
704
    unless (isValidNatural n) $ F.fail $ "Invalid Natural decoded " ++ showNatural n
705
    pure n
706
    where
707
      showNatural = \case
708
        NatS# w# -> "NatS# " ++ show (W# w#)
709
        NatJ# (BN#  ba#) -> "NatJ# " ++ show (ByteArray ba#)
710
  {-# INLINE unpackM #-}
711

712
#endif
713

714
instance MemPack a => MemPack (Complex a) where
715
  typeName = "Complex " ++ typeName @a
2✔
716
  packedByteCount (a :+ b) = packedByteCount a + packedByteCount b
1✔
717
  {-# INLINE packedByteCount #-}
718
  packM (a :+ b) = packM a >> packM b
2✔
719
  {-# INLINE packM #-}
720
  unpackM = do
2✔
721
    !a <- unpackM
2✔
722
    !b <- unpackM
2✔
723
    pure (a :+ b)
2✔
724
  {-# INLINE unpackM #-}
725

726
instance (MemPack a, Integral a) => MemPack (Ratio a) where
727
  typeName = "Ratio " ++ typeName @a
2✔
728
  packedByteCount r = packedByteCount (numerator r) + packedByteCount (denominator r)
1✔
729
  {-# INLINE packedByteCount #-}
730
  packM r = packM (numerator r) >> packM (denominator r)
2✔
731
  {-# INLINE packM #-}
732
  unpackM = do
2✔
733
    !a <- unpackM
2✔
734
    !b <- unpackM
2✔
735
    when (b == 0) $ F.fail $ "Zero denominator was detected when unpacking " ++ typeName @(Ratio a)
1✔
736
    pure (a % b)
2✔
737
  {-# INLINE unpackM #-}
738

739
instance (MemPack a, MemPack b) => MemPack (a, b) where
740
  typeName = "(" ++ typeName @a ++ "," ++ typeName @b ++ ")"
2✔
741
  packedByteCount (a, b) = packedByteCount a + packedByteCount b
1✔
742
  {-# INLINE packedByteCount #-}
743
  packM (a, b) = packM a >> packM b
2✔
744
  {-# INLINEABLE packM #-}
745
  unpackM = do
2✔
746
    !a <- unpackM
2✔
747
    !b <- unpackM
2✔
748
    pure (a, b)
2✔
749
  {-# INLINEABLE unpackM #-}
750

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

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

779
instance (MemPack a, MemPack b, MemPack c, MemPack d, MemPack e) => MemPack (a, b, c, d, e) where
780
  typeName =
2✔
781
    "("
2✔
782
      ++ intercalate
2✔
783
        ","
2✔
784
        [ typeName @a
2✔
785
        , typeName @b
2✔
786
        , typeName @c
2✔
787
        , typeName @d
2✔
788
        , typeName @e
2✔
789
        ]
790
      ++ ")"
2✔
791
  packedByteCount (a, b, c, d, e) =
2✔
792
    packedByteCount a + packedByteCount b + packedByteCount c + packedByteCount d + packedByteCount e
1✔
793
  {-# INLINE packedByteCount #-}
794
  packM (a, b, c, d, e) =
2✔
795
    packM a >> packM b >> packM c >> packM d >> packM e
2✔
796
  {-# INLINEABLE packM #-}
797
  unpackM = do
2✔
798
    !a <- unpackM
2✔
799
    !b <- unpackM
2✔
800
    !c <- unpackM
2✔
801
    !d <- unpackM
2✔
802
    !e <- unpackM
2✔
803
    pure (a, b, c, d, e)
2✔
804
  {-# INLINEABLE unpackM #-}
805

806
instance (MemPack a, MemPack b, MemPack c, MemPack d, MemPack e, MemPack f) => MemPack (a, b, c, d, e, f) where
807
  typeName =
2✔
808
    "("
2✔
809
      ++ intercalate
2✔
810
        ","
2✔
811
        [ typeName @a
2✔
812
        , typeName @b
2✔
813
        , typeName @c
2✔
814
        , typeName @d
2✔
815
        , typeName @e
2✔
816
        , typeName @f
2✔
817
        ]
818
      ++ ")"
2✔
819
  packedByteCount (a, b, c, d, e, f) =
2✔
820
    packedByteCount a
1✔
821
      + packedByteCount b
1✔
822
      + packedByteCount c
2✔
823
      + packedByteCount d
2✔
824
      + packedByteCount e
1✔
825
      + packedByteCount f
2✔
826
  {-# INLINE packedByteCount #-}
827
  packM (a, b, c, d, e, f) =
2✔
828
    packM a >> packM b >> packM c >> packM d >> packM e >> packM f
2✔
829
  {-# INLINEABLE packM #-}
830
  unpackM = do
2✔
831
    !a <- unpackM
2✔
832
    !b <- unpackM
2✔
833
    !c <- unpackM
2✔
834
    !d <- unpackM
2✔
835
    !e <- unpackM
2✔
836
    !f <- unpackM
2✔
837
    pure (a, b, c, d, e, f)
2✔
838
  {-# INLINEABLE unpackM #-}
839

840
instance
841
  (MemPack a, MemPack b, MemPack c, MemPack d, MemPack e, MemPack f, MemPack g) =>
842
  MemPack (a, b, c, d, e, f, g)
843
  where
844
  typeName =
2✔
845
    "("
2✔
846
      ++ intercalate
2✔
847
        ","
2✔
848
        [ typeName @a
2✔
849
        , typeName @b
2✔
850
        , typeName @c
2✔
851
        , typeName @d
2✔
852
        , typeName @e
2✔
853
        , typeName @f
2✔
854
        , typeName @g
2✔
855
        ]
856
      ++ ")"
2✔
857
  packedByteCount (a, b, c, d, e, f, g) =
2✔
858
    packedByteCount a
1✔
859
      + packedByteCount b
1✔
860
      + packedByteCount c
1✔
861
      + packedByteCount d
1✔
862
      + packedByteCount e
1✔
863
      + packedByteCount f
1✔
864
      + packedByteCount g
2✔
865
  {-# INLINE packedByteCount #-}
866
  packM (a, b, c, d, e, f, g) =
2✔
867
    packM a >> packM b >> packM c >> packM d >> packM e >> packM f >> packM g
2✔
868
  {-# INLINEABLE packM #-}
869
  unpackM = do
2✔
870
    !a <- unpackM
2✔
871
    !b <- unpackM
2✔
872
    !c <- unpackM
2✔
873
    !d <- unpackM
2✔
874
    !e <- unpackM
2✔
875
    !f <- unpackM
2✔
876
    !g <- unpackM
2✔
877
    pure (a, b, c, d, e, f, g)
2✔
878
  {-# INLINEABLE unpackM #-}
879

880
instance MemPack a => MemPack [a] where
881
  typeName = "[" ++ typeName @a ++ "]"
2✔
882
  packedByteCount es = packedByteCount (Length (length es)) + getSum (foldMap (Sum . packedByteCount) es)
2✔
883
  {-# INLINE packedByteCount #-}
884
  packM as = do
2✔
885
    packM (Length (length as))
2✔
886
    mapM_ packM as
2✔
887
  {-# INLINE packM #-}
888
  unpackM = do
2✔
889
    Length n <- unpackM
2✔
890
    replicateTailM n unpackM
2✔
891
  {-# INLINE unpackM #-}
892

893
-- | Tail recursive version of `replicateM`
894
replicateTailM :: Monad m => Int -> m a -> m [a]
895
replicateTailM n f = go n []
2✔
896
  where
897
    go i !acc
2✔
898
      | i <= 0 = pure $ reverse acc
2✔
899
      | otherwise = f >>= \x -> go (i - 1) (x : acc)
1✔
900
{-# INLINE replicateTailM #-}
901

902
instance MemPack ByteArray where
2✔
903
  packedByteCount ba =
2✔
904
    let len = bufferByteCount ba
2✔
905
     in packedByteCount (Length len) + len
2✔
906
  {-# INLINE packedByteCount #-}
907
  packM ba@(ByteArray ba#) = do
2✔
908
    let !len@(I# len#) = bufferByteCount ba
2✔
909
    packM (Length len)
2✔
910
    I# curPos# <- state $ \i -> (i, i + len)
2✔
911
    MutableByteArray mba# <- ask
2✔
912
    lift_# (copyByteArray# ba# 0# mba# curPos# len#)
2✔
913
  {-# INLINE packM #-}
914
  unpackM = unpackByteArray False
2✔
915
  {-# INLINE unpackM #-}
916

UNCOV
917
instance MemPack ShortByteString where
×
UNCOV
918
  packedByteCount ba =
×
UNCOV
919
    let len = bufferByteCount ba
×
UNCOV
920
     in packedByteCount (Length len) + len
×
921
  {-# INLINE packedByteCount #-}
UNCOV
922
  packM = packM . byteArrayFromShortByteString
×
923
  {-# INLINE packM #-}
UNCOV
924
  unpackM = byteArrayToShortByteString <$> unpackByteArray False
×
925
  {-# INLINE unpackM #-}
926

927
instance MemPack ByteString where
2✔
928
  packedByteCount ba =
2✔
929
    let len = bufferByteCount ba
2✔
930
     in packedByteCount (Length len) + len
2✔
931
  {-# INLINE packedByteCount #-}
932
  packM bs = packM (Length (bufferByteCount bs)) >> packByteStringM bs
2✔
933
  {-# INLINE packM #-}
934
  unpackM = pinnedByteArrayToByteString <$> unpackByteArray True
2✔
935
  {-# INLINE unpackM #-}
936

937
{- FOURMOLU_DISABLE -}
938
instance MemPack BSL.ByteString where
2✔
939
#if WORD_SIZE_IN_BITS == 32
940
  packedByteCount bsl =
941
    let len64 = BSL.length bsl
942
        len = fromIntegral len64
943
     in if len64 <= fromIntegral (maxBound :: Int)
944
        then packedByteCount (Length len) + len
945
        else error $ mconcat [ "Cannot pack more that '2 ^ 31 - 1' bytes on a 32bit architecture, "
946
                             , "but tried to pack a lazy ByteString with "
947
                             , show len64
948
                             , " bytes"
949
                             ]
950
#elif WORD_SIZE_IN_BITS == 64
951
  packedByteCount bsl =
2✔
952
    let len = fromIntegral (BSL.length bsl)
2✔
953
     in packedByteCount (Length len) + len
2✔
954
#else
955
#error "Only 32bit and 64bit systems are supported"
956
#endif
957
  {-# INLINE packedByteCount #-}
958
  packM bsl = do
2✔
959
    let !len = fromIntegral (BSL.length bsl)
2✔
960
        go BSL.Empty = pure ()
1✔
961
        go (BSL.Chunk bs rest) = packByteStringM bs >> go rest
2✔
962
    packM (Length len)
2✔
963
    go bsl
2✔
964
  {-# INLINE packM #-}
965
  unpackM = do
2✔
966
    Length len <- unpackM
2✔
967
    let c = BSL.defaultChunkSize
2✔
968
        go n
2✔
969
          | n == 0 = pure BSL.Empty
2✔
970
          | n <= c = BSL.Chunk <$> unpackByteStringM n <*> pure BSL.Empty
1✔
NEW
971
          | otherwise = BSL.Chunk <$> unpackByteStringM c <*> go (n - c)
×
972
    go len
2✔
973
  {-# INLINE unpackM #-}
974

975
instance MemPack Text where
2✔
976
#if MIN_VERSION_text(2,0,0)
977
  packedByteCount (Text _ _ byteCount) = packedByteCount (Length byteCount) + byteCount
2✔
978
  packM (Text (T.ByteArray ba#) (I# offset#) len@(I# len#)) = do
2✔
979
    packM (Length len)
2✔
980
    I# curPos# <- state $ \i -> (i, i + len)
2✔
981
    MutableByteArray mba# <- ask
2✔
982
    lift_# (copyByteArray# ba# offset# mba# curPos# len#)
2✔
983
#else
984
  -- FIXME: This is very inefficient and shall be fixed in the next major version
985
  packedByteCount = packedByteCount . T.encodeUtf8
986
  packM = packM . T.encodeUtf8
987
#endif
988
  {-# INLINE packedByteCount #-}
989
  {-# INLINE packM #-}
990
  unpackM = do
2✔
991
    bs <- unpackM
2✔
992
    case T.decodeUtf8' bs of
2✔
993
      Right txt -> pure txt
2✔
NEW
994
      Left exc -> F.fail $ show exc
×
995
  {-# INLINE unpackM #-}
996
{- FOURMOLU_ENABLE -}
997

998
-- | This is the implementation of `unpackM` for `ByteArray`, `ByteString` and `ShortByteString`
999
unpackByteArray :: Buffer b => Bool -> Unpack b ByteArray
1000
unpackByteArray isPinned = unpackByteArrayLen isPinned . unLength =<< unpackM
2✔
1001
{-# INLINE unpackByteArray #-}
1002

1003
-- | Unpack a `ByteArray` with supplied number of bytes.
1004
--
1005
-- Similar to `unpackByteArray`, except it does not unpack a length.
1006
--
1007
-- @since 0.1.1
1008
unpackByteArrayLen :: Buffer b => Bool -> Int -> Unpack b ByteArray
1009
unpackByteArrayLen isPinned len@(I# len#) = do
2✔
1010
  I# curPos# <- guardAdvanceUnpack len
2✔
1011
  buf <- ask
2✔
1012
  pure $! runST $ do
2✔
1013
    mba@(MutableByteArray mba#) <- newMutableByteArray isPinned len
2✔
1014
    buffer
2✔
1015
      buf
2✔
1016
      (\ba# -> st_ (copyByteArray# ba# curPos# mba# 0# len#))
2✔
1017
      (\addr# -> st_ (copyAddrToByteArray# (addr# `plusAddr#` curPos#) mba# 0# len#))
2✔
1018
    freezeMutableByteArray mba
2✔
1019
{-# INLINE unpackByteArrayLen #-}
1020

1021
-- | Increment the offset counter of `Pack` monad by then number of `packedByteCount` and
1022
-- return the starting offset.
1023
packIncrement :: MemPack a => a -> Pack s Int
1024
packIncrement a =
2✔
1025
  state $ \i ->
2✔
1026
    let !n = i + packedByteCount a
1✔
1027
     in (i, n)
2✔
1028
{-# INLINE packIncrement #-}
1029

1030
-- | Increment the offset counter of `Unpack` monad by the supplied number of
1031
-- bytes. Returns the original offset or fails with `RanOutOfBytesError` whenever there is
1032
-- not enough bytes in the `Buffer`.
1033
guardAdvanceUnpack :: Buffer b => Int -> Unpack b Int
1034
guardAdvanceUnpack n@(I# n#) = do
2✔
1035
  buf <- ask
2✔
1036
  let !len = bufferByteCount buf
2✔
1037
  -- Check that we still have enough bytes, while guarding against integer overflow.
1038
  join $ state $ \i@(I# i#) ->
2✔
1039
    case addIntC# i# n# of
2✔
1040
      (# adv#, 0# #)
1041
        | len >= I# adv# -> (pure i, I# adv#)
2✔
1042
      _ -> (failOutOfBytes i len n, i)
1✔
1043
{-# INLINE guardAdvanceUnpack #-}
1044

1045
failOutOfBytes :: Int -> Int -> Int -> Unpack b a
1046
failOutOfBytes i len n =
2✔
1047
  failUnpack $
2✔
1048
    toSomeError $
2✔
1049
      RanOutOfBytesError
2✔
1050
        { ranOutOfBytesRead = i
2✔
1051
        , ranOutOfBytesAvailable = len
2✔
1052
        , ranOutOfBytesRequested = n
2✔
1053
        }
1054
{-# NOINLINE failOutOfBytes #-}
1055

1056
-- | Serialize a type into an unpinned `ByteArray`
1057
--
1058
-- ====__Examples__
1059
--
1060
-- >>> :set -XTypeApplications
1061
-- >>> unpack @[Int] $ pack ([1,2,3,4,5] :: [Int])
1062
-- Right [1,2,3,4,5]
1063
pack :: forall a. (MemPack a, HasCallStack) => a -> ByteArray
1064
pack = packByteArray False
2✔
1065
{-# INLINE pack #-}
1066

1067
-- | Serialize a type into a pinned `ByteString`
1068
packByteString :: forall a. (MemPack a, HasCallStack) => a -> ByteString
1069
packByteString = pinnedByteArrayToByteString . packByteArray True
2✔
1070
{-# INLINE packByteString #-}
1071

1072
-- | Serialize a type into an unpinned `ShortByteString`
1073
packShortByteString :: forall a. (MemPack a, HasCallStack) => a -> ShortByteString
UNCOV
1074
packShortByteString = byteArrayToShortByteString . pack
×
1075
{-# INLINE packShortByteString #-}
1076

1077
-- | Same as `pack`, but allows controlling the pinnedness of allocated memory
1078
packByteArray ::
1079
  forall a.
1080
  (MemPack a, HasCallStack) =>
1081
  -- | Should the array be allocated in pinned memory?
1082
  Bool ->
1083
  a ->
1084
  ByteArray
1085
packByteArray isPinned a =
2✔
1086
  packWithByteArray isPinned (typeName @a) (packedByteCount a) (packM a)
1✔
1087
{-# INLINE packByteArray #-}
1088

1089
-- | Allocate a `MutableByteArray` and run the supplied `Pack` action on it. Freezes the
1090
-- allocated `MutableByteArray` at the end yielding the immutable `ByteArray` with
1091
-- serialization packed into it.
1092
packWithByteArray ::
1093
  HasCallStack =>
1094
  -- | Should the array be allocated in pinned memory?
1095
  Bool ->
1096
  -- | Name of the type that is being serialized. Used for error reporting
1097
  String ->
1098
  -- | Size of the array to be allocated
1099
  Int ->
1100
  (forall s. Pack s ()) ->
1101
  ByteArray
1102
packWithByteArray isPinned name len packerM =
2✔
1103
  runST $ packWithMutableByteArray isPinned name len packerM >>= freezeMutableByteArray
1✔
1104
{-# INLINE packWithByteArray #-}
1105

1106
-- | Same as `packByteArray`, but produces a mutable array instead
1107
packMutableByteArray ::
1108
  forall a s.
1109
  (MemPack a, HasCallStack) =>
1110
  -- | Should the array be allocated in pinned memory?
1111
  Bool ->
1112
  a ->
1113
  ST s (MutableByteArray s)
UNCOV
1114
packMutableByteArray isPinned a =
×
1115
  packWithMutableByteArray isPinned (typeName @a) (packedByteCount a) (packM a)
×
1116
{-# INLINE packMutableByteArray #-}
1117

1118
-- | Allocate a `MutableByteArray` and run the supplied `Pack` action on it.
1119
packWithMutableByteArray ::
1120
  forall s.
1121
  HasCallStack =>
1122
  -- | Should the array be allocated in pinned memory?
1123
  Bool ->
1124
  -- | Name of the type that is being serialized. Used for error reporting
1125
  String ->
1126
  -- | Size of the mutable array to be allocated
1127
  Int ->
1128
  -- | Packing action to be executed on the mutable buffer
1129
  Pack s () ->
1130
  ST s (MutableByteArray s)
1131
packWithMutableByteArray isPinned name len packerM = do
2✔
1132
  mba <- newMutableByteArray isPinned len
2✔
1133
  filledBytes <- execStateT (runPack packerM mba) 0
2✔
1134
  when (filledBytes /= len) $ errorFilledBytes name filledBytes len
1✔
1135
  pure mba
2✔
1136
{-# INLINEABLE packWithMutableByteArray #-}
1137

1138
-- | This is a critical error, therefore we are not gracefully failing this unpacking
1139
errorFilledBytes :: HasCallStack => [Char] -> Int -> Int -> a
NEW
1140
errorFilledBytes name filledBytes len =
×
NEW
1141
  if filledBytes < len
×
1142
    then
NEW
1143
      error $
×
NEW
1144
        "Some bug in 'packM' was detected. Buffer of length " <> showBytes len
×
NEW
1145
          ++ " was not fully filled while packing " <> name
×
NEW
1146
          ++ ". Unfilled " <> showBytes (len - filledBytes) <> "."
×
1147
    else
NEW
1148
      error $
×
NEW
1149
        "Potential buffer overflow. Some bug in 'packM' was detected while packing " <> name
×
NEW
1150
          ++ ". Filled " <> showBytes (filledBytes - len) <> " more than allowed into a buffer of length "
×
NEW
1151
          ++ show len
×
1152
{-# NOINLINE errorFilledBytes #-}
1153

1154
-- | Helper function for packing a `ByteString` without its length being packed first.
1155
--
1156
-- @since 0.1.1
1157
packByteStringM :: ByteString -> Pack s ()
1158
packByteStringM bs = do
2✔
1159
  let !len@(I# len#) = bufferByteCount bs
2✔
1160
  I# curPos# <- state $ \i -> (i, i + len)
2✔
1161
  Pack $ \(MutableByteArray mba#) -> lift $ withPtrByteStringST bs $ \(Ptr addr#) ->
2✔
1162
    st_ (copyAddrToByteArray# addr# mba# curPos# len#)
2✔
1163
{-# INLINE packByteStringM #-}
1164

1165
-- | Unpack a `ByteString` of a specified size.
1166
--
1167
-- @since 0.1.1
1168
unpackByteStringM ::
1169
  Buffer b =>
1170
  -- | number of bytes to unpack
1171
  Int ->
1172
  Unpack b ByteString
1173
unpackByteStringM len = pinnedByteArrayToByteString <$> unpackByteArrayLen True len
2✔
1174
{-# INLINE unpackByteStringM #-}
1175

1176
-- | Unpack a memory `Buffer` into a type using its `MemPack` instance. Besides the
1177
-- unpacked type it also returns an index into a buffer where unpacked has stopped.
1178
unpackLeftOver :: forall a b. (MemPack a, Buffer b, HasCallStack) => b -> Fail SomeError (a, Int)
1179
unpackLeftOver b = do
2✔
1180
  let len = bufferByteCount b
2✔
1181
  res@(_, consumedBytes) <- runStateT (runUnpack unpackM b) 0
2✔
1182
  when (consumedBytes > len) $ errorLeftOver (typeName @a) consumedBytes len
1✔
1183
  pure res
2✔
1184
{-# INLINEABLE unpackLeftOver #-}
1185

1186
-- | This is a critical error, therefore we are not gracefully failing this unpacking
1187
errorLeftOver :: HasCallStack => String -> Int -> Int -> a
NEW
1188
errorLeftOver name consumedBytes len =
×
NEW
1189
  error $
×
NEW
1190
    "Potential buffer overflow. Some bug in 'unpackM' was detected while unpacking " <> name
×
NEW
1191
      ++ ". Consumed " <> showBytes (consumedBytes - len) <> " more than allowed from a buffer of length "
×
NEW
1192
      ++ show len
×
1193
{-# NOINLINE errorLeftOver #-}
1194

1195
-- | Unpack a memory `Buffer` into a type using its `MemPack` instance. Besides potential
1196
-- unpacking failures due to a malformed buffer it will also fail the supplied `Buffer`
1197
-- was not fully consumed. Use `unpackLeftOver`, whenever a partially consumed buffer is
1198
-- possible.
1199
unpack :: forall a b. (MemPack a, Buffer b, HasCallStack) => b -> Either SomeError a
1200
unpack = first fromMultipleErrors . runFailAgg . unpackFail
2✔
1201
{-# INLINEABLE unpack #-}
1202

1203
-- | Same as `unpack` except fails in a `Fail` monad, instead of `Either`.
1204
unpackFail :: forall a b. (MemPack a, Buffer b, HasCallStack) => b -> Fail SomeError a
1205
unpackFail b = do
2✔
1206
  let len = bufferByteCount b
2✔
1207
  (a, consumedBytes) <- unpackLeftOver b
2✔
1208
  when (consumedBytes /= len) $ unpackFailNotFullyConsumed (typeName @a) consumedBytes len
2✔
1209
  pure a
2✔
1210
{-# INLINEABLE unpackFail #-}
1211

1212
unpackFailNotFullyConsumed :: Applicative m => String -> Int -> Int -> FailT SomeError m a
1213
unpackFailNotFullyConsumed name consumedBytes len =
2✔
1214
  failT $
2✔
1215
    toSomeError $
2✔
1216
      NotFullyConsumedError
2✔
1217
        { notFullyConsumedRead = consumedBytes
2✔
1218
        , notFullyConsumedAvailable = len
2✔
1219
        , notFullyConsumedTypeName = name
2✔
1220
        }
1221
{-# NOINLINE unpackFailNotFullyConsumed #-}
1222

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

1228
-- | Same as `unpack` except throws a runtime exception upon a failure
1229
unpackError :: forall a b. (MemPack a, Buffer b, HasCallStack) => b -> a
1230
unpackError = errorFail . unpackFail
2✔
1231
{-# INLINEABLE unpackError #-}
1232

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

1239
instance MemPack (VarLen Word16) where
2✔
1240
  packedByteCount = packedVarLenByteCount
2✔
1241
  {-# INLINE packedByteCount #-}
1242
  packM v@(VarLen x) = p7 (p7 (p7 (errorTooManyBits "Word16"))) (numBits - 7)
1✔
1243
    where
1244
      p7 = packIntoCont7 x
2✔
1245
      {-# INLINE p7 #-}
1246
      numBits = packedVarLenByteCount v * 7
2✔
1247
  {-# INLINE packM #-}
1248
  unpackM = do
2✔
1249
    let d7 = unpack7BitVarLen
2✔
1250
        {-# INLINE d7 #-}
1251
    VarLen <$> d7 (d7 (unpack7BitVarLenLast 0b_1111_1100)) 0 0
2✔
1252
  {-# INLINE unpackM #-}
1253

1254
instance MemPack (VarLen Word32) where
2✔
1255
  packedByteCount = packedVarLenByteCount
2✔
1256
  {-# INLINE packedByteCount #-}
1257
  packM v@(VarLen x) = p7 (p7 (p7 (p7 (p7 (errorTooManyBits "Word32"))))) (numBits - 7)
1✔
1258
    where
1259
      p7 = packIntoCont7 x
2✔
1260
      {-# INLINE p7 #-}
1261
      numBits = packedVarLenByteCount v * 7
2✔
1262
  {-# INLINE packM #-}
1263
  unpackM = do
2✔
1264
    let d7 = unpack7BitVarLen
2✔
1265
        {-# INLINE d7 #-}
1266
    VarLen <$> d7 (d7 (d7 (d7 (unpack7BitVarLenLast 0b_1111_0000)))) 0 0
2✔
1267
  {-# INLINE unpackM #-}
1268

1269
instance MemPack (VarLen Word64) where
2✔
1270
  packedByteCount = packedVarLenByteCount
2✔
1271
  {-# INLINE packedByteCount #-}
1272
  packM v@(VarLen x) =
2✔
1273
    p7 (p7 (p7 (p7 (p7 (p7 (p7 (p7 (p7 (p7 (errorTooManyBits "Word64")))))))))) (numBits - 7)
1✔
1274
    where
1275
      p7 = packIntoCont7 x
2✔
1276
      {-# INLINE p7 #-}
1277
      numBits = packedVarLenByteCount v * 7
2✔
1278
  {-# INLINE packM #-}
1279
  unpackM = do
2✔
1280
    let d7 = unpack7BitVarLen
2✔
1281
        {-# INLINE d7 #-}
1282
    VarLen <$> d7 (d7 (d7 (d7 (d7 (d7 (d7 (d7 (d7 (unpack7BitVarLenLast 0b_1111_1110))))))))) 0 0
2✔
1283
  {-# INLINE unpackM #-}
1284

1285
instance MemPack (VarLen Word) where
2✔
1286
  packedByteCount = packedVarLenByteCount
2✔
1287
  {-# INLINE packedByteCount #-}
1288
#if WORD_SIZE_IN_BITS == 32
1289
  packM mba v@(VarLen x) = p7 (p7 (p7 (p7 (p7 (errorTooManyBits "Word"))))) (numBits - 7)
1290
    where
1291
      p7 = packIntoCont7 mba x
1292
      {-# INLINE p7 #-}
1293
      numBits = packedVarLenByteCount v * 7
1294
  {-# INLINE packM #-}
1295
  unpackM buf = do
1296
    let d7 = unpack7BitVarLen buf
1297
        {-# INLINE d7 #-}
1298
    VarLen <$> d7 (d7 (d7 (d7 (unpack7BitVarLenLast buf 0b_1111_0000)))) 0 0
1299
  {-# INLINE unpackM #-}
1300
#elif WORD_SIZE_IN_BITS == 64
1301
  packM v@(VarLen x) =
2✔
1302
    p7 (p7 (p7 (p7 (p7 (p7 (p7 (p7 (p7 (p7 (errorTooManyBits "Word")))))))))) (numBits - 7)
1✔
1303
    where
1304
      p7 = packIntoCont7 x
2✔
1305
      {-# INLINE p7 #-}
1306
      numBits = packedVarLenByteCount v * 7
2✔
1307
  {-# INLINE packM #-}
1308
  unpackM = do
2✔
1309
    let d7 = unpack7BitVarLen
2✔
1310
        {-# INLINE d7 #-}
1311
    VarLen <$> d7 (d7 (d7 (d7 (d7 (d7 (d7 (d7 (d7 (unpack7BitVarLenLast 0b_1111_1110))))))))) 0 0
2✔
1312
  {-# INLINE unpackM #-}
1313
#else
1314
#error "Only 32bit and 64bit systems are supported"
1315
#endif
1316

1317
packedVarLenByteCount :: FiniteBits b => VarLen b -> Int
1318
packedVarLenByteCount (VarLen x) =
2✔
1319
  case (finiteBitSize x - countLeadingZeros x) `quotRem` 7 of
1✔
1320
    (0, 0) -> 1
2✔
1321
    (q, 0) -> q
2✔
1322
    (q, _) -> q + 1
2✔
1323
{-# INLINE packedVarLenByteCount #-}
1324

1325
errorTooManyBits :: HasCallStack => String -> a
UNCOV
1326
errorTooManyBits name =
×
1327
  error $ "Bug detected. Trying to pack more bits for " ++ name ++ " than it should be posssible"
×
1328
{-# NOINLINE errorTooManyBits #-}
1329

1330
packIntoCont7 ::
1331
  (Bits t, Integral t) => t -> (Int -> Pack s ()) -> Int -> Pack s ()
1332
packIntoCont7 x cont n
2✔
1333
  | n <= 0 = packM (fromIntegral @_ @Word8 x .&. complement topBit8)
2✔
1334
  | otherwise = do
1✔
1335
      packM (fromIntegral @_ @Word8 (x `shiftR` n) .|. topBit8)
2✔
1336
      cont (n - 7)
2✔
1337
  where
1338
    topBit8 :: Word8
1339
    !topBit8 = 0b_1000_0000
2✔
1340
{-# INLINE packIntoCont7 #-}
1341

1342
-- | Decode a variable length integral value that is encoded with 7 bits of data
1343
-- and the most significant bit (MSB), the 8th bit is set whenever there are
1344
-- more bits following. Continuation style allows us to avoid
1345
-- recursion. Removing loops is good for performance.
1346
unpack7BitVarLen ::
1347
  (Num a, Bits a, Buffer b) =>
1348
  -- | Continuation that will be invoked if MSB is set
1349
  (Word8 -> a -> Unpack b a) ->
1350
  -- | Will be set either to 0 initially or to the very first unmodified byte, which is
1351
  -- guaranteed to have the first bit set.
1352
  Word8 ->
1353
  -- | Accumulator
1354
  a ->
1355
  Unpack b a
1356
unpack7BitVarLen cont firstByte !acc = do
2✔
1357
  b8 :: Word8 <- unpackM
2✔
1358
  if b8 `testBit` 7
2✔
1359
    then
1360
      cont (if firstByte == 0 then b8 else firstByte) (acc `shiftL` 7 .|. fromIntegral (b8 `clearBit` 7))
2✔
1361
    else pure (acc `shiftL` 7 .|. fromIntegral b8)
2✔
1362
{-# INLINE unpack7BitVarLen #-}
1363

1364
unpack7BitVarLenLast ::
1365
  forall t b.
1366
  (Num t, Bits t, MemPack t, Buffer b) =>
1367
  Word8 ->
1368
  Word8 ->
1369
  t ->
1370
  Unpack b t
1371
unpack7BitVarLenLast mask firstByte acc = do
2✔
1372
  res <- unpack7BitVarLen (\_ _ -> F.fail "Too many bytes.") firstByte acc
1✔
1373
  -- Only while decoding the last 7bits we check if there was too many
1374
  -- bits supplied at the beginning.
1375
  unless (firstByte .&. mask == 0b_1000_0000) $ unpack7BitVarLenLastFail (typeName @t) firstByte
1✔
1376
  pure res
2✔
1377
{-# INLINE unpack7BitVarLenLast #-}
1378

1379
unpack7BitVarLenLastFail :: F.MonadFail m => String -> Word8 -> m a
NEW
1380
unpack7BitVarLenLastFail name firstByte =
×
NEW
1381
  F.fail $
×
NEW
1382
    "Unexpected bits for "
×
NEW
1383
      ++ name
×
NEW
1384
      ++ " were set in the first byte of 'VarLen': 0x" <> showHex firstByte ""
×
1385
{-# NOINLINE unpack7BitVarLenLastFail #-}
1386

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

1393
instance Bounded Length where
1394
  minBound = 0
2✔
1395
  maxBound = Length maxBound
2✔
1396

1397
instance Enum Length where
1✔
1398
  toEnum n
2✔
1399
    | n < 0 = error $ "toEnum: Length cannot be negative: " ++ show n
1✔
1400
    | otherwise = Length n
1✔
1401
  fromEnum = unLength
2✔
1402

1403
instance MemPack Length where
2✔
1404
  packedByteCount = packedByteCount . VarLen . fromIntegral @Int @Word . unLength
2✔
1405
  packM (Length n)
2✔
1406
    | n < 0 = packLengthError n
1✔
1407
    | otherwise = packM (VarLen (fromIntegral @Int @Word n))
1✔
1408
  {-# INLINE packM #-}
1409
  unpackM = do
2✔
1410
    VarLen (w :: Word) <- unpackM
2✔
1411
    when (testBit w (finiteBitSize w - 1)) $ upackLengthFail w
1✔
1412
    pure $ Length $ fromIntegral @Word @Int w
2✔
1413
  {-# INLINE unpackM #-}
1414

1415
packLengthError :: Int -> a
NEW
1416
packLengthError n = error $ "Length cannot be negative. Supplied: " ++ show n
×
1417
{-# NOINLINE packLengthError #-}
1418

1419
upackLengthFail :: F.MonadFail m => Word -> m a
1420
upackLengthFail w =
2✔
1421
  F.fail $ "Attempt to unpack negative length was detected: " ++ show (fromIntegral @Word @Int w)
1✔
1422
{-# NOINLINE upackLengthFail #-}
1423

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

1428
-- Manually defined instance, since ghc-8.6 has issues with deriving MemPack
1429
instance MemPack Tag where
2✔
1430
  packedByteCount _ = packedTagByteCount
2✔
1431
  {-# INLINE packedByteCount #-}
1432
  unpackM = unpackTagM
2✔
1433
  {-# INLINE unpackM #-}
1434
  packM = packTagM
2✔
1435
  {-# INLINE packM #-}
1436

1437
packedTagByteCount :: Int
1438
packedTagByteCount = SIZEOF_WORD8
2✔
1439
{-# INLINE packedTagByteCount #-}
1440

1441
unpackTagM :: Buffer b => Unpack b Tag
1442
unpackTagM = Tag <$> unpackM
2✔
1443
{-# INLINE unpackTagM #-}
1444

1445
packTagM :: Tag -> Pack s ()
1446
packTagM = packM . unTag
2✔
1447
{-# INLINE packTagM #-}
1448

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

1452
lift_# :: (State# s -> State# s) -> Pack s ()
1453
lift_# f = Pack $ \_ -> lift $ st_ f
2✔
1454
{-# INLINE lift_# #-}
1455

1456
st_ :: (State# s -> State# s) -> ST s ()
1457
st_ f = ST $ \s# -> (# f s#, () #)
2✔
1458
{-# 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