Safe Haskell | None |
---|---|
Language | Haskell2010 |
Data.ProtocolBuffers.Internal
- type Tag = Word32
- data WireField
- = VarintField !Tag !Word64
- | Fixed64Field !Tag !Word64
- | DelimitedField !Tag !ByteString
- | StartField !Tag
- | EndField !Tag
- | Fixed32Field !Tag !Word32
- wireFieldTag :: WireField -> Tag
- getWireField :: Get WireField
- class EncodeWire a where
- encodeWire :: Tag -> a -> Put
- class DecodeWire a where
- decodeWire :: WireField -> Get a
- zzEncode32 :: Int32 -> Word32
- zzEncode64 :: Int64 -> Word64
- zzDecode32 :: Word32 -> Int32
- zzDecode64 :: Word64 -> Int64
- newtype Field n a = Field {
- runField :: a
- newtype Value a = Value {
- runValue :: a
- newtype Always a = Always {
- runAlways :: a
- newtype Enumeration a = Enumeration {
- runEnumeration :: a
- newtype RequiredField a = Required {
- runRequired :: a
- newtype OptionalField a = Optional {
- runOptional :: a
- newtype RepeatedField a = Repeated {
- runRepeated :: a
- newtype PackedField a = PackedField {
- runPackedField :: a
- newtype PackedList a = PackedList {
- unPackedList :: [a]
- newtype Message m = Message {
- runMessage :: m
Documentation
A representation of the wire format as described in https://developers.google.com/protocol-buffers/docs/encoding#structure
Constructors
VarintField !Tag !Word64 | For: int32, int64, uint32, uint64, sint32, sint64, bool, enum |
Fixed64Field !Tag !Word64 | For: fixed64, sfixed64, double |
DelimitedField !Tag !ByteString | For: string, bytes, embedded messages, packed repeated fields |
StartField !Tag | For: groups (deprecated) |
EndField !Tag | For: groups (deprecated) |
Fixed32Field !Tag !Word32 | For: fixed32, sfixed32, float |
wireFieldTag :: WireField -> Tag Source
class EncodeWire a where Source
Methods
encodeWire :: Tag -> a -> Put Source
Instances
class DecodeWire a where Source
Methods
decodeWire :: WireField -> Get a Source
Instances
zzEncode32 :: Int32 -> Word32 Source
zzEncode64 :: Int64 -> Word64 Source
zzDecode32 :: Word32 -> Int32 Source
zzDecode64 :: Word64 -> Int64 Source
Fields are merely a way to hold a field tag along with its type, this shouldn't normally be referenced directly.
This provides better error messages than older versions which used Tagged
Instances
Value
selects the normal/typical way for encoding scalar (primitive) values.
Instances
To provide consistent instances for serialization a Traversable
Functor
is needed to
make Required
fields have the same shape as Optional
, Repeated
and Packed
.
Instances
Functor Always | |
Foldable Always | |
Traversable Always | |
Bounded a => Bounded (Always a) | |
Enum a => Enum (Always a) | |
Eq a => Eq (Always a) | |
Ord a => Ord (Always a) | |
Show a => Show (Always a) | |
Monoid (Always a) | |
NFData a => NFData (Always a) | |
Enum a => DecodeWire (Always (Enumeration a)) | |
DecodeWire a => DecodeWire (Always (Value a)) | |
EncodeWire a => EncodeWire (Always (Value a)) | |
HasField (Field n (RequiredField (Always (Enumeration a)))) | Iso: |
HasField (Field n (RequiredField (Always (Value a)))) | |
HasField (Field n (RequiredField (Always (Message a)))) | |
Typeable (* -> *) Always | |
type FieldType (Field n (RequiredField (Always (Enumeration a)))) = a | |
type FieldType (Field n (RequiredField (Always (Value a)))) = a | |
type FieldType (Field n (RequiredField (Always (Message a)))) = a |
newtype Enumeration a Source
Enumeration
fields use fromEnum
and toEnum
when encoding and decoding messages.
Constructors
Enumeration | |
Fields
|
Instances
newtype RequiredField a Source
RequiredField
is a newtype wrapped used to break overlapping instances
for encoding and decoding values
Constructors
Required | |
Fields
|
Instances
Functor RequiredField | |
Foldable RequiredField | |
Traversable RequiredField | |
Bounded a => Bounded (RequiredField a) | |
Enum a => Enum (RequiredField a) | |
Eq a => Eq (RequiredField a) | |
Ord a => Ord (RequiredField a) | |
Show a => Show (RequiredField a) | |
Monoid a => Monoid (RequiredField a) | |
NFData a => NFData (RequiredField a) | |
HasField (Field n (RequiredField (Always (Enumeration a)))) | Iso: |
HasField (Field n (RequiredField (Always (Value a)))) | |
HasField (Field n (RequiredField (Always (Message a)))) | |
Typeable (* -> *) RequiredField | |
type FieldType (Field n (RequiredField (Always (Enumeration a)))) = a | |
type FieldType (Field n (RequiredField (Always (Value a)))) = a | |
type FieldType (Field n (RequiredField (Always (Message a)))) = a |
newtype OptionalField a Source
OptionalField
is a newtype wrapped used to break overlapping instances
for encoding and decoding values
Constructors
Optional | |
Fields
|
Instances
Functor OptionalField | |
Foldable OptionalField | |
Traversable OptionalField | |
Bounded a => Bounded (OptionalField a) | |
Enum a => Enum (OptionalField a) | |
Eq a => Eq (OptionalField a) | |
Ord a => Ord (OptionalField a) | |
Show a => Show (OptionalField a) | |
Monoid a => Monoid (OptionalField a) | |
NFData a => NFData (OptionalField a) | |
HasField (Field n (OptionalField (Last (Enumeration a)))) | Iso: |
HasField (Field n (OptionalField (Last (Value a)))) | |
HasField (Field n (OptionalField (Maybe (Message a)))) | |
Typeable (* -> *) OptionalField | |
type FieldType (Field n (OptionalField (Last (Enumeration a)))) = Maybe a | |
type FieldType (Field n (OptionalField (Last (Value a)))) = Maybe a | |
type FieldType (Field n (OptionalField (Maybe (Message a)))) = Maybe a |
newtype RepeatedField a Source
RepeatedField
is a newtype wrapped used to break overlapping instances
for encoding and decoding values
Constructors
Repeated | |
Fields
|
Instances
Functor RepeatedField | |
Foldable RepeatedField | |
Traversable RepeatedField | |
Bounded a => Bounded (RepeatedField a) | |
Enum a => Enum (RepeatedField a) | |
Eq a => Eq (RepeatedField a) | |
Ord a => Ord (RepeatedField a) | |
Show a => Show (RepeatedField a) | |
Monoid a => Monoid (RepeatedField a) | |
NFData a => NFData (RepeatedField a) | |
HasField (Field n (RepeatedField [Enumeration a])) | Iso: |
HasField (Field n (RepeatedField [Value a])) | |
HasField (Field n (RepeatedField [Message a])) | |
Typeable (* -> *) RepeatedField | |
type FieldType (Field n (RepeatedField [Enumeration a])) = [a] | |
type FieldType (Field n (RepeatedField [Value a])) = [a] | |
type FieldType (Field n (RepeatedField [Message a])) = [a] |
newtype PackedField a Source
A Traversable
Functor
used to select packed sequence encoding/decoding.
Constructors
PackedField | |
Fields
|
Instances
Functor PackedField | |
Foldable PackedField | |
Traversable PackedField | |
Eq a => Eq (PackedField a) | |
Ord a => Ord (PackedField a) | |
Show a => Show (PackedField a) | |
Monoid a => Monoid (PackedField a) | |
NFData a => NFData (PackedField a) | |
HasField (Field n (PackedField (PackedList (Enumeration a)))) | Iso: |
HasField (Field n (PackedField (PackedList (Value a)))) | |
Typeable (* -> *) PackedField | |
type FieldType (Field n (PackedField (PackedList (Enumeration a)))) = [a] | |
type FieldType (Field n (PackedField (PackedList (Value a)))) = [a] |
newtype PackedList a Source
A list that is stored in a packed format.
Constructors
PackedList | |
Fields
|
Instances
The way to embed a message within another message. These embedded messages are stored as length-delimited fields.
For example:
data Inner = Inner { innerField ::Required
'1' (Value
Int64
) } deriving (Generic
,Show
) instanceEncode
Inner instanceDecode
Inner data Outer = Outer { outerField ::Required
'1' (Message
Inner) } deriving (Generic
,Show
) instanceEncode
Outer instanceDecode
Outer
It's worth noting that
is a Message
a Monoid
and NFData
instance. The Monoid
behavior models
that of the Protocol Buffers documentation, effectively Last
. It's done with a fairly big hammer
and it isn't possible to override this behavior. This can cause some less-obvious compile errors for
paramterized Message
types:
data Inner = Inner{inner ::Required
'2' (Value
Float
)} deriving (Generic
,Show
) instanceEncode
Inner instanceDecode
Inner data Outer a = Outer{outer ::Required
'3' (Message
a)} deriving (Generic
,Show
) instanceEncode
a =>Encode
(Outer a) instanceDecode
a =>Decode
(Outer a)
This fails because Decode
needs to know that the message can be merged. The resulting error
implies that you may want to add a constraint to the internal GMessageMonoid
class:
/tmp/tst.hs:18:10: Could not deduce (protobuf-0.1:GMessageMonoid
(Rep
a)) arising from a use of `protobuf-0.1:Decode
.$gdmdecode' from the context (Decode
a) bound by the instance declaration at /tmp/tst.hs:18:10-39 Possible fix: add an instance declaration for (protobuf-0.1:GMessageMonoid
(Rep
a)) In the expression: (protobuf-0.1:Decode
.$gdmdecode) In an equation fordecode
: decode = (protobuf-0.1:Decode
.$gdmdecode) In the instance declaration for `'Decode' (Outer a)'
The correct fix is to add the Monoid
constraint for the message:
- instance (Encode
a) =>Decode
(Outer a) + instance (Monoid
(Message
a),Decode
a) =>Decode
(Outer a)
Constructors
Message | |
Fields
|
Instances
Functor Message | |
Foldable Message | |
Traversable Message | |
Eq m => Eq (Message m) | |
Ord m => Ord (Message m) | |
Show m => Show (Message m) | |
(Generic m, GMessageMonoid (Rep m)) => Monoid (Message m) | |
(Generic m, GMessageNFData (Rep m)) => NFData (Message m) | |
Decode m => DecodeWire (Message m) | |
(Foldable f, Encode m) => EncodeWire (f (Message m)) | |
HasField (Field n (RepeatedField [Message a])) | |
HasField (Field n (OptionalField (Maybe (Message a)))) | |
HasField (Field n (RequiredField (Always (Message a)))) | |
type Required n (Message a) = Field n (RequiredField (Always (Message a))) | |
type Optional n (Message a) = Field n (OptionalField (Maybe (Message a))) | |
type FieldType (Field n (RepeatedField [Message a])) = [a] | |
type FieldType (Field n (OptionalField (Maybe (Message a)))) = Maybe a | |
type FieldType (Field n (RequiredField (Always (Message a)))) = a |