Copyright | (c) 2015-2016 Martijn Rijkeboer <mrr@sru-systems.com> |
---|---|
License | MIT |
Maintainer | Martijn Rijkeboer <mrr@sru-systems.com> |
Safe Haskell | None |
Language | Haskell2010 |
Internal functions used by the generated types.
- class Default a where
- newtype FieldNumber = FieldNumber Word32
- fromFieldNumber :: FieldNumber -> Word32
- toFieldNumber :: Word32 -> Either String FieldNumber
- class Mergeable a where
- class Required a where
- class WireEnum a where
- class Default a where
- newtype FieldNumber = FieldNumber Word32
- fromFieldNumber :: FieldNumber -> Word32
- toFieldNumber :: Word32 -> Either String FieldNumber
- class Mergeable a where
- class Required a where
- class WireEnum a where
- class WireMessage a where
- data WireTag = WireTag FieldNumber WireType
- fromWireTag :: WireTag -> Word32
- toWireTag :: Word32 -> Either String WireTag
- data WireType
- fromWireType :: WireType -> Word32
- toWireType :: Word32 -> Either String WireType
- decode :: (Default a, Required a, WireMessage a) => ByteString -> Either String a
- encode :: WireMessage a => a -> ByteString
- getBool :: Get Bool
- getBoolOpt :: Get (Maybe Bool)
- getBoolPacked :: Get (Seq Bool)
- getBytes :: Get ByteString
- getBytesOpt :: Get (Maybe ByteString)
- getDouble :: Get Double
- getDoubleOpt :: Get (Maybe Double)
- getDoublePacked :: Get (Seq Double)
- getEnum :: WireEnum a => Get a
- getEnumOpt :: WireEnum a => Get (Maybe a)
- getEnumPacked :: WireEnum a => Get (Seq a)
- getFixed32 :: Get Word32
- getFixed32Opt :: Get (Maybe Word32)
- getFixed32Packed :: Get (Seq Word32)
- getFixed64 :: Get Word64
- getFixed64Opt :: Get (Maybe Word64)
- getFixed64Packed :: Get (Seq Word64)
- getFloat :: Get Float
- getFloatOpt :: Get (Maybe Float)
- getFloatPacked :: Get (Seq Float)
- getGroup :: (Default a, Required a, WireMessage a) => Get a
- getGroupOpt :: (Default a, Required a, WireMessage a) => Get (Maybe a)
- getInt32 :: Get Int32
- getInt32Opt :: Get (Maybe Int32)
- getInt32Packed :: Get (Seq Int32)
- getInt64 :: Get Int64
- getInt64Opt :: Get (Maybe Int64)
- getInt64Packed :: Get (Seq Int64)
- getMessage :: (Default a, Required a, WireMessage a) => Get a
- getMessageOpt :: (Default a, Required a, WireMessage a) => Get (Maybe a)
- getSFixed32 :: Get Int32
- getSFixed32Opt :: Get (Maybe Int32)
- getSFixed32Packed :: Get (Seq Int32)
- getSFixed64 :: Get Int64
- getSFixed64Opt :: Get (Maybe Int64)
- getSFixed64Packed :: Get (Seq Int64)
- getSInt32 :: Get Int32
- getSInt32Opt :: Get (Maybe Int32)
- getSInt32Packed :: Get (Seq Int32)
- getSInt64 :: Get Int64
- getSInt64Opt :: Get (Maybe Int64)
- getSInt64Packed :: Get (Seq Int64)
- getString :: Get Text
- getStringOpt :: Get (Maybe Text)
- getUInt32 :: Get Word32
- getUInt32Opt :: Get (Maybe Word32)
- getUInt32Packed :: Get (Seq Word32)
- getUInt64 :: Get Word64
- getUInt64Opt :: Get (Maybe Word64)
- getUInt64Packed :: Get (Seq Word64)
- getUnknown :: WireTag -> a -> Get a
- getWireTag :: Get WireTag
- putBool :: WireTag -> Bool -> Put
- putBoolList :: WireTag -> Seq Bool -> Put
- putBoolOpt :: WireTag -> Maybe Bool -> Put
- putBoolPacked :: WireTag -> Seq Bool -> Put
- putBytes :: WireTag -> ByteString -> Put
- putBytesList :: WireTag -> Seq ByteString -> Put
- putBytesOpt :: WireTag -> Maybe ByteString -> Put
- putDouble :: WireTag -> Double -> Put
- putDoubleList :: WireTag -> Seq Double -> Put
- putDoubleOpt :: WireTag -> Maybe Double -> Put
- putDoublePacked :: WireTag -> Seq Double -> Put
- putEnum :: WireEnum a => WireTag -> a -> Put
- putEnumList :: WireEnum a => WireTag -> Seq a -> Put
- putEnumOpt :: WireEnum a => WireTag -> Maybe a -> Put
- putEnumPacked :: WireEnum a => WireTag -> Seq a -> Put
- putFixed32 :: WireTag -> Word32 -> Put
- putFixed32List :: WireTag -> Seq Word32 -> Put
- putFixed32Opt :: WireTag -> Maybe Word32 -> Put
- putFixed32Packed :: WireTag -> Seq Word32 -> Put
- putFixed64 :: WireTag -> Word64 -> Put
- putFixed64List :: WireTag -> Seq Word64 -> Put
- putFixed64Opt :: WireTag -> Maybe Word64 -> Put
- putFixed64Packed :: WireTag -> Seq Word64 -> Put
- putFloat :: WireTag -> Float -> Put
- putFloatList :: WireTag -> Seq Float -> Put
- putFloatOpt :: WireTag -> Maybe Float -> Put
- putFloatPacked :: WireTag -> Seq Float -> Put
- putGroup :: WireMessage a => a -> Put
- putGroupOpt :: WireMessage a => Maybe a -> Put
- putInt32 :: WireTag -> Int32 -> Put
- putInt32List :: WireTag -> Seq Int32 -> Put
- putInt32Opt :: WireTag -> Maybe Int32 -> Put
- putInt32Packed :: WireTag -> Seq Int32 -> Put
- putInt64 :: WireTag -> Int64 -> Put
- putInt64List :: WireTag -> Seq Int64 -> Put
- putInt64Opt :: WireTag -> Maybe Int64 -> Put
- putInt64Packed :: WireTag -> Seq Int64 -> Put
- putSFixed32 :: WireTag -> Int32 -> Put
- putSFixed32List :: WireTag -> Seq Int32 -> Put
- putSFixed32Opt :: WireTag -> Maybe Int32 -> Put
- putSFixed32Packed :: WireTag -> Seq Int32 -> Put
- putSFixed64 :: WireTag -> Int64 -> Put
- putSFixed64List :: WireTag -> Seq Int64 -> Put
- putSFixed64Opt :: WireTag -> Maybe Int64 -> Put
- putSFixed64Packed :: WireTag -> Seq Int64 -> Put
- putSInt32 :: WireTag -> Int32 -> Put
- putSInt32List :: WireTag -> Seq Int32 -> Put
- putSInt32Opt :: WireTag -> Maybe Int32 -> Put
- putSInt32Packed :: WireTag -> Seq Int32 -> Put
- putSInt64 :: WireTag -> Int64 -> Put
- putSInt64List :: WireTag -> Seq Int64 -> Put
- putSInt64Opt :: WireTag -> Maybe Int64 -> Put
- putSInt64Packed :: WireTag -> Seq Int64 -> Put
- putMessage :: WireMessage a => WireTag -> a -> Put
- putMessageList :: WireMessage a => WireTag -> Seq a -> Put
- putMessageOpt :: WireMessage a => WireTag -> Maybe a -> Put
- putString :: WireTag -> Text -> Put
- putStringList :: WireTag -> Seq Text -> Put
- putStringOpt :: WireTag -> Maybe Text -> Put
- putUInt32 :: WireTag -> Word32 -> Put
- putUInt32List :: WireTag -> Seq Word32 -> Put
- putUInt32Opt :: WireTag -> Maybe Word32 -> Put
- putUInt32Packed :: WireTag -> Seq Word32 -> Put
- putUInt64 :: WireTag -> Word64 -> Put
- putUInt64List :: WireTag -> Seq Word64 -> Put
- putUInt64Opt :: WireTag -> Maybe Word64 -> Put
- putUInt64Packed :: WireTag -> Seq Word64 -> Put
- putWireTag :: WireTag -> Put
- class WireMessage a where
- data WireTag = WireTag FieldNumber WireType
- fromWireTag :: WireTag -> Word32
- toWireTag :: Word32 -> Either String WireTag
- data WireType
- fromWireType :: WireType -> Word32
- toWireType :: Word32 -> Either String WireType
- append :: Seq a -> a -> Seq a
Documentation
class Default a where Source #
Typeclass to handle default values.
defaultVal :: a Source #
The default value for the field.
newtype FieldNumber Source #
Type to represent a field number (unique numbered tag).
fromFieldNumber :: FieldNumber -> Word32 Source #
Convert a FieldNumber into a Word32.
toFieldNumber :: Word32 -> Either String FieldNumber Source #
Convert a Word32 into a FieldNumber or an error.
class Mergeable a where Source #
Typeclass to handle merging of values.
class Default a where Source #
Typeclass to handle default values.
defaultVal :: a Source #
The default value for the field.
newtype FieldNumber Source #
Type to represent a field number (unique numbered tag).
fromFieldNumber :: FieldNumber -> Word32 Source #
Convert a FieldNumber into a Word32.
toFieldNumber :: Word32 -> Either String FieldNumber Source #
Convert a Word32 into a FieldNumber or an error.
class Mergeable a where Source #
Typeclass to handle merging of values.
class WireMessage a where Source #
Typeclass to handle encoding and decoding of messages.
fieldToValue :: WireTag -> a -> Get a Source #
Decode a field and merge it with the existing value in the message.
messageToFields :: a -> Put Source #
Encode all the fields of the message.
Type to represent a wire tag.
fromWireTag :: WireTag -> Word32 Source #
Convert a WireTag into a Word32.
Type to represent the Protocol Buffers wire type.
fromWireType :: WireType -> Word32 Source #
Convert a WireType into a Word32.
toWireType :: Word32 -> Either String WireType Source #
Convert a Word32 into a WireType or an error.
decode :: (Default a, Required a, WireMessage a) => ByteString -> Either String a Source #
Decode a ByteString into either the data-type or an error message.
Decode CustomType:
decCustomType :: ByteString -> Either String CustomType decCustomType = decode
encode :: WireMessage a => a -> ByteString Source #
Encode a data-type into a ByteString.
Encode CustomType:
encCustomType :: CustomType -> ByteString encCustomType = encode
getBytes :: Get ByteString Source #
Decode a required bytes field.
getBytesOpt :: Get (Maybe ByteString) Source #
Decode an optional bytes field.
getFixed32 :: Get Word32 Source #
Decode a required fixed32 field.
getFixed64 :: Get Word64 Source #
Decode a required fixed64 field.
getGroupOpt :: (Default a, Required a, WireMessage a) => Get (Maybe a) Source #
Decode an optional group field.
getMessage :: (Default a, Required a, WireMessage a) => Get a Source #
Decode a required message field.
getMessageOpt :: (Default a, Required a, WireMessage a) => Get (Maybe a) Source #
Decode an optional message field.
getSFixed32 :: Get Int32 Source #
Decode a required sfixed32 field.
getSFixed64 :: Get Int64 Source #
Decode a required sfixed64 field.
getUnknown :: WireTag -> a -> Get a Source #
Skip an unknown field.
getWireTag :: Get WireTag Source #
Decode a wire tag.
putBytesList :: WireTag -> Seq ByteString -> Put Source #
Encode a repeated bytes field.
putBytesOpt :: WireTag -> Maybe ByteString -> Put Source #
Encode an optional bytes field.
putGroup :: WireMessage a => a -> Put Source #
Encode a required group field.
putGroupOpt :: WireMessage a => Maybe a -> Put Source #
Encode an optional group field.
putMessage :: WireMessage a => WireTag -> a -> Put Source #
Encode a required message field.
putMessageList :: WireMessage a => WireTag -> Seq a -> Put Source #
Encode a repeated message field.
putMessageOpt :: WireMessage a => WireTag -> Maybe a -> Put Source #
Encode an optional message field.
putWireTag :: WireTag -> Put Source #
Encode a wire tag.
class WireMessage a where Source #
Typeclass to handle encoding and decoding of messages.
fieldToValue :: WireTag -> a -> Get a Source #
Decode a field and merge it with the existing value in the message.
messageToFields :: a -> Put Source #
Encode all the fields of the message.
Type to represent a wire tag.
fromWireTag :: WireTag -> Word32 Source #
Convert a WireTag into a Word32.
Type to represent the Protocol Buffers wire type.
fromWireType :: WireType -> Word32 Source #
Convert a WireType into a Word32.