pack-0.4.0: Bidirectional fast ByteString packer/unpacker

LicenseBSD-style
Maintainercapsjac <capsjac at gmail dot com>
StabilityExperimental
PortabilityGHC, Unknown
Safe HaskellNone
LanguageHaskell2010

Data.Pack

Contents

Description

The pack package provides bidirectional packing and unpacking (aka. (de)serialise) Haskell values to and from strict ByteStrings. Both operations are faster than binary and cereal package so that it can be used in performance sensible operations. Bytestring allocation is batched and done before packing any values to avoid performance loss. The pack package does not provide specific typeclasses (it's a good idea, though) to clear out ambiguity of serialisation format.

  • Migration Sheet from binary, cereal and packer
encode, runPacking
packing (packer).
decode, runUnpacking
unpacking (packer).
getWord8, putWord8
i8 (put value) and u8 (put value).
getWord*, putWord*
{i,u}{8,16,32,64}{,b,host} (put value).
skip
unused, or pad.
isEmpty, bytesRead
isFull and getPosition.
getByteString
bytes.
getLazyByteStringNul
cstring.
getWordhost
uptrsize and iptrsize.
  • Example
pactest = do
  putStrLn . show $ packing i8 100
  let i8i8i8 ~(v,w,x) = do -- `~` is important!
        a <- i8 v
        b <- i8 w
        c <- i8 x
        return (a,b,c)
      {-# INLINE i8i8i8 #-} -- For efficiency
  putStrLn . show $ packing i8i8i8 (-90,-80,100)
  putStrLn . show $ unpacking i8i8i8 $ packing i8i8i8 (-90,-80,100)
  • Output
"d"
"\166\176d"
Right (-90,-80,100)

Synopsis

Main

packing :: (a -> Packet e a) -> a -> ByteString Source

Pack with a monadic action (Packer a) and return the ByteString.

unpacking :: (a -> Packet e a) -> ByteString -> Either e a Source

Unpack a ByteString using a Packer.

packet :: Packer a -> Prism' ByteString a Source

Prism from lens package.

pactest :: IO () Source

Readme.

type Packer a = a -> Packet String a Source

A Packer recieves one value to pack and returns one Packet which is used to unpack the value of same type.

data Packet e a Source

Bidirectional packing/unpacking Monad.

Instances

Fixed sized

i16 :: Packer Int16 Source

A Int16 Packet serialized in little endian.

i32 :: Packer Int32 Source

A Int32 Packet serialized in little endian.

i64 :: Packer Int64 Source

A Int64 Packet serialized in little endian.

u16 :: Packer Word16 Source

A Word16 Packet serialized in little endian.

u32 :: Packer Word32 Source

A Word32 Packet serialized in little endian.

u64 :: Packer Word64 Source

A Word64 Packet serialized in little endian.

i16b :: Packer Int16 Source

A Int16 Packet serialized in big endian.

i32b :: Packer Int32 Source

A Int32 Packet serialized in big endian.

i64b :: Packer Int64 Source

A Int64 Packet serialized in big endian.

u16b :: Packer Word16 Source

A Word16 Packet serialized in big endian.

u32b :: Packer Word32 Source

A Word32 Packet serialized in big endian.

u64b :: Packer Word64 Source

A Word64 Packet serialized in big endian.

i16host :: Packer Int16 Source

A Int16 Packet in the host endianness.

i32host :: Packer Int32 Source

A Int32 Packet in the host endianness.

i64host :: Packer Int64 Source

A Int64 Packet in the host endianness.

iptrsize :: Packer Word Source

A host pointer-sized Int Packet in the host endianness.

u16host :: Packer Word16 Source

A Word16 Packet in the host endianness.

u32host :: Packer Word32 Source

A Word32 Packet in the host endianness.

u64host :: Packer Word64 Source

A Word64 Packet in the host endianness.

uptrsize :: Packer Word Source

A host pointer-sized Word Packet in the host endianness.

f32 :: Packer Float Source

A IEEE754-Float Packet serialized in little endian.

f64 :: Packer Double Source

A IEEE754-Double Packet serialized in little endian.

f32b :: Packer Float Source

A IEEE754-Float Packet serialized in big endian.

f64b :: Packer Double Source

A IEEE754-Double Packet serialized in big endian.

f32host :: Packer Float Source

A IEEE754-Float Packet in the host endianness.

f64host :: Packer Double Source

A IEEE754-Double Packet in the host endianness.

Bytes

bytes :: Int -> Packer ByteString Source

Slice a number of bytes from the source ByteString. The original block of memory is expected to live for the life of this ByteString.

bytesCopy :: Int -> Packer ByteString Source

Copy a number of bytes from the source ByteString. Similar to bytes but this allow the original block of memory to go away.

bytesWhile :: (Word8 -> Bool) -> Packer ByteString Source

bytesWhile, applied to a predicate p, returns the longest prefix (possibly empty) of bytes that satisfy p.

bytesUntil :: Word8 -> Packer ByteString Source

bytesUntil slices remaining ByteString at the first occurence of the specified byte. It is more efficient than bytesWhile as it is implemented with memchr(3).

cstring :: Packer ByteString Source

Variable-length NUL terminated string.

varchar :: Int -> Packer ByteString Source

Fixed-length (possibly) NUL terminated string field. Longer string will be trimmed and shorter one will be padded out with NUL.

signature :: ByteString -> Packet String (Maybe ByteString) Source

Constant block of packet. Similar to unused but specified ByteString will be used to fill out rather than NUL bytes. Additionally, read content is compared to the value and mismatch is reported.

remainingBytes :: Packer ByteString Source

Slice the remaining bytes.

remainingBytesCopy :: Packer ByteString Source

Similar to remainingBytes but copy the remaining bytes.

Structures

vector :: Vector v a => Packer a -> Int -> Packer (v a) Source

A Data.Vector.Generic Packet. Get and put an array of arbitary type of Packets.

array :: Storable a => Int -> Packer (Vector a) Source

A Data.Vector.Storable Packet. Read operation is copy-free.

arrayCopy :: Storable a => Int -> Packer (Vector a) Source

Similar to array but copy the bytes.

storable :: Storable a => Packer a Source

A Storable Packet. Note that Storable must not be used to store variable sized structures.

enumOf :: (Integral a, Enum b) => Packer a -> Packer b Source

Represent a simple enum field.

dimapP :: (b -> a) -> (a -> b) -> (a -> Packet e a) -> b -> Packet e b Source

Derived from lens package. Bidirectional mapping.

dicase :: Packet e a -> Packet e' a -> Packet e a Source

A dirty hack to handle unions.

tag <- i32 (getTagId dat)
let getcase tag = case tag of
  0 -> A <$> i32 undefined
  1 -> B <$> f32 undefined
let putcase dat = case dat of
  A i -> i32 i
  B f -> f32 f
val <- dicase (getcase tag) (putcase data)

Spaces

unused :: Int -> Packet String () Source

Skip bytes, filling with NUL bytes.

pad :: Word8 -> Int -> Packet String () Source

Skip bytes, filling with specified byte.

alignedTo :: Int -> Packet String () Source

(Unpacker only) Adjust alignment, filling with NUL bytes.

alignedWith :: Word8 -> Int -> Packet String () Source

(Unpacker only) Adjust alignment, filling with specified byte.

Information

getPosition :: Packet e Int Source

(Unpacker only) Get the position in the memory block.

getTotalSize :: Packet e Int Source

(Unpacker only) Get the total size of the memory block.

getRemaining :: Packet e Int Source

(Unpacker only) Get a number of bytes to go in the memory block.

isFull :: Packet e Bool Source

(Unpacker only) Return True if source ByteString is fully consumed or target ByteString is full.