repa-convert-4.1.0.1: Packing and unpacking binary data.

Safe HaskellNone
LanguageHaskell98

Data.Repa.Convert.Format

Contents

Description

Convert Haskell values to and from a compact binary representation.

For testing purposes, use packToList which takes a format, a record, and returns a list of bytes.

> import Data.Repa.Convert.Format

> let Just bytes = packToList (FixString ASCII 10 :*: Word16be :*: Float64be) ("foo" :*: 66 :*: 93.42)
> bytes
[102,111,111,0,0,0,0,0,0,0,0,66,64,87,90,225,71,174,20,123]

We can then unpack the raw bytes back to Haskell values with unpackFromList.

> unpackFromList (FixString ASCII 10 :*: Word16be :*: Float64be) bytes 
Just ("foo" :*: (66 :*: 93.42))

In production code use pack and unpack to work directly with a buffer in foreign memory.

Synopsis

Data formats

class Format f where Source

Relates a storage format to the Haskell type of the value that is stored in that format.

Associated Types

type Value f Source

Get the type of a value with this format.

Methods

fixedSize :: f -> Maybe Int Source

For fixed size storage formats, yield their size (length) in bytes.

Yields Nothing if this is not a fixed size format.

packedSize :: f -> Value f -> Maybe Int Source

Yield the size of a value in the given format.

Yields Nothing when a collection of values is to be packed into a fixed length format, but the size of the collection does not match the format.

Packing records

class Format format => Packable format where Source

Class of storage formats that can have values packed and unpacked from foreign bufferes.

The methods are written using continuations to make it easier for GHC to optimise its core code when packing/unpacking many fields.

Methods

pack Source

Arguments

:: Ptr Word8

Target Buffer.

-> format

Storage format.

-> Value format

Value to pack.

-> (Int -> IO (Maybe a))

Continue, given the number of bytes written.

-> IO (Maybe a) 

Pack a value into a buffer using the given format.

If the format contains fixed width fields and the corresponding value has too many elements, then this function returns False, otherwise True.

unpack Source

Arguments

:: Ptr Word8

Source buffer.

-> format

Format of buffer.

-> ((Value format, Int) -> IO (Maybe a))

Continue, given the unpacked value and the number of bytes read.

-> IO (Maybe a) 

Unpack a value from a buffer using the given format.

This is the inverse of pack above.

packToList :: Packable format => format -> Value format -> Maybe [Word8] Source

Pack a value into a list of Word8.

unpackFromList :: Packable format => format -> [Word8] -> Maybe (Value format) Source

Unpack a value from a list of Word8.

Constraints

forFormat :: format -> Value format -> Value format Source

Constrain the type of a value to match the given format.

The value itself is not used.

listFormat :: format -> [Value format] -> [Value format] Source

Constrain the type of some values to match the given format.

The value itself is not used.

Products

data a :*: b infixr 9 Source

Strict product type, written infix.

Constructors

!a :*: !b infixr 9 

Instances

(Unbox a, Unbox b) => Vector Vector ((:*:) a b) 
(Unbox a, Unbox b) => MVector MVector ((:*:) a b) 
(Eq a, Eq b) => Eq ((:*:) a b) 
(Show a, Show b) => Show ((:*:) a b) 
(Unbox a, Unbox b) => Unbox ((:*:) a b) 
(Packable fa, Packable fb) => Packable ((:*:) fa fb) 
(Format a, Format b) => Format ((:*:) a b) 
data MVector s ((:*:) a b) = MV_Prod !Int !(MVector s a) !(MVector s b) 
data Vector ((:*:) a b) = V_Prod !Int !(Vector a) !(Vector b) 
type Value ((:*:) a b) = (:*:) (Value a) (Value b) 

Lists

data FixList f Source

Fixed length list.

Constructors

FixList f Int 

Instances

Eq f => Eq (FixList f) 
Show f => Show (FixList f) 
Format f => Format (FixList f) 
type Value (FixList f) = [Value f] 

data VarList f Source

Variable length list.

Constructors

VarList f 

Instances

Eq f => Eq (VarList f) 
Show f => Show (VarList f) 
Format f => Format (VarList f) 
type Value (VarList f) = [Value f] 

Strings

data FixString t Source

Fixed length string.

  • When packing, if the provided string is shorter than the fixed length then the extra bytes are zero-filled.

Constructors

FixString t Int 

data VarString t Source

Variable length string.

Constructors

VarString t 

data ASCII Source

String is encoded as 8-bit ASCII characters.

Constructors

ASCII 

Atomic values

8-bit

data Word8be Source

Big-endian 8-bit unsigned word.

Constructors

Word8be 

data Int8be Source

Big-endian 8-bit signed integer.

Constructors

Int8be 

16-bit

data Word16be Source

Big-endian 32-bit unsigned word.

Constructors

Word16be 

32-bit

data Word32be Source

Big-endian 32-bit unsigned word.

Constructors

Word32be 

data Int32be Source

Big-endian 32-bit signed integer.

Constructors

Int32be 

data Float32be Source

Big-endian 32-bit IEEE 754 float.

Constructors

Float32be 

64-bit

data Word64be Source

Big-endian 64-bit unsigned word.

Constructors

Word64be 

data Int64be Source

Big-endian 64-bit signed integer.

Constructors

Int64be 

data Float64be Source

Big-endian 64-bit IEEE 754 float.

Constructors

Float64be