haskus-binary-1.3: Haskus binary format manipulation

Safe HaskellNone
LanguageHaskell2010

Haskus.Format.Binary.Serialize

Contents

Description

Binary serialization of Haskell values

Synopsis

Documentation

class Monad m => PutMonad m where Source #

Monad which can build a sequence of bytes

Minimal complete definition

putWord8, putWord16, putWord32, putWord64, putBuffer

Methods

putWord8 :: Word8 -> m () Source #

Write a Word8

putWord16 :: Word16 -> m () Source #

Write a Word16

putWord32 :: Word32 -> m () Source #

Write a Word32

putWord64 :: Word64 -> m () Source #

Write a Word64

putWord8s :: [Word8] -> m () Source #

Write some Word8

putWord16s :: [Word16] -> m () Source #

Write some Word16

putWord32s :: [Word32] -> m () Source #

Write some Word32

putWord64s :: [Word64] -> m () Source #

Write some Word64

putBuffer :: Buffer mut pin gc heap -> m () Source #

Write the contents of a buffer

preAllocateAtLeast :: Word -> m () Source #

Pre-allocate at least the given amount of bytes

This is a hint for the putter to speed up the allocation of memory

Instances
(MonadIO m, MonadFail m) => PutMonad (BufferPutT (Buffer Mutable pin gc heap) m) Source # 
Instance details

Defined in Haskus.Format.Binary.Serialize.Buffer

Methods

putWord8 :: Word8 -> BufferPutT (Buffer Mutable pin gc heap) m () Source #

putWord16 :: Word16 -> BufferPutT (Buffer Mutable pin gc heap) m () Source #

putWord32 :: Word32 -> BufferPutT (Buffer Mutable pin gc heap) m () Source #

putWord64 :: Word64 -> BufferPutT (Buffer Mutable pin gc heap) m () Source #

putWord8s :: [Word8] -> BufferPutT (Buffer Mutable pin gc heap) m () Source #

putWord16s :: [Word16] -> BufferPutT (Buffer Mutable pin gc heap) m () Source #

putWord32s :: [Word32] -> BufferPutT (Buffer Mutable pin gc heap) m () Source #

putWord64s :: [Word64] -> BufferPutT (Buffer Mutable pin gc heap) m () Source #

putBuffer :: Buffer mut pin0 gc0 heap0 -> BufferPutT (Buffer Mutable pin gc heap) m () Source #

preAllocateAtLeast :: Word -> BufferPutT (Buffer Mutable pin gc heap) m () Source #

class Monad m => GetMonad m where Source #

Monad which can read a sequence of bytes

Minimal complete definition

getWord8, getWord16, getWord32, getWord64, getBufferInto

Methods

getWord8 :: m Word8 Source #

Read a Word8

getWord16 :: m Word16 Source #

Read a Word16 with host endianness

getWord32 :: m Word32 Source #

Read a Word32 with host endianness

getWord64 :: m Word64 Source #

Read a Word64 with host endianness

getWord8s :: Word -> m [Word8] Source #

Read some Word8

getWord16s :: Word -> m [Word16] Source #

Read some Word16 with host endianness

getWord32s :: Word -> m [Word32] Source #

Read some Word32 with host endianness

getWord64s :: Word -> m [Word64] Source #

Read some Word64 with host endianness

getBuffer :: Word -> m BufferI Source #

Read the given amount of bytes into a new buffer

getBufferInto :: Word -> Buffer Mutable pin gc heap -> m () Source #

Read the given amount of bytes into the specified buffer

class Serializable a where Source #

Binary serializable data

Associated Types

type SizeOf a :: Size Source #

Size of the data in bytes

type Endian a :: Bool Source #

Sensible to endianness

Methods

sizeOf :: a -> Word Source #

Dynamic size of the data in bytes

put :: PutMonad m => Endianness -> a -> m () Source #

Serialize a value

get :: GetMonad m => Endianness -> Word -> m a Source #

Deserialize a value

Instances
Serializable Int8 Source # 
Instance details

Defined in Haskus.Format.Binary.Serialize

Associated Types

type SizeOf Int8 :: Size Source #

type Endian Int8 :: Bool Source #

Methods

sizeOf :: Int8 -> Word Source #

put :: PutMonad m => Endianness -> Int8 -> m () Source #

get :: GetMonad m => Endianness -> Word -> m Int8 Source #

Serializable Int16 Source # 
Instance details

Defined in Haskus.Format.Binary.Serialize

Associated Types

type SizeOf Int16 :: Size Source #

type Endian Int16 :: Bool Source #

Methods

sizeOf :: Int16 -> Word Source #

put :: PutMonad m => Endianness -> Int16 -> m () Source #

get :: GetMonad m => Endianness -> Word -> m Int16 Source #

Serializable Int32 Source # 
Instance details

Defined in Haskus.Format.Binary.Serialize

Associated Types

type SizeOf Int32 :: Size Source #

type Endian Int32 :: Bool Source #

Methods

sizeOf :: Int32 -> Word Source #

put :: PutMonad m => Endianness -> Int32 -> m () Source #

get :: GetMonad m => Endianness -> Word -> m Int32 Source #

Serializable Int64 Source # 
Instance details

Defined in Haskus.Format.Binary.Serialize

Associated Types

type SizeOf Int64 :: Size Source #

type Endian Int64 :: Bool Source #

Methods

sizeOf :: Int64 -> Word Source #

put :: PutMonad m => Endianness -> Int64 -> m () Source #

get :: GetMonad m => Endianness -> Word -> m Int64 Source #

Serializable Word8 Source # 
Instance details

Defined in Haskus.Format.Binary.Serialize

Associated Types

type SizeOf Word8 :: Size Source #

type Endian Word8 :: Bool Source #

Methods

sizeOf :: Word8 -> Word Source #

put :: PutMonad m => Endianness -> Word8 -> m () Source #

get :: GetMonad m => Endianness -> Word -> m Word8 Source #

Serializable Word16 Source # 
Instance details

Defined in Haskus.Format.Binary.Serialize

Associated Types

type SizeOf Word16 :: Size Source #

type Endian Word16 :: Bool Source #

Serializable Word32 Source # 
Instance details

Defined in Haskus.Format.Binary.Serialize

Associated Types

type SizeOf Word32 :: Size Source #

type Endian Word32 :: Bool Source #

Serializable Word64 Source # 
Instance details

Defined in Haskus.Format.Binary.Serialize

Associated Types

type SizeOf Word64 :: Size Source #

type Endian Word64 :: Bool Source #

Serializable BufferI Source # 
Instance details

Defined in Haskus.Format.Binary.Serialize

Associated Types

type SizeOf BufferI :: Size Source #

type Endian BufferI :: Bool Source #

Serializable a => Serializable (AsLittleEndian a) Source # 
Instance details

Defined in Haskus.Format.Binary.Serialize

Associated Types

type SizeOf (AsLittleEndian a) :: Size Source #

type Endian (AsLittleEndian a) :: Bool Source #

Serializable a => Serializable (AsBigEndian a) Source # 
Instance details

Defined in Haskus.Format.Binary.Serialize

Associated Types

type SizeOf (AsBigEndian a) :: Size Source #

type Endian (AsBigEndian a) :: Bool Source #

data Size Source #

Size in bytes

Constructors

Exactly Nat

Exactly the given size

AtLeast Nat

At least the given size

Dynamic

Dynamically known size

Endianness helpers

putWord16BE :: PutMonad m => Word16 -> m () Source #

Write a Word16 with big-endian order

putWord32BE :: PutMonad m => Word32 -> m () Source #

Write a Word32 with big-endian order

putWord64BE :: PutMonad m => Word64 -> m () Source #

Write a Word64 with big-endian order

putWord16LE :: PutMonad m => Word16 -> m () Source #

Write a Word16 with little-endian order

putWord32LE :: PutMonad m => Word32 -> m () Source #

Write a Word32 with little-endian order

putWord64LE :: PutMonad m => Word64 -> m () Source #

Write a Word64 with little-endian order

putWord16BEs :: PutMonad m => [Word16] -> m () Source #

Write some Word16 with big-endian order

putWord32BEs :: PutMonad m => [Word32] -> m () Source #

Write some Word32 with big-endian order

putWord64BEs :: PutMonad m => [Word64] -> m () Source #

Write some Word64 with big-endian order

putWord16LEs :: PutMonad m => [Word16] -> m () Source #

Write some Word16 with little-endian order

putWord32LEs :: PutMonad m => [Word32] -> m () Source #

Write some Word32 with little-endian order

putWord64LEs :: PutMonad m => [Word64] -> m () Source #

Write some Word64 with little-endian order

getWord16BE :: GetMonad m => m Word16 Source #

Read a Word16 with big-endian order

getWord32BE :: GetMonad m => m Word32 Source #

Read a Word32 with big-endian order

getWord64BE :: GetMonad m => m Word64 Source #

Read a Word64 with big-endian order

getWord16LE :: GetMonad m => m Word16 Source #

Read a Word16 with little-endian order

getWord32LE :: GetMonad m => m Word32 Source #

Read a Word32 with little-endian order

getWord64LE :: GetMonad m => m Word64 Source #

Read a Word64 with little-endian order

getWord16BEs :: GetMonad m => Word -> m [Word16] Source #

Read some Word16 with big-endian order

getWord32BEs :: GetMonad m => Word -> m [Word32] Source #

Read some Word32 with big-endian order

getWord64BEs :: GetMonad m => Word -> m [Word64] Source #

Read some Word64 with big-endian order

getWord16LEs :: GetMonad m => Word -> m [Word16] Source #

Read some Word16 with little-endian order

getWord32LEs :: GetMonad m => Word -> m [Word32] Source #

Read some Word32 with little-endian order

getWord64LEs :: GetMonad m => Word -> m [Word64] Source #

Read some Word64 with little-endian order