msgpack-0.1.0: A Haskell binding to MessagePack

Copyright(c) Hideyuki Tanaka, 2009
LicenseBSD3
Maintainertanaka.hideyuki@gmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Data.MessagePack.Base

Contents

Description

Low Level Interface to MessagePack C API

Synopsis

Simple Buffer

newSimpleBuffer :: IO SimpleBuffer Source

Create a new Simple Buffer. It will be deleted automatically.

simpleBufferData :: SimpleBuffer -> IO ByteString Source

Get data of Simple Buffer.

Serializer

newPacker :: SimpleBuffer -> IO Packer Source

Create new Packer. It will be deleted automatically.

packInt :: Integral a => Packer -> a -> IO Int Source

Pack an integral data.

packDouble :: Packer -> Double -> IO Int Source

Pack a double data.

packNil :: Packer -> IO Int Source

Pack a nil.

packBool :: Packer -> Bool -> IO Int Source

Pack a bool data.

packArray :: Packer -> Int -> IO Int Source

packArray p n starts packing an array. Next n data will consist this array.

packMap :: Packer -> Int -> IO Int Source

packMap p n starts packing a map. Next n pairs of data (2*n data) will consist this map.

packRAW :: Packer -> Int -> IO Int Source

packRAW p n starts packing a byte sequence. Next total n bytes of packRAWBody call will consist this sequence.

packRAWBody :: Packer -> ByteString -> IO Int Source

Pack a byte sequence.

packRAW' :: Packer -> ByteString -> IO Int Source

Pack a single byte stream. It calls packRAW and packRAWBody.

Stream Deserializer

newUnpacker :: Int -> IO Unpacker Source

newUnpacker initialBufferSize creates a new Unpacker. It will be deleted automatically.

unpackerReserveBuffer :: Unpacker -> Int -> IO Bool Source

unpackerReserveBuffer up size reserves at least size bytes of buffer.

unpackerBuffer :: Unpacker -> IO (Ptr CChar) Source

Get a pointer of unpacker buffer.

unpackerBufferCapacity :: Unpacker -> IO Int Source

Get size of allocated buffer.

unpackerBufferConsumed :: Unpacker -> Int -> IO () Source

unpackerBufferConsumed up size notices that writed size bytes to buffer.

unpackerFeed :: Unpacker -> ByteString -> IO () Source

Write byte sequence to Unpacker. It is utility funciton, calls unpackerReserveBuffer, unpackerBuffer and unpackerBufferConsumed.

unpackerExecute :: Unpacker -> IO Int Source

Execute deserializing. It returns 0 when buffer contains not enough bytes, returns 1 when succeeded, returns negative value when it failed.

unpackerData :: Unpacker -> IO Object Source

Returns a deserialized object when unpackerExecute returned 1.

unpackerReleaseZone :: Unpacker -> IO Zone Source

Release memory zone. The returned zone must be freed by calling freeZone.

unpackerResetZone :: Unpacker -> IO () Source

Free memory zone used by Unapcker.

unpackerReset :: Unpacker -> IO () Source

Reset Unpacker state except memory zone.

unpackerMessageSize :: Unpacker -> IO Int Source

Returns number of bytes of sequence of deserializing object.

MessagePack Object

data Object Source

Object Representation of MessagePack data.

Instances

packObject :: Packer -> Object -> IO () Source

Pack a Object.

data UnpackReturn Source

Constructors

UnpackContinue

not enough bytes to unpack object

UnpackParseError

got invalid bytes

UnpackError

other error

unpackObject :: Zone -> ByteString -> IO (Either UnpackReturn (Int, Object)) Source

Unpack a single MessagePack object from byte sequence.

Memory Zone

type Zone = Ptr () Source

newZone :: IO Zone Source

Create a new memory zone. It must be freed manually.

freeZone :: Zone -> IO () Source

Free a memory zone.

withZone :: (Zone -> IO a) -> IO a Source

Create a memory zone, then execute argument, then free memory zone.