graph-serialize-0.1: Serialization of data structures with references.

Data.Serialize.References

Contents

Description

This module provides a way to serialize graph-like structures into lazy ByteStrings. Graph-like structures here are structures that may reference other locations in the resulting output. The references are serialized as relative byte offsets.

A simple example:

test1 :: [Word8]
test1 =
  L.unpack $ toLazyByteString id $ do
    r <- newRegion
    l1 <- label r
    emit r (42 :: Word32)
    reference S4 LE r l1
    emit r (43 :: Word32)

test1 == [42,0,0,0,252,255,255,255,43,0,0,0]

Synopsis

Monad and ByteString construction

data BuildM a Source

Monad for constructing the serialised structure.

toLazyByteStringSource

Arguments

:: ([Region] -> [Region])

Determines the ordering of the regions. If you pass id regions will occur in creation order.

-> BuildM () 
-> ByteString 

Serialise the graph into a lazy ByteString.

Regions

data Region Source

A logical section of the data stream.

Instances

newRegion :: BuildM RegionSource

Create a new region.

Emitting Data, Labels, References

data Label Source

A location in the data stream.

Instances

label :: Region -> BuildM LabelSource

Emit a label at the current location in the given region.

makeLabel :: BuildM LabelSource

Create a new label (with no location attached to it).

It is up to the user to ensure that if this label is ever used in a reference, then the label must have been placed via placeLabel.

This is intended for forward references within a region:

 example r = do
  l <- makeLabel
  reference S4 Host r l
  ... more stuff ...
  placeLabel r l
  ... other stuff ...

placeLabel :: Region -> Label -> BuildM ()Source

Place a label previously created with makeLabel.

This function must only be called once per label. If the same label is placed multiple times, it is undefined where references to it point to.

referenceSource

Arguments

:: Size

The size of the reference in bytes.

-> ByteOrder

Byte order used for encoding the reference.

-> Region

The region in which the reference will be emitted.

-> Label

The target label.

-> BuildM () 

Emit a reference to the given label in the current region.

The reference will be encoded as a signed integer that specifies the relative distance (in bytes) from the current location to the target label.

The current location starts before the reference. A serialised reference with value 0 therefore refers to itself.

It is up to the user to ensure that references are large enough to encode the required range. If they are not in range toLazyByteString will fail.

data Size Source

The size of a reference (1, 2, 4, or 8 bytes).

Instances

sizeToBytes :: Size -> IntSource

Translate Size into matching number of bytes.

data ByteOrder Source

The byte ordering to be used when serializing a reference.

Emitting Words

emitWord8 :: Region -> Word8 -> BuildM ()Source

Emit a single byte.

emitWord8s :: Region -> [Word8] -> BuildM ()Source

Emit a list of bytes.

emitWord16le :: Region -> Word16 -> BuildM ()Source

Emit a Word16 in little endian format.

emitWord16be :: Region -> Word16 -> BuildM ()Source

Emit a Word16 in big endian format.

emitWord16host :: Region -> Word16 -> BuildM ()Source

Emit a Word16 in native host order and host endianness.

emitWord32le :: Region -> Word32 -> BuildM ()Source

Emit a Word32 in little endian format.

emitWord32be :: Region -> Word32 -> BuildM ()Source

Emit a Word32 in big endian format.

emitWord32host :: Region -> Word32 -> BuildM ()Source

Emit a Word32 in native host order and host endianness.

emitWord64le :: Region -> Word64 -> BuildM ()Source

Emit a Word64 in little endian format.

emitWord64be :: Region -> Word64 -> BuildM ()Source

Emit a Word64 in big endian format.

emitWord64host :: Region -> Word64 -> BuildM ()Source

Emit a Word64 in native host order and host endianness.

Emitting Ints

emitInt8 :: Region -> Int8 -> BuildM ()Source

Emit a single byte.

emitInt8s :: Region -> [Int8] -> BuildM ()Source

Emit a list of bytes.

emitInt16le :: Region -> Int16 -> BuildM ()Source

Emit a Int16 in little endian format.

emitInt16be :: Region -> Int16 -> BuildM ()Source

Emit a Int16 in big endian format.

emitInt16host :: Region -> Int16 -> BuildM ()Source

Emit a Int16 in native host order and host endianness.

emitInt32le :: Region -> Int32 -> BuildM ()Source

Emit a Int32 in little endian format.

emitInt32be :: Region -> Int32 -> BuildM ()Source

Emit a Int32 in big endian format.

emitInt32host :: Region -> Int32 -> BuildM ()Source

Emit a Int32 in native host order and host endianness.

emitInt64le :: Region -> Int64 -> BuildM ()Source

Emit a Int64 in little endian format.

emitInt64be :: Region -> Int64 -> BuildM ()Source

Emit a Int64 in big endian format.

emitInt64host :: Region -> Int64 -> BuildM ()Source

Emit a Int64 in native host order and host endianness.

Storables

emitStorable :: Storable a => Region -> a -> BuildM ()Source

Emit an instance of Storable. Does not take into account alignment.

emitStorableList :: Storable a => Region -> [a] -> BuildM ()Source

Emit a list of Storable instances. Ignores alignment.

Alignment

padToSource

Arguments

:: Region 
-> Int

Intended alignment

-> Word8

Fill with these bytes.

-> BuildM () 

Insert padding bytes into given region until its size is a multiple of the expected alignment.

alignedLabel :: Region -> Int -> BuildM LabelSource

Emit an aligned label at the current location in the region.

The label's address relative to the region start will be at a multiple of the given alignment