protobuf-0.1.3: Google Protocol Buffers via GHC.Generics

Safe HaskellNone

Data.ProtocolBuffers.Internal

Synopsis

Documentation

type Tag = Word32Source

Field identifiers

data WireField Source

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

newtype Field n a 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

Constructors

Field 

Fields

runField :: a
 

newtype Value a Source

Value selects the normal/typical way for encoding scalar (primitive) values.

Constructors

Value 

Fields

runValue :: a
 

Instances

Functor Value 
Typeable1 Value 
Foldable Value 
Traversable Value 
Bounded a => Bounded (Value a) 
Enum a => Enum (Value a) 
Eq a => Eq (Value a) 
Ord a => Ord (Value a) 
Show a => Show (Value a) 
Monoid a => Monoid (Value a) 
NFData a => NFData (Value a) 
DecodeWire a => DecodeWire (Last (Value a)) 
DecodeWire a => DecodeWire (Maybe (Value a)) 
DecodeWire (PackedList (Value Bool)) 
DecodeWire (PackedList (Value Double)) 
DecodeWire (PackedList (Value Float)) 
DecodeWire (PackedList (Value Int32)) 
DecodeWire (PackedList (Value Int64)) 
DecodeWire (PackedList (Value Word32)) 
DecodeWire (PackedList (Value Word64)) 
DecodeWire (PackedList (Value (Fixed Int32))) 
DecodeWire (PackedList (Value (Fixed Int64))) 
DecodeWire (PackedList (Value (Fixed Word32))) 
DecodeWire (PackedList (Value (Fixed Word64))) 
DecodeWire (PackedList (Value (Signed Int32))) 
DecodeWire (PackedList (Value (Signed Int64))) 
DecodeWire a => DecodeWire (Always (Value a)) 
DecodeWire a => DecodeWire (Value a) 
EncodeWire a => EncodeWire [Value a] 
EncodeWire a => EncodeWire (Last (Value a)) 
EncodeWire a => EncodeWire (Maybe (Value a)) 
EncodeWire (PackedList (Value Bool)) 
EncodeWire (PackedList (Value Double)) 
EncodeWire (PackedList (Value Float)) 
EncodeWire (PackedList (Value Int32)) 
EncodeWire (PackedList (Value Int64)) 
EncodeWire (PackedList (Value Word32)) 
EncodeWire (PackedList (Value Word64)) 
EncodeWire (PackedList (Value (Fixed Int32))) 
EncodeWire (PackedList (Value (Fixed Int64))) 
EncodeWire (PackedList (Value (Fixed Word32))) 
EncodeWire (PackedList (Value (Fixed Word64))) 
EncodeWire (PackedList (Value (Signed Int32))) 
EncodeWire (PackedList (Value (Signed Int64))) 
EncodeWire a => EncodeWire (Always (Value a)) 
EncodeWire a => EncodeWire (Value a) 
HasField (Field n (PackedField (PackedList (Value a))))

Iso: FieldType (Packed n (Value a)) = [a]

HasField (Field n (RepeatedField [Value a]))

Iso: FieldType (Repeated n (Value a)) = [a]

HasField (Field n (OptionalField (Last (Value a))))

Iso: FieldType (Optional n (Value a)) = Maybe a

HasField (Field n (RequiredField (Always (Value a))))

Iso: FieldType (Required n (Value a)) = a

newtype Always a Source

To provide consistent instances for serialization a Traversable Functor is needed to make Required fields have the same shape as Optional, Repeated and Packed.

This is the Identity Functor with a Show instance.

Constructors

Always 

Fields

runAlways :: a
 

newtype RequiredField a Source

RequiredField is a newtype wrapped used to break overlapping instances for encoding and decoding values

Constructors

Required 

Fields

runRequired :: a
 

newtype OptionalField a Source

OptionalField is a newtype wrapped used to break overlapping instances for encoding and decoding values

Constructors

Optional 

Fields

runOptional :: a
 

newtype RepeatedField a Source

RepeatedField is a newtype wrapped used to break overlapping instances for encoding and decoding values

Constructors

Repeated 

Fields

runRepeated :: a
 

newtype PackedField a Source

A Traversable Functor used to select packed sequence encoding/decoding.

Constructors

PackedField 

Fields

runPackedField :: a
 

newtype PackedList a Source

A list that is stored in a packed format.

Constructors

PackedList 

Fields

unPackedList :: [a]
 

Instances

Functor PackedList 
Typeable1 PackedList 
Foldable PackedList 
Traversable PackedList 
Eq a => Eq (PackedList a) 
Ord a => Ord (PackedList a) 
Show a => Show (PackedList a) 
Monoid (PackedList a) 
NFData a => NFData (PackedList a) 
Enum a => DecodeWire (PackedList (Enumeration a)) 
DecodeWire (PackedList (Value Bool)) 
DecodeWire (PackedList (Value Double)) 
DecodeWire (PackedList (Value Float)) 
DecodeWire (PackedList (Value Int32)) 
DecodeWire (PackedList (Value Int64)) 
DecodeWire (PackedList (Value Word32)) 
DecodeWire (PackedList (Value Word64)) 
DecodeWire (PackedList (Value (Fixed Int32))) 
DecodeWire (PackedList (Value (Fixed Int64))) 
DecodeWire (PackedList (Value (Fixed Word32))) 
DecodeWire (PackedList (Value (Fixed Word64))) 
DecodeWire (PackedList (Value (Signed Int32))) 
DecodeWire (PackedList (Value (Signed Int64))) 
Enum a => EncodeWire (PackedList (Enumeration a)) 
EncodeWire (PackedList (Value Bool)) 
EncodeWire (PackedList (Value Double)) 
EncodeWire (PackedList (Value Float)) 
EncodeWire (PackedList (Value Int32)) 
EncodeWire (PackedList (Value Int64)) 
EncodeWire (PackedList (Value Word32)) 
EncodeWire (PackedList (Value Word64)) 
EncodeWire (PackedList (Value (Fixed Int32))) 
EncodeWire (PackedList (Value (Fixed Int64))) 
EncodeWire (PackedList (Value (Fixed Word32))) 
EncodeWire (PackedList (Value (Fixed Word64))) 
EncodeWire (PackedList (Value (Signed Int32))) 
EncodeWire (PackedList (Value (Signed Int64))) 
HasField (Field n (PackedField (PackedList (Enumeration a))))

Iso: FieldType (Packed n (Enumeration a)) = [a]

HasField (Field n (PackedField (PackedList (Value a))))

Iso: FieldType (Packed n (Value a)) = [a]

newtype Message m Source

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 D1 (Value Int64)
   } deriving (Generic, Show)

instance Encode Inner
instance Decode Inner

data Outer = Outer
   { outerField :: Required D1 (Message Inner)
   } deriving (Generic, Show)

instance Encode Outer
instance Decode Outer

It's worth noting that Message a is 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 D2 (Value Float)} deriving (Generic, Show)
instance Encode Inner
instance Decode Inner

data Outer a = Outer{outer :: Required D3 (Message a)} deriving (Generic, Show)
instance Encode a => Encode (Outer a)
instance Decode 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 for decode:
       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

runMessage :: m
 

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]))

Iso: FieldType (Repeated n (Message a)) = [a]

HasField (Field n (OptionalField (Maybe (Message a))))

Iso: FieldType (Optional n (Message a)) = Maybe a

HasField (Field n (RequiredField (Always (Message a))))

Iso: FieldType (Required n (Message a)) = a