bond-haskell-0.1.5.0: Runtime support for BOND serialization

Safe HaskellNone
LanguageHaskell2010

Data.Bond

Contents

Description

Bond is an extensible framework for working with schematized data. It is suitable for scenarios ranging from service communications to Big Data storage and processing.

Bond defines a rich type system and schema versioning rules which allow forward and backward compatibility.

Core bond library is published on GitHub at https://github.com/Microsoft/bond/.

Synopsis

Example

Let's use following schema.bond IDL file:

namespace my.test

struct my_struct {
  10: int32 m_int;
  20: string m_str = "some string";
}

Code generation requires hbc program from bond-haskell-compiler package:

hbc schema.bond

This creates file My.Test.My_struct.hs. Note that case conversions are performed to create syntactically correct Haskell code.

-- create structure and set m_int to 5:
let struct = defaultValue { m_int = 5 }
-- serialize struct with FastBinary protocol
let Right binstream = bondWrite FastBinaryProto struct
-- parse binstream using runtime schema
let Right rtstruct = bondReadWithSchema FastBinaryProto (getSchema (Proxy :: Proxy My_struct)) binstream

class BondProto t where Source #

Typeclass for Bond serialization protocols.

Methods

bondRead :: BondStruct a => t -> ByteString -> Either String a Source #

Deserialize structure from stream.

bondWrite :: BondStruct a => t -> a -> Either String ByteString Source #

Serialize structure to stream.

bondReadWithSchema :: t -> StructSchema -> ByteString -> Either String Struct Source #

Deserialize structure from stream using provided schema.

bondWriteWithSchema :: t -> StructSchema -> Struct -> Either String ByteString Source #

Serialize structure to stream using provided schema.

bondMarshal :: BondStruct a => t -> a -> Either String ByteString Source #

Serialize structure to stream and add protocol header. See bondUnmarshal for deserialization.

bondMarshalWithSchema :: t -> StructSchema -> Struct -> Either String ByteString Source #

Serialize structure to stream using provided schema and add protocol header. See bondUnmarshalWithSchema for deserialization.

protoSig :: t -> ByteString Source #

Get protocol header.

Instances

BondProto CompactBinaryV1Proto Source # 
BondProto CompactBinaryProto Source # 
BondProto FastBinaryProto Source # 
BondProto JsonProto Source # 
BondProto SimpleBinaryV1Proto Source # 
BondProto SimpleBinaryProto Source # 

class BondProto t => BondTaggedProto t where Source #

Typeclass for tagged Bond serialization protocols. Such protocols support schemaless operations.

Minimal complete definition

bondReadTagged, bondWriteTagged

Methods

bondReadTagged :: t -> ByteString -> Either String Struct Source #

Deserialize structure from stream without schema.

bondWriteTagged :: t -> Struct -> Either String ByteString Source #

Serialize structure to stream without schema.

bondMarshalTagged :: t -> Struct -> Either String ByteString Source #

Serialize structure to stream without schema and add protocol header. See bondUnmarshalTagged for deserialization.

Supported protocols

data CompactBinaryV1Proto Source #

A binary, tagged protocol using variable integer encoding and compact field header.

Constructors

CompactBinaryV1Proto 

Instances

Protocol CompactBinaryV1Proto Source # 

Associated Types

type ReaderM CompactBinaryV1Proto :: * -> * Source #

type WriterM CompactBinaryV1Proto :: * -> * Source #

Methods

bondPutStruct :: BondStruct a => a -> BondPut CompactBinaryV1Proto Source #

bondPutBaseStruct :: BondStruct a => a -> BondPut CompactBinaryV1Proto Source #

bondGetStruct :: BondStruct a => BondGet CompactBinaryV1Proto a Source #

bondGetBaseStruct :: BondStruct a => BondGet CompactBinaryV1Proto a Source #

bondPutField :: (BondType a, BondStruct b) => Proxy * b -> Ordinal -> a -> BondPut CompactBinaryV1Proto Source #

bondPutDefNothingField :: (BondType a, BondStruct b) => Proxy * b -> Ordinal -> Maybe a -> BondPut CompactBinaryV1Proto Source #

bondPutBool :: Bool -> BondPut CompactBinaryV1Proto Source #

bondPutUInt8 :: Word8 -> BondPut CompactBinaryV1Proto Source #

bondPutUInt16 :: Word16 -> BondPut CompactBinaryV1Proto Source #

bondPutUInt32 :: Word32 -> BondPut CompactBinaryV1Proto Source #

bondPutUInt64 :: Word64 -> BondPut CompactBinaryV1Proto Source #

bondPutInt8 :: Int8 -> BondPut CompactBinaryV1Proto Source #

bondPutInt16 :: Int16 -> BondPut CompactBinaryV1Proto Source #

bondPutInt32 :: Int32 -> BondPut CompactBinaryV1Proto Source #

bondPutInt64 :: Int64 -> BondPut CompactBinaryV1Proto Source #

bondPutFloat :: Float -> BondPut CompactBinaryV1Proto Source #

bondPutDouble :: Double -> BondPut CompactBinaryV1Proto Source #

bondPutString :: Utf8 -> BondPut CompactBinaryV1Proto Source #

bondPutWString :: Utf16 -> BondPut CompactBinaryV1Proto Source #

bondPutBlob :: Blob -> BondPut CompactBinaryV1Proto Source #

bondPutList :: BondType a => [a] -> BondPut CompactBinaryV1Proto Source #

bondPutVector :: BondType a => Vector a -> BondPut CompactBinaryV1Proto Source #

bondPutHashSet :: BondType a => HashSet a -> BondPut CompactBinaryV1Proto Source #

bondPutSet :: BondType a => Set a -> BondPut CompactBinaryV1Proto Source #

bondPutMap :: (BondType k, BondType v) => Map k v -> BondPut CompactBinaryV1Proto Source #

bondPutNullable :: BondType a => Maybe a -> BondPut CompactBinaryV1Proto Source #

bondPutBonded :: BondStruct a => Bonded a -> BondPut CompactBinaryV1Proto Source #

bondGetBool :: BondGet CompactBinaryV1Proto Bool Source #

bondGetUInt8 :: BondGet CompactBinaryV1Proto Word8 Source #

bondGetUInt16 :: BondGet CompactBinaryV1Proto Word16 Source #

bondGetUInt32 :: BondGet CompactBinaryV1Proto Word32 Source #

bondGetUInt64 :: BondGet CompactBinaryV1Proto Word64 Source #

bondGetInt8 :: BondGet CompactBinaryV1Proto Int8 Source #

bondGetInt16 :: BondGet CompactBinaryV1Proto Int16 Source #

bondGetInt32 :: BondGet CompactBinaryV1Proto Int32 Source #

bondGetInt64 :: BondGet CompactBinaryV1Proto Int64 Source #

bondGetFloat :: BondGet CompactBinaryV1Proto Float Source #

bondGetDouble :: BondGet CompactBinaryV1Proto Double Source #

bondGetString :: BondGet CompactBinaryV1Proto Utf8 Source #

bondGetWString :: BondGet CompactBinaryV1Proto Utf16 Source #

bondGetBlob :: BondGet CompactBinaryV1Proto Blob Source #

bondGetList :: BondType a => BondGet CompactBinaryV1Proto [a] Source #

bondGetVector :: BondType a => BondGet CompactBinaryV1Proto (Vector a) Source #

bondGetHashSet :: (Eq a, Hashable a, BondType a) => BondGet CompactBinaryV1Proto (HashSet a) Source #

bondGetSet :: (Ord a, BondType a) => BondGet CompactBinaryV1Proto (Set a) Source #

bondGetMap :: (Ord k, BondType k, BondType v) => BondGet CompactBinaryV1Proto (Map k v) Source #

bondGetNullable :: BondType a => BondGet CompactBinaryV1Proto (Maybe a) Source #

bondGetDefNothing :: BondType a => BondGet CompactBinaryV1Proto (Maybe a) Source #

bondGetBonded :: BondStruct a => BondGet CompactBinaryV1Proto (Bonded a) Source #

BondTaggedProto CompactBinaryV1Proto Source # 
BondProto CompactBinaryV1Proto Source # 
type ReaderM CompactBinaryV1Proto Source # 
type WriterM CompactBinaryV1Proto Source # 

data CompactBinaryProto Source #

A binary, tagged protocol using variable integer encoding and compact field header. Version 2 of Compact Binary adds length prefix for structs. This enables deserialization of bonded<T> and skipping of unknown struct fields in constant time.

Constructors

CompactBinaryProto 

Instances

Protocol CompactBinaryProto Source # 

Associated Types

type ReaderM CompactBinaryProto :: * -> * Source #

type WriterM CompactBinaryProto :: * -> * Source #

Methods

bondPutStruct :: BondStruct a => a -> BondPut CompactBinaryProto Source #

bondPutBaseStruct :: BondStruct a => a -> BondPut CompactBinaryProto Source #

bondGetStruct :: BondStruct a => BondGet CompactBinaryProto a Source #

bondGetBaseStruct :: BondStruct a => BondGet CompactBinaryProto a Source #

bondPutField :: (BondType a, BondStruct b) => Proxy * b -> Ordinal -> a -> BondPut CompactBinaryProto Source #

bondPutDefNothingField :: (BondType a, BondStruct b) => Proxy * b -> Ordinal -> Maybe a -> BondPut CompactBinaryProto Source #

bondPutBool :: Bool -> BondPut CompactBinaryProto Source #

bondPutUInt8 :: Word8 -> BondPut CompactBinaryProto Source #

bondPutUInt16 :: Word16 -> BondPut CompactBinaryProto Source #

bondPutUInt32 :: Word32 -> BondPut CompactBinaryProto Source #

bondPutUInt64 :: Word64 -> BondPut CompactBinaryProto Source #

bondPutInt8 :: Int8 -> BondPut CompactBinaryProto Source #

bondPutInt16 :: Int16 -> BondPut CompactBinaryProto Source #

bondPutInt32 :: Int32 -> BondPut CompactBinaryProto Source #

bondPutInt64 :: Int64 -> BondPut CompactBinaryProto Source #

bondPutFloat :: Float -> BondPut CompactBinaryProto Source #

bondPutDouble :: Double -> BondPut CompactBinaryProto Source #

bondPutString :: Utf8 -> BondPut CompactBinaryProto Source #

bondPutWString :: Utf16 -> BondPut CompactBinaryProto Source #

bondPutBlob :: Blob -> BondPut CompactBinaryProto Source #

bondPutList :: BondType a => [a] -> BondPut CompactBinaryProto Source #

bondPutVector :: BondType a => Vector a -> BondPut CompactBinaryProto Source #

bondPutHashSet :: BondType a => HashSet a -> BondPut CompactBinaryProto Source #

bondPutSet :: BondType a => Set a -> BondPut CompactBinaryProto Source #

bondPutMap :: (BondType k, BondType v) => Map k v -> BondPut CompactBinaryProto Source #

bondPutNullable :: BondType a => Maybe a -> BondPut CompactBinaryProto Source #

bondPutBonded :: BondStruct a => Bonded a -> BondPut CompactBinaryProto Source #

bondGetBool :: BondGet CompactBinaryProto Bool Source #

bondGetUInt8 :: BondGet CompactBinaryProto Word8 Source #

bondGetUInt16 :: BondGet CompactBinaryProto Word16 Source #

bondGetUInt32 :: BondGet CompactBinaryProto Word32 Source #

bondGetUInt64 :: BondGet CompactBinaryProto Word64 Source #

bondGetInt8 :: BondGet CompactBinaryProto Int8 Source #

bondGetInt16 :: BondGet CompactBinaryProto Int16 Source #

bondGetInt32 :: BondGet CompactBinaryProto Int32 Source #

bondGetInt64 :: BondGet CompactBinaryProto Int64 Source #

bondGetFloat :: BondGet CompactBinaryProto Float Source #

bondGetDouble :: BondGet CompactBinaryProto Double Source #

bondGetString :: BondGet CompactBinaryProto Utf8 Source #

bondGetWString :: BondGet CompactBinaryProto Utf16 Source #

bondGetBlob :: BondGet CompactBinaryProto Blob Source #

bondGetList :: BondType a => BondGet CompactBinaryProto [a] Source #

bondGetVector :: BondType a => BondGet CompactBinaryProto (Vector a) Source #

bondGetHashSet :: (Eq a, Hashable a, BondType a) => BondGet CompactBinaryProto (HashSet a) Source #

bondGetSet :: (Ord a, BondType a) => BondGet CompactBinaryProto (Set a) Source #

bondGetMap :: (Ord k, BondType k, BondType v) => BondGet CompactBinaryProto (Map k v) Source #

bondGetNullable :: BondType a => BondGet CompactBinaryProto (Maybe a) Source #

bondGetDefNothing :: BondType a => BondGet CompactBinaryProto (Maybe a) Source #

bondGetBonded :: BondStruct a => BondGet CompactBinaryProto (Bonded a) Source #

BondTaggedProto CompactBinaryProto Source # 
BondProto CompactBinaryProto Source # 
type ReaderM CompactBinaryProto Source # 
type WriterM CompactBinaryProto Source # 

data FastBinaryProto Source #

A binary, tagged protocol similar to CompactBinaryProto but optimized for deserialization speed rather than payload compactness.

Constructors

FastBinaryProto 

Instances

Protocol FastBinaryProto Source # 

Associated Types

type ReaderM FastBinaryProto :: * -> * Source #

type WriterM FastBinaryProto :: * -> * Source #

Methods

bondPutStruct :: BondStruct a => a -> BondPut FastBinaryProto Source #

bondPutBaseStruct :: BondStruct a => a -> BondPut FastBinaryProto Source #

bondGetStruct :: BondStruct a => BondGet FastBinaryProto a Source #

bondGetBaseStruct :: BondStruct a => BondGet FastBinaryProto a Source #

bondPutField :: (BondType a, BondStruct b) => Proxy * b -> Ordinal -> a -> BondPut FastBinaryProto Source #

bondPutDefNothingField :: (BondType a, BondStruct b) => Proxy * b -> Ordinal -> Maybe a -> BondPut FastBinaryProto Source #

bondPutBool :: Bool -> BondPut FastBinaryProto Source #

bondPutUInt8 :: Word8 -> BondPut FastBinaryProto Source #

bondPutUInt16 :: Word16 -> BondPut FastBinaryProto Source #

bondPutUInt32 :: Word32 -> BondPut FastBinaryProto Source #

bondPutUInt64 :: Word64 -> BondPut FastBinaryProto Source #

bondPutInt8 :: Int8 -> BondPut FastBinaryProto Source #

bondPutInt16 :: Int16 -> BondPut FastBinaryProto Source #

bondPutInt32 :: Int32 -> BondPut FastBinaryProto Source #

bondPutInt64 :: Int64 -> BondPut FastBinaryProto Source #

bondPutFloat :: Float -> BondPut FastBinaryProto Source #

bondPutDouble :: Double -> BondPut FastBinaryProto Source #

bondPutString :: Utf8 -> BondPut FastBinaryProto Source #

bondPutWString :: Utf16 -> BondPut FastBinaryProto Source #

bondPutBlob :: Blob -> BondPut FastBinaryProto Source #

bondPutList :: BondType a => [a] -> BondPut FastBinaryProto Source #

bondPutVector :: BondType a => Vector a -> BondPut FastBinaryProto Source #

bondPutHashSet :: BondType a => HashSet a -> BondPut FastBinaryProto Source #

bondPutSet :: BondType a => Set a -> BondPut FastBinaryProto Source #

bondPutMap :: (BondType k, BondType v) => Map k v -> BondPut FastBinaryProto Source #

bondPutNullable :: BondType a => Maybe a -> BondPut FastBinaryProto Source #

bondPutBonded :: BondStruct a => Bonded a -> BondPut FastBinaryProto Source #

bondGetBool :: BondGet FastBinaryProto Bool Source #

bondGetUInt8 :: BondGet FastBinaryProto Word8 Source #

bondGetUInt16 :: BondGet FastBinaryProto Word16 Source #

bondGetUInt32 :: BondGet FastBinaryProto Word32 Source #

bondGetUInt64 :: BondGet FastBinaryProto Word64 Source #

bondGetInt8 :: BondGet FastBinaryProto Int8 Source #

bondGetInt16 :: BondGet FastBinaryProto Int16 Source #

bondGetInt32 :: BondGet FastBinaryProto Int32 Source #

bondGetInt64 :: BondGet FastBinaryProto Int64 Source #

bondGetFloat :: BondGet FastBinaryProto Float Source #

bondGetDouble :: BondGet FastBinaryProto Double Source #

bondGetString :: BondGet FastBinaryProto Utf8 Source #

bondGetWString :: BondGet FastBinaryProto Utf16 Source #

bondGetBlob :: BondGet FastBinaryProto Blob Source #

bondGetList :: BondType a => BondGet FastBinaryProto [a] Source #

bondGetVector :: BondType a => BondGet FastBinaryProto (Vector a) Source #

bondGetHashSet :: (Eq a, Hashable a, BondType a) => BondGet FastBinaryProto (HashSet a) Source #

bondGetSet :: (Ord a, BondType a) => BondGet FastBinaryProto (Set a) Source #

bondGetMap :: (Ord k, BondType k, BondType v) => BondGet FastBinaryProto (Map k v) Source #

bondGetNullable :: BondType a => BondGet FastBinaryProto (Maybe a) Source #

bondGetDefNothing :: BondType a => BondGet FastBinaryProto (Maybe a) Source #

bondGetBonded :: BondStruct a => BondGet FastBinaryProto (Bonded a) Source #

BondTaggedProto FastBinaryProto Source # 
BondProto FastBinaryProto Source # 
type ReaderM FastBinaryProto Source # 
type WriterM FastBinaryProto Source # 

data SimpleBinaryV1Proto Source #

A binary, untagged protocol which is a good choice for storage scenarios as it offers potential for big saving on payload size. Because Simple is an untagged protocol, it requires that the payload schema is available during deserialization.

Constructors

SimpleBinaryV1Proto 

Instances

Protocol SimpleBinaryV1Proto Source # 

Associated Types

type ReaderM SimpleBinaryV1Proto :: * -> * Source #

type WriterM SimpleBinaryV1Proto :: * -> * Source #

Methods

bondPutStruct :: BondStruct a => a -> BondPut SimpleBinaryV1Proto Source #

bondPutBaseStruct :: BondStruct a => a -> BondPut SimpleBinaryV1Proto Source #

bondGetStruct :: BondStruct a => BondGet SimpleBinaryV1Proto a Source #

bondGetBaseStruct :: BondStruct a => BondGet SimpleBinaryV1Proto a Source #

bondPutField :: (BondType a, BondStruct b) => Proxy * b -> Ordinal -> a -> BondPut SimpleBinaryV1Proto Source #

bondPutDefNothingField :: (BondType a, BondStruct b) => Proxy * b -> Ordinal -> Maybe a -> BondPut SimpleBinaryV1Proto Source #

bondPutBool :: Bool -> BondPut SimpleBinaryV1Proto Source #

bondPutUInt8 :: Word8 -> BondPut SimpleBinaryV1Proto Source #

bondPutUInt16 :: Word16 -> BondPut SimpleBinaryV1Proto Source #

bondPutUInt32 :: Word32 -> BondPut SimpleBinaryV1Proto Source #

bondPutUInt64 :: Word64 -> BondPut SimpleBinaryV1Proto Source #

bondPutInt8 :: Int8 -> BondPut SimpleBinaryV1Proto Source #

bondPutInt16 :: Int16 -> BondPut SimpleBinaryV1Proto Source #

bondPutInt32 :: Int32 -> BondPut SimpleBinaryV1Proto Source #

bondPutInt64 :: Int64 -> BondPut SimpleBinaryV1Proto Source #

bondPutFloat :: Float -> BondPut SimpleBinaryV1Proto Source #

bondPutDouble :: Double -> BondPut SimpleBinaryV1Proto Source #

bondPutString :: Utf8 -> BondPut SimpleBinaryV1Proto Source #

bondPutWString :: Utf16 -> BondPut SimpleBinaryV1Proto Source #

bondPutBlob :: Blob -> BondPut SimpleBinaryV1Proto Source #

bondPutList :: BondType a => [a] -> BondPut SimpleBinaryV1Proto Source #

bondPutVector :: BondType a => Vector a -> BondPut SimpleBinaryV1Proto Source #

bondPutHashSet :: BondType a => HashSet a -> BondPut SimpleBinaryV1Proto Source #

bondPutSet :: BondType a => Set a -> BondPut SimpleBinaryV1Proto Source #

bondPutMap :: (BondType k, BondType v) => Map k v -> BondPut SimpleBinaryV1Proto Source #

bondPutNullable :: BondType a => Maybe a -> BondPut SimpleBinaryV1Proto Source #

bondPutBonded :: BondStruct a => Bonded a -> BondPut SimpleBinaryV1Proto Source #

bondGetBool :: BondGet SimpleBinaryV1Proto Bool Source #

bondGetUInt8 :: BondGet SimpleBinaryV1Proto Word8 Source #

bondGetUInt16 :: BondGet SimpleBinaryV1Proto Word16 Source #

bondGetUInt32 :: BondGet SimpleBinaryV1Proto Word32 Source #

bondGetUInt64 :: BondGet SimpleBinaryV1Proto Word64 Source #

bondGetInt8 :: BondGet SimpleBinaryV1Proto Int8 Source #

bondGetInt16 :: BondGet SimpleBinaryV1Proto Int16 Source #

bondGetInt32 :: BondGet SimpleBinaryV1Proto Int32 Source #

bondGetInt64 :: BondGet SimpleBinaryV1Proto Int64 Source #

bondGetFloat :: BondGet SimpleBinaryV1Proto Float Source #

bondGetDouble :: BondGet SimpleBinaryV1Proto Double Source #

bondGetString :: BondGet SimpleBinaryV1Proto Utf8 Source #

bondGetWString :: BondGet SimpleBinaryV1Proto Utf16 Source #

bondGetBlob :: BondGet SimpleBinaryV1Proto Blob Source #

bondGetList :: BondType a => BondGet SimpleBinaryV1Proto [a] Source #

bondGetVector :: BondType a => BondGet SimpleBinaryV1Proto (Vector a) Source #

bondGetHashSet :: (Eq a, Hashable a, BondType a) => BondGet SimpleBinaryV1Proto (HashSet a) Source #

bondGetSet :: (Ord a, BondType a) => BondGet SimpleBinaryV1Proto (Set a) Source #

bondGetMap :: (Ord k, BondType k, BondType v) => BondGet SimpleBinaryV1Proto (Map k v) Source #

bondGetNullable :: BondType a => BondGet SimpleBinaryV1Proto (Maybe a) Source #

bondGetDefNothing :: BondType a => BondGet SimpleBinaryV1Proto (Maybe a) Source #

bondGetBonded :: BondStruct a => BondGet SimpleBinaryV1Proto (Bonded a) Source #

BondProto SimpleBinaryV1Proto Source # 
type ReaderM SimpleBinaryV1Proto Source # 
type WriterM SimpleBinaryV1Proto Source # 

data SimpleBinaryProto Source #

A binary, untagged protocol which is a good choice for storage scenarios as it offers potential for big saving on payload size. Because Simple is an untagged protocol, it requires that the payload schema is available during deserialization. Version 2 of Simple Protocol uses variable integer encoding for string and container lengths, resulting in more compact payload.

Constructors

SimpleBinaryProto 

Instances

Protocol SimpleBinaryProto Source # 

Associated Types

type ReaderM SimpleBinaryProto :: * -> * Source #

type WriterM SimpleBinaryProto :: * -> * Source #

Methods

bondPutStruct :: BondStruct a => a -> BondPut SimpleBinaryProto Source #

bondPutBaseStruct :: BondStruct a => a -> BondPut SimpleBinaryProto Source #

bondGetStruct :: BondStruct a => BondGet SimpleBinaryProto a Source #

bondGetBaseStruct :: BondStruct a => BondGet SimpleBinaryProto a Source #

bondPutField :: (BondType a, BondStruct b) => Proxy * b -> Ordinal -> a -> BondPut SimpleBinaryProto Source #

bondPutDefNothingField :: (BondType a, BondStruct b) => Proxy * b -> Ordinal -> Maybe a -> BondPut SimpleBinaryProto Source #

bondPutBool :: Bool -> BondPut SimpleBinaryProto Source #

bondPutUInt8 :: Word8 -> BondPut SimpleBinaryProto Source #

bondPutUInt16 :: Word16 -> BondPut SimpleBinaryProto Source #

bondPutUInt32 :: Word32 -> BondPut SimpleBinaryProto Source #

bondPutUInt64 :: Word64 -> BondPut SimpleBinaryProto Source #

bondPutInt8 :: Int8 -> BondPut SimpleBinaryProto Source #

bondPutInt16 :: Int16 -> BondPut SimpleBinaryProto Source #

bondPutInt32 :: Int32 -> BondPut SimpleBinaryProto Source #

bondPutInt64 :: Int64 -> BondPut SimpleBinaryProto Source #

bondPutFloat :: Float -> BondPut SimpleBinaryProto Source #

bondPutDouble :: Double -> BondPut SimpleBinaryProto Source #

bondPutString :: Utf8 -> BondPut SimpleBinaryProto Source #

bondPutWString :: Utf16 -> BondPut SimpleBinaryProto Source #

bondPutBlob :: Blob -> BondPut SimpleBinaryProto Source #

bondPutList :: BondType a => [a] -> BondPut SimpleBinaryProto Source #

bondPutVector :: BondType a => Vector a -> BondPut SimpleBinaryProto Source #

bondPutHashSet :: BondType a => HashSet a -> BondPut SimpleBinaryProto Source #

bondPutSet :: BondType a => Set a -> BondPut SimpleBinaryProto Source #

bondPutMap :: (BondType k, BondType v) => Map k v -> BondPut SimpleBinaryProto Source #

bondPutNullable :: BondType a => Maybe a -> BondPut SimpleBinaryProto Source #

bondPutBonded :: BondStruct a => Bonded a -> BondPut SimpleBinaryProto Source #

bondGetBool :: BondGet SimpleBinaryProto Bool Source #

bondGetUInt8 :: BondGet SimpleBinaryProto Word8 Source #

bondGetUInt16 :: BondGet SimpleBinaryProto Word16 Source #

bondGetUInt32 :: BondGet SimpleBinaryProto Word32 Source #

bondGetUInt64 :: BondGet SimpleBinaryProto Word64 Source #

bondGetInt8 :: BondGet SimpleBinaryProto Int8 Source #

bondGetInt16 :: BondGet SimpleBinaryProto Int16 Source #

bondGetInt32 :: BondGet SimpleBinaryProto Int32 Source #

bondGetInt64 :: BondGet SimpleBinaryProto Int64 Source #

bondGetFloat :: BondGet SimpleBinaryProto Float Source #

bondGetDouble :: BondGet SimpleBinaryProto Double Source #

bondGetString :: BondGet SimpleBinaryProto Utf8 Source #

bondGetWString :: BondGet SimpleBinaryProto Utf16 Source #

bondGetBlob :: BondGet SimpleBinaryProto Blob Source #

bondGetList :: BondType a => BondGet SimpleBinaryProto [a] Source #

bondGetVector :: BondType a => BondGet SimpleBinaryProto (Vector a) Source #

bondGetHashSet :: (Eq a, Hashable a, BondType a) => BondGet SimpleBinaryProto (HashSet a) Source #

bondGetSet :: (Ord a, BondType a) => BondGet SimpleBinaryProto (Set a) Source #

bondGetMap :: (Ord k, BondType k, BondType v) => BondGet SimpleBinaryProto (Map k v) Source #

bondGetNullable :: BondType a => BondGet SimpleBinaryProto (Maybe a) Source #

bondGetDefNothing :: BondType a => BondGet SimpleBinaryProto (Maybe a) Source #

bondGetBonded :: BondStruct a => BondGet SimpleBinaryProto (Bonded a) Source #

BondProto SimpleBinaryProto Source # 
type ReaderM SimpleBinaryProto Source # 
type WriterM SimpleBinaryProto Source # 

data JsonProto Source #

The output is a standard JSON and is a very good choice for interoperating with other systems or generating human readable payload. Because payload doesn't include field ordinals, it is treated as untagged protocol.

Constructors

JsonProto 

Instances

Protocol JsonProto Source # 

Associated Types

type ReaderM JsonProto :: * -> * Source #

type WriterM JsonProto :: * -> * Source #

Methods

bondPutStruct :: BondStruct a => a -> BondPut JsonProto Source #

bondPutBaseStruct :: BondStruct a => a -> BondPut JsonProto Source #

bondGetStruct :: BondStruct a => BondGet JsonProto a Source #

bondGetBaseStruct :: BondStruct a => BondGet JsonProto a Source #

bondPutField :: (BondType a, BondStruct b) => Proxy * b -> Ordinal -> a -> BondPut JsonProto Source #

bondPutDefNothingField :: (BondType a, BondStruct b) => Proxy * b -> Ordinal -> Maybe a -> BondPut JsonProto Source #

bondPutBool :: Bool -> BondPut JsonProto Source #

bondPutUInt8 :: Word8 -> BondPut JsonProto Source #

bondPutUInt16 :: Word16 -> BondPut JsonProto Source #

bondPutUInt32 :: Word32 -> BondPut JsonProto Source #

bondPutUInt64 :: Word64 -> BondPut JsonProto Source #

bondPutInt8 :: Int8 -> BondPut JsonProto Source #

bondPutInt16 :: Int16 -> BondPut JsonProto Source #

bondPutInt32 :: Int32 -> BondPut JsonProto Source #

bondPutInt64 :: Int64 -> BondPut JsonProto Source #

bondPutFloat :: Float -> BondPut JsonProto Source #

bondPutDouble :: Double -> BondPut JsonProto Source #

bondPutString :: Utf8 -> BondPut JsonProto Source #

bondPutWString :: Utf16 -> BondPut JsonProto Source #

bondPutBlob :: Blob -> BondPut JsonProto Source #

bondPutList :: BondType a => [a] -> BondPut JsonProto Source #

bondPutVector :: BondType a => Vector a -> BondPut JsonProto Source #

bondPutHashSet :: BondType a => HashSet a -> BondPut JsonProto Source #

bondPutSet :: BondType a => Set a -> BondPut JsonProto Source #

bondPutMap :: (BondType k, BondType v) => Map k v -> BondPut JsonProto Source #

bondPutNullable :: BondType a => Maybe a -> BondPut JsonProto Source #

bondPutBonded :: BondStruct a => Bonded a -> BondPut JsonProto Source #

bondGetBool :: BondGet JsonProto Bool Source #

bondGetUInt8 :: BondGet JsonProto Word8 Source #

bondGetUInt16 :: BondGet JsonProto Word16 Source #

bondGetUInt32 :: BondGet JsonProto Word32 Source #

bondGetUInt64 :: BondGet JsonProto Word64 Source #

bondGetInt8 :: BondGet JsonProto Int8 Source #

bondGetInt16 :: BondGet JsonProto Int16 Source #

bondGetInt32 :: BondGet JsonProto Int32 Source #

bondGetInt64 :: BondGet JsonProto Int64 Source #

bondGetFloat :: BondGet JsonProto Float Source #

bondGetDouble :: BondGet JsonProto Double Source #

bondGetString :: BondGet JsonProto Utf8 Source #

bondGetWString :: BondGet JsonProto Utf16 Source #

bondGetBlob :: BondGet JsonProto Blob Source #

bondGetList :: BondType a => BondGet JsonProto [a] Source #

bondGetVector :: BondType a => BondGet JsonProto (Vector a) Source #

bondGetHashSet :: (Eq a, Hashable a, BondType a) => BondGet JsonProto (HashSet a) Source #

bondGetSet :: (Ord a, BondType a) => BondGet JsonProto (Set a) Source #

bondGetMap :: (Ord k, BondType k, BondType v) => BondGet JsonProto (Map k v) Source #

bondGetNullable :: BondType a => BondGet JsonProto (Maybe a) Source #

bondGetDefNothing :: BondType a => BondGet JsonProto (Maybe a) Source #

bondGetBonded :: BondStruct a => BondGet JsonProto (Bonded a) Source #

BondProto JsonProto Source # 
type ReaderM JsonProto Source # 
type WriterM JsonProto Source # 

bonded<T>

data Bonded a Source #

bonded<T> value

Constructors

BondedStream ByteString

Marshalled stream

BondedObject a

Deserialized value

Instances

(BondStruct a, Eq a) => Eq (Bonded a) Source # 

Methods

(==) :: Bonded a -> Bonded a -> Bool #

(/=) :: Bonded a -> Bonded a -> Bool #

Show a => Show (Bonded a) Source # 

Methods

showsPrec :: Int -> Bonded a -> ShowS #

show :: Bonded a -> String #

showList :: [Bonded a] -> ShowS #

Generic (Bonded a) Source # 

Associated Types

type Rep (Bonded a) :: * -> * #

Methods

from :: Bonded a -> Rep (Bonded a) x #

to :: Rep (Bonded a) x -> Bonded a #

NFData a => NFData (Bonded a) Source # 

Methods

rnf :: Bonded a -> () #

BondStruct a => BondType (Bonded a) Source # 

Methods

bondGet :: (Functor (ReaderM t), Monad (ReaderM t), Protocol t) => BondGet t (Bonded a) Source #

bondPut :: (Monad (BondPutM t), Protocol t) => Bonded a -> BondPut t Source #

getName :: Proxy * (Bonded a) -> Text Source #

getQualifiedName :: Proxy * (Bonded a) -> Text Source #

getElementType :: Proxy * (Bonded a) -> ElementTypeInfo Source #

Default a => Default (Bonded a) 
type Rep (Bonded a) Source # 
type Rep (Bonded a) = D1 (MetaData "Bonded" "Data.Bond.Internal.Bonded" "bond-haskell-0.1.5.0-5YZ4ohYlsGS7OUiNgWkBDp" False) ((:+:) (C1 (MetaCons "BondedStream" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString))) (C1 (MetaCons "BondedObject" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a))))

getValue :: BondStruct a => Bonded a -> Either String a Source #

Extract value from Bonded using compile-type schema

putValue :: a -> Bonded a Source #

Put struct to the bonded<T> field.

castValue :: BondStruct b => Bonded a -> Either String b Source #

Extract value from Bonded using compile-type schema for other type. This may be useful for casting values to child structs. User is responsible for schema compatibility.

marshalValue :: (BondProto t, BondStruct a) => t -> a -> Either String (Bonded b) Source #

Marshal struct to the bonded<T> field. There is no checks for schema compatibility, caveat emptor.

data BondedException Source #

BondedException is thrown when attempt to deserialize bonded field for comparison fails. To handle such cases in the pure code explicitly decode all bonded fields before comparing structures.

Constructors

BondedException String 

Runtime-schema operations

Generic applications may need to work with Bond schemas unknown at compile-time. In order to address such scenarios Bond defines a type SchemaDef to represent schemas in stoorage and transfer.

Haskell library uses StructSchema internally for performance reasons and provides conversion functions.

class BondType a => BondStruct a where Source #

Bond top-level structure, can be de/serialized on its own.

Methods

getSchema :: Proxy a -> StructSchema Source #

Obtain struct schema.

Instances

BondStruct TypeDef Source # 
BondStruct Variant Source # 
BondStruct Metadata Source # 
BondStruct FieldDef Source # 
BondStruct StructDef Source # 
BondStruct SchemaDef Source # 

class BondEnum a where Source #

Bond enumeration class containing utility functions.

Minimal complete definition

toName, fromName

Methods

toName :: a -> Maybe Text Source #

Convert constant value to name.

fromName :: Text -> Maybe a Source #

Convert constant name to value.

assembleSchema :: StructSchema -> SchemaDef Source #

Convert internal schema representation to SchemaDef for storage or transfer.

checkStructSchema :: MonadError String m => StructSchema -> Struct -> m Struct Source #

Verify that Struct matches StructSchema and is internally consistent.

defaultStruct :: StructSchema -> Struct Source #

Create minimal valid Struct representing given schema

parseSchema :: SchemaDef -> Either String StructSchema Source #

Convert SchemaDef to internal schema representation.

data Struct Source #

Representation of bond structure used in runtime-schema operations.

Constructors

Struct 

Instances

Eq Struct Source # 

Methods

(==) :: Struct -> Struct -> Bool #

(/=) :: Struct -> Struct -> Bool #

Show Struct Source # 
Generic Struct Source # 

Associated Types

type Rep Struct :: * -> * #

Methods

from :: Struct -> Rep Struct x #

to :: Rep Struct x -> Struct #

NFData Struct Source # 

Methods

rnf :: Struct -> () #

type Rep Struct Source # 
type Rep Struct = D1 (MetaData "Struct" "Data.Bond.Struct" "bond-haskell-0.1.5.0-5YZ4ohYlsGS7OUiNgWkBDp" False) (C1 (MetaCons "Struct" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "base") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Struct))) (S1 (MetaSel (Just Symbol "fields") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map Ordinal Value)))))

data Value Source #

Representation of bond serializable type used in runtime-schema operations.

Instances

Eq Value Source # 

Methods

(==) :: Value -> Value -> Bool #

(/=) :: Value -> Value -> Bool #

Show Value Source # 

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

Generic Value Source # 

Associated Types

type Rep Value :: * -> * #

Methods

from :: Value -> Rep Value x #

to :: Rep Value x -> Value #

NFData Value Source # 

Methods

rnf :: Value -> () #

type Rep Value Source # 
type Rep Value = D1 (MetaData "Value" "Data.Bond.Struct" "bond-haskell-0.1.5.0-5YZ4ohYlsGS7OUiNgWkBDp" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "BOOL" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))) (C1 (MetaCons "INT8" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int8)))) ((:+:) (C1 (MetaCons "INT16" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int16))) (C1 (MetaCons "INT32" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32))))) ((:+:) ((:+:) (C1 (MetaCons "INT64" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int64))) (C1 (MetaCons "UINT8" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word8)))) ((:+:) (C1 (MetaCons "UINT16" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word16))) ((:+:) (C1 (MetaCons "UINT32" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word32))) (C1 (MetaCons "UINT64" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64))))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "FLOAT" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float))) (C1 (MetaCons "DOUBLE" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double)))) ((:+:) (C1 (MetaCons "STRING" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Utf8))) (C1 (MetaCons "WSTRING" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Utf16))))) ((:+:) ((:+:) (C1 (MetaCons "STRUCT" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Struct))) (C1 (MetaCons "LIST" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BondDataType)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Value]))))) ((:+:) (C1 (MetaCons "SET" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BondDataType)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Value])))) ((:+:) (C1 (MetaCons "MAP" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BondDataType)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BondDataType)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(Value, Value)]))))) (C1 (MetaCons "BONDED" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Bonded Struct)))))))))

Marshalling

Since Bond supports multiple serialization protocols, application endpoints either have to agree on a particular protocol, or include protocol metadata in the payload. Marshaling APIs provide the standard way to do the latter, by automatically adding a payload header with the protocol identifier and version.

See bondMarshal, bondMarshalWithSchema and bondMarshalTagged for serialization.

bondUnmarshal :: BondStruct a => ByteString -> Either String a Source #

Deserialize structure from stream, finding protocol from stream header.

bondUnmarshalWithSchema :: StructSchema -> ByteString -> Either String Struct Source #

Deserialize structure from stream with provided schema, finding protocol from stream header.

bondUnmarshalTagged :: ByteString -> Either String Struct Source #

Deserialize structure from stream without schema, finding protocol from stream header.

Misc

class IsString a => EncodedString a where Source #

Bond string/wstring transformations from/to String and Text.

Minimal complete definition

fromText, toText

Methods

toString :: a -> String Source #

Convert to String

fromText :: Text -> a Source #

Make bond string from Text

toText :: a -> Text Source #

Convert to Text

newtype Ordinal Source #

Bond structure field ordinal.

Constructors

Ordinal Word16 

defaultValue :: Default a => a Source #

Get default value for specified type.

Reexported from generated code

newtype BondDataType Source #

Constructors

BondDataType Int32 

Instances

Enum BondDataType Source # 
Eq BondDataType Source # 
Ord BondDataType Source # 
Show BondDataType Source # 
NFData BondDataType Source # 

Methods

rnf :: BondDataType -> () #

Hashable BondDataType Source # 
BondType BondDataType Source # 
BondEnum BondDataType Source # 
Default BondDataType Source # 

data SchemaDef Source #

Instances

Eq SchemaDef Source # 
Show SchemaDef Source # 
Generic SchemaDef Source # 

Associated Types

type Rep SchemaDef :: * -> * #

NFData SchemaDef Source # 

Methods

rnf :: SchemaDef -> () #

BondStruct SchemaDef Source # 
BondType SchemaDef Source # 
Default SchemaDef Source # 
type Rep SchemaDef Source # 
type Rep SchemaDef = D1 (MetaData "SchemaDef" "Data.Bond.Schema.SchemaDef" "bond-haskell-0.1.5.0-5YZ4ohYlsGS7OUiNgWkBDp" False) (C1 (MetaCons "SchemaDef" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "structs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Vector StructDef))) (S1 (MetaSel (Just Symbol "root") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TypeDef))))