Safe Haskell | None |
---|
- User API functions
- Main encoding and decoding operations (non-delimited message encoding)
- These should agree with the length delimited message format of protobuf-2.10, where the message size preceeds the data.
- Encoding to write or read a single message field (good for delimited messages or incremental use)
- The Put monad from the binary package, and a custom binary Get monad (Text.ProtocolBuffers.Get)
- The Wire monad itself. Users should beware that passing an incompatible
FieldType
is a runtime error or fail - The internal exports, for use by generated code and the Text.ProtcolBuffer.Extensions module
Here are the serialization and deserialization functions.
This module cooperates with the generated code to implement the Wire instances. The encoding is mostly documented at http://code.google.com/apis/protocolbuffers/docs/encoding.html.
The user API functions are grouped into sections and documented. The
rest are for internal use. The main functions are messageGet
and
messagePut
(and messageSize
). There are then several 'message*'
variants which allow for finer control and for making delimited
messages.
- messageSize :: (ReflectDescriptor msg, Wire msg) => msg -> WireSize
- messagePut :: (ReflectDescriptor msg, Wire msg) => msg -> ByteString
- messageGet :: (ReflectDescriptor msg, Wire msg) => ByteString -> Either String (msg, ByteString)
- messagePutM :: (ReflectDescriptor msg, Wire msg) => msg -> Put
- messageGetM :: (ReflectDescriptor msg, Wire msg) => Get msg
- messageWithLengthSize :: (ReflectDescriptor msg, Wire msg) => msg -> WireSize
- messageWithLengthPut :: (ReflectDescriptor msg, Wire msg) => msg -> ByteString
- messageWithLengthGet :: (ReflectDescriptor msg, Wire msg) => ByteString -> Either String (msg, ByteString)
- messageWithLengthPutM :: (ReflectDescriptor msg, Wire msg) => msg -> Put
- messageWithLengthGetM :: (ReflectDescriptor msg, Wire msg) => Get msg
- messageAsFieldSize :: (ReflectDescriptor msg, Wire msg) => FieldId -> msg -> WireSize
- messageAsFieldPutM :: (ReflectDescriptor msg, Wire msg) => FieldId -> msg -> Put
- messageAsFieldGetM :: (ReflectDescriptor msg, Wire msg) => Get (FieldId, msg)
- type Put = PutM ()
- data Get a
- runPut :: Put -> ByteString
- runGet :: Get a -> ByteString -> Result a
- runGetOnLazy :: Get r -> ByteString -> Either String (r, ByteString)
- getFromBS :: Get r -> ByteString -> r
- class Wire b where
- size'WireTag :: WireTag -> Int64
- toWireType :: FieldType -> WireType
- toWireTag :: FieldId -> FieldType -> WireTag
- toPackedWireTag :: FieldId -> WireTag
- mkWireTag :: FieldId -> WireType -> WireTag
- prependMessageSize :: WireSize -> WireSize
- putSize :: WireSize -> Put
- putVarUInt :: (Integral a, Bits a) => a -> Put
- getVarInt :: (Show a, Integral a, Bits a) => Get a
- putLazyByteString :: ByteString -> Put
- splitWireTag :: WireTag -> (FieldId, WireType)
- fieldIdOf :: WireTag -> FieldId
- wireSizeReq :: Wire v => Int64 -> FieldType -> v -> Int64
- wireSizeOpt :: Wire v => Int64 -> FieldType -> Maybe v -> Int64
- wireSizeRep :: Wire v => Int64 -> FieldType -> Seq v -> Int64
- wireSizePacked :: Wire v => Int64 -> FieldType -> Seq v -> Int64
- wirePutReq :: Wire v => WireTag -> FieldType -> v -> Put
- wirePutOpt :: Wire v => WireTag -> FieldType -> Maybe v -> Put
- wirePutRep :: Wire v => WireTag -> FieldType -> Seq v -> Put
- wirePutPacked :: Wire v => WireTag -> FieldType -> Seq v -> Put
- wireSizeErr :: Typeable a => FieldType -> a -> WireSize
- wirePutErr :: Typeable a => FieldType -> a -> Put
- wireGetErr :: Typeable a => FieldType -> Get a
- getMessageWith :: (Default message, ReflectDescriptor message) => (WireTag -> message -> Get message) -> Get message
- getBareMessageWith :: (Default message, ReflectDescriptor message) => (WireTag -> message -> Get message) -> Get message
- wireGetEnum :: (Typeable e, Enum e) => (Int -> Maybe e) -> Get e
- wireGetPackedEnum :: (Typeable e, Enum e) => (Int -> Maybe e) -> Get (Seq e)
- unknownField :: Typeable a => a -> FieldId -> Get a
- unknown :: (Typeable a, ReflectDescriptor a) => FieldId -> WireType -> a -> Get a
- wireGetFromWire :: FieldId -> WireType -> Get ByteString
- castWord64ToDouble :: Word64 -> Double
- castWord32ToFloat :: Word32 -> Float
- castDoubleToWord64 :: Double -> Word64
- castFloatToWord32 :: Float -> Word32
- zzEncode64 :: Int64 -> Word64
- zzEncode32 :: Int32 -> Word32
- zzDecode64 :: Word64 -> Int64
- zzDecode32 :: Word32 -> Int32
User API functions
Main encoding and decoding operations (non-delimited message encoding)
messageSize :: (ReflectDescriptor msg, Wire msg) => msg -> WireSizeSource
This computes the size of the message's fields with tags on the wire with no initial tag or length (in bytes). This is also the length of the message as placed between group start and stop tags.
messagePut :: (ReflectDescriptor msg, Wire msg) => msg -> ByteStringSource
This is runPut
applied to messagePutM
. It result in a
ByteString
with a length of messageSize
bytes.
messageGet :: (ReflectDescriptor msg, Wire msg) => ByteString -> Either String (msg, ByteString)Source
This consumes the ByteString
to decode a message. It assumes
the ByteString
is merely a sequence of the tagged fields of the
message, and consumes until a group stop tag is detected or the
entire input is consumed. Any ByteString
past the end of the
stop tag is returned as well.
This is runGetOnLazy
applied to messageGetM
.
messagePutM :: (ReflectDescriptor msg, Wire msg) => msg -> PutSource
messageGetM :: (ReflectDescriptor msg, Wire msg) => Get msgSource
This reads the tagged message fields until the stop tag or the end of input is reached.
This is actually wireGet 10 msg
These should agree with the length delimited message format of protobuf-2.10, where the message size preceeds the data.
messageWithLengthSize :: (ReflectDescriptor msg, Wire msg) => msg -> WireSizeSource
This computes the size of the message fields as in messageSize
and add the length of the encoded size to the total. Thus this is
the the length of the message including the encoded length header,
but without any leading tag.
messageWithLengthPut :: (ReflectDescriptor msg, Wire msg) => msg -> ByteStringSource
This is runPut
applied to messageWithLengthPutM
. It results
in a ByteString
with a length of messageWithLengthSize
bytes.
messageWithLengthGet :: (ReflectDescriptor msg, Wire msg) => ByteString -> Either String (msg, ByteString)Source
This runGetOnLazy
applied to messageWithLengthGetM
.
This first reads the encoded length of the message and will then
succeed when it has consumed precisely this many additional bytes.
The ByteString
after this point will be returned.
messageWithLengthPutM :: (ReflectDescriptor msg, Wire msg) => msg -> PutSource
messageWithLengthGetM :: (ReflectDescriptor msg, Wire msg) => Get msgSource
This reads the encoded message length and then the message.
This is actually wireGet 11 msg
Encoding to write or read a single message field (good for delimited messages or incremental use)
messageAsFieldSize :: (ReflectDescriptor msg, Wire msg) => FieldId -> msg -> WireSizeSource
This computes the size of the messageWithLengthSize
and then
adds the length an initial tag with the given FieldId
.
messageAsFieldPutM :: (ReflectDescriptor msg, Wire msg) => FieldId -> msg -> PutSource
messageAsFieldGetM :: (ReflectDescriptor msg, Wire msg) => Get (FieldId, msg)Source
The Put monad from the binary package, and a custom binary Get monad (Text.ProtocolBuffers.Get)
Monad Get | |
Functor Get | |
MonadPlus Get | |
Applicative Get | |
Alternative Get | |
MonadSuspend Get | |
MonadError String Get |
runPut :: Put -> ByteString
Run the Put
monad with a serialiser
runGetOnLazy :: Get r -> ByteString -> Either String (r, ByteString)Source
getFromBS :: Get r -> ByteString -> rSource
This is runGetOnLazy
with the Left
results converted to
error
calls and the trailing ByteString
discarded. This use of
runtime errors is discouraged, but may be convenient.
The Wire monad itself. Users should beware that passing an incompatible FieldType
is a runtime error or fail
The Wire
class is for internal use, and may change. If there
is a mis-match between the FieldType
and the type of b
then you
will get a failure at runtime.
Users should stick to the message functions defined in Text.ProtocolBuffers.WireMessage and exported to use user by Text.ProtocolBuffers. These are less likely to change.
The internal exports, for use by generated code and the Text.ProtcolBuffer.Extensions module
size'WireTag :: WireTag -> Int64Source
prependMessageSize :: WireSize -> WireSizeSource
Used in generated code.
putVarUInt :: (Integral a, Bits a) => a -> PutSource
putLazyByteString :: ByteString -> Put
Write a lazy ByteString efficiently, simply appending the lazy ByteString chunks to the output buffer
splitWireTag :: WireTag -> (FieldId, WireType)Source
wireSizeErr :: Typeable a => FieldType -> a -> WireSizeSource
wirePutErr :: Typeable a => FieldType -> a -> PutSource
wireGetErr :: Typeable a => FieldType -> Get aSource
getMessageWith :: (Default message, ReflectDescriptor message) => (WireTag -> message -> Get message) -> Get messageSource
getBareMessageWith :: (Default message, ReflectDescriptor message) => (WireTag -> message -> Get message) -> Get messageSource
Used by generated code getBareMessageWith assumes the wireTag for the message, if it existed, has already been read. getBareMessageWith assumes that it does needs to read the Varint encoded length of the message. getBareMessageWith will consume the entire ByteString it is operating on, or until it finds any STOP_GROUP tag (wireType == 4)
unknownField :: Typeable a => a -> FieldId -> Get aSource
wireGetFromWire :: FieldId -> WireType -> Get ByteStringSource
zzEncode64 :: Int64 -> Word64Source
zzEncode32 :: Int32 -> Word32Source
zzDecode64 :: Word64 -> Int64Source
zzDecode32 :: Word32 -> Int32Source