protobuf-0.2.1.1: Google Protocol Buffers via GHC.Generics

Safe HaskellNone
LanguageHaskell2010

Data.ProtocolBuffers

Contents

Description

An implementation of Protocol Buffers in pure Haskell.

Extensive documentation is available at https://developers.google.com/protocol-buffers/docs/overview and Google's reference implementation can be found at http://code.google.com/p/protobuf/.

It is intended to be used via GHC.Generics and does not require .proto files to function. Tools are being developed that will convert a Haskell Protobuf definition into a .proto and vice versa.

Given a message definition:

{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DataKinds     #-}

import Data.Int
import Data.ProtocolBuffers
import Data.Text
import GHC.Generics (Generic)
import GHC.TypeLits
import Data.Monoid
import Data.Serialize
import Data.Hex  -- cabal install hex (for testing)

 data Foo = Foo
   { field1 :: Required 1 (Value Int64) -- ^ The last field with tag = 1
   , field2 :: Optional 2 (Value Text) -- ^ The last field with tag = 2
   , field3 :: Repeated 3 (Value Bool)   -- ^ All fields with tag = 3, ordering is preserved
   } deriving (Generic, Show)

instance Encode Foo
instance Decode Foo
 

It can then be used for encoding and decoding. The Encode and Decode instances are derived automatically using DeriveGeneric and DefaultSignatures as outlined here: http://www.haskell.org/haskellwiki/GHC.Generics#More_general_default_methods.

To construct a message, use putField to set each field value. Optional, Repeated and Packed fields can be set to their empty value by using mempty. An example using record syntax for clarity:

>>> let msg = Foo{field1 = putField 42, field2 = mempty, field3 = putField [True, False]}

To serialize a message first convert it into a Put by way of encodeMessage and then to a ByteString by using runPut. Lazy ByteString serialization is done with runPutLazy.

>>> fmap hex runPut $ encodeMessage msg
"082A18011800"

Decoding is done with the inverse functions: decodeMessage and runGet, or runGetLazy.

>>> runGet decodeMessage =<< unhex "082A18011800" :: Either String Foo
Right
  (Foo
    { field1 = Field {runField = Required {runRequired = Always {runAlways = Value {runValue = 42}}}}
    , field2 = Field {runField = Optional {runOptional = Last {getLast = Nothing}}}
    , field3 = Field {runField = Repeated {runRepeated = [Value {runValue = True},Value {runValue = False}]}}
    }
  )

Use getField to read fields from a message:

>>> let Right msg = runGet decodeMessage =<< unhex "082A18011800" :: Either String Foo
>>> getField $ field1 msg
42
>>> getField $ field2 msg
Nothing
>>> getField $ field3 msg
[True,False]

Some Protocol Buffers features are not currently implemented:

  • Default values for Optional fields
  • Extension fields
  • Storing unknown fields, those without a mapped field tag in message record
  • Tag-delimited Groups, deprecated in lieu of Message

Synopsis

Message Serialization

Encoding

class Encode a where Source #

Methods

encode :: a -> Put Source #

encode :: (Generic a, GEncode (Rep a)) => a -> Put Source #

Instances

Encode (HashMap Tag [WireField]) Source #

Untyped message encoding

encodeMessage :: Encode a => a -> Put Source #

Encode a Protocol Buffers message.

encodeLengthPrefixedMessage :: Encode a => a -> Put Source #

Encode a Protocol Buffers message prefixed with a varint encoded 32-bit integer describing its length.

Decoding

class Decode a where Source #

Instances

Decode (HashMap Tag [WireField]) Source #

Untyped message decoding, decode = id

decodeMessage :: Decode a => Get a Source #

Decode a Protocol Buffers message.

decodeLengthPrefixedMessage :: Decode a => Get a Source #

Decode a Protocol Buffers message prefixed with a varint encoded 32-bit integer describing its length.

Fields

Tags

Restricted type aliases of Field. These are used to attach a field tag (a numeric id) to a field. Each tag must be unique within a given message, though this is not currently checked or enforced.

type family Required (n :: Nat) (a :: *) :: * Source #

Required fields. Parsing will return empty if a Required value is not found while decoding.

Instances

type family Optional (n :: Nat) (a :: *) :: * Source #

Optional fields. Values that are not found will return Nothing.

Instances

type Repeated n a = Field n (RepeatedField [a]) Source #

Lists of values.

type Packed n a = Field n (PackedField (PackedList a)) Source #

Packed values.

Accessors

Fields tend to have rather complex types that are unpleasant to interact with. HasField was designed to hide this complexity and provide a consistent way of getting and setting fields.

class HasField a where Source #

Functions for wrapping and unwrapping record fields. When applied they will have types similar to these:

getField :: Required '1' (Value Text) -> Text
putField :: Text -> Required '1' (Value Text)

getField :: Optional '2' (Value Int32) -> Maybe Int32
putField :: Maybe Int32 -> Optional '2' (Value Int32)

getField :: Repeated '3' (Value Double) -> [Double]
putField :: [Double] -> Repeated '3' (Value Double)

getField :: Packed '4' (Value Word64) -> [Word64]
putField :: [Word64] -> Packed '4' (Value Word64)
 

Minimal complete definition

getField, putField

Associated Types

type FieldType a :: * Source #

Methods

getField :: a -> FieldType a Source #

Extract a value from it's Field representation.

putField :: FieldType a -> a Source #

Wrap it back up again.

field :: Functor f => (FieldType a -> f (FieldType a)) -> a -> f a Source #

An isomorphism lens compatible with the lens package

Instances

HasField (Field n (PackedField (PackedList (Enumeration a)))) Source #

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

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

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

HasField (Field n (RepeatedField [Enumeration a])) Source #

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

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

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

HasField (Field n (OptionalField (Last (Enumeration a)))) Source #

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

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

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

HasField (Field n (RequiredField (Always (Enumeration a)))) Source #

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

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

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

HasField (Field n (RepeatedField [Message a])) Source #

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

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

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

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

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

Selectors

Follow these rules to define fields supported by the generic encoder/decoder:

  • The n phantom type parameter specifies the Protocol Buffers field tag (id).
  • Field tags must be an instance of Nat.
  • Field selectors must be an instance of Foldable to support encoding.
  • Value selectors must be an instance of Monoid to support decoding.

data 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

Instances

Functor (Field n) Source # 

Methods

fmap :: (a -> b) -> Field n a -> Field n b #

(<$) :: a -> Field n b -> Field n a #

Foldable (Field n) Source # 

Methods

fold :: Monoid m => Field n m -> m #

foldMap :: Monoid m => (a -> m) -> Field n a -> m #

foldr :: (a -> b -> b) -> b -> Field n a -> b #

foldr' :: (a -> b -> b) -> b -> Field n a -> b #

foldl :: (b -> a -> b) -> b -> Field n a -> b #

foldl' :: (b -> a -> b) -> b -> Field n a -> b #

foldr1 :: (a -> a -> a) -> Field n a -> a #

foldl1 :: (a -> a -> a) -> Field n a -> a #

toList :: Field n a -> [a] #

null :: Field n a -> Bool #

length :: Field n a -> Int #

elem :: Eq a => a -> Field n a -> Bool #

maximum :: Ord a => Field n a -> a #

minimum :: Ord a => Field n a -> a #

sum :: Num a => Field n a -> a #

product :: Num a => Field n a -> a #

Traversable (Field n) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Field n a -> f (Field n b) #

sequenceA :: Applicative f => Field n (f a) -> f (Field n a) #

mapM :: Monad m => (a -> m b) -> Field n a -> m (Field n b) #

sequence :: Monad m => Field n (m a) -> m (Field n a) #

Bounded a => Bounded (Field n a) Source # 

Methods

minBound :: Field n a #

maxBound :: Field n a #

Enum a => Enum (Field n a) Source # 

Methods

succ :: Field n a -> Field n a #

pred :: Field n a -> Field n a #

toEnum :: Int -> Field n a #

fromEnum :: Field n a -> Int #

enumFrom :: Field n a -> [Field n a] #

enumFromThen :: Field n a -> Field n a -> [Field n a] #

enumFromTo :: Field n a -> Field n a -> [Field n a] #

enumFromThenTo :: Field n a -> Field n a -> Field n a -> [Field n a] #

Eq a => Eq (Field n a) Source # 

Methods

(==) :: Field n a -> Field n a -> Bool #

(/=) :: Field n a -> Field n a -> Bool #

Ord a => Ord (Field n a) Source # 

Methods

compare :: Field n a -> Field n a -> Ordering #

(<) :: Field n a -> Field n a -> Bool #

(<=) :: Field n a -> Field n a -> Bool #

(>) :: Field n a -> Field n a -> Bool #

(>=) :: Field n a -> Field n a -> Bool #

max :: Field n a -> Field n a -> Field n a #

min :: Field n a -> Field n a -> Field n a #

Show a => Show (Field n a) Source # 

Methods

showsPrec :: Int -> Field n a -> ShowS #

show :: Field n a -> String #

showList :: [Field n a] -> ShowS #

Monoid a => Monoid (Field n a) Source # 

Methods

mempty :: Field n a #

mappend :: Field n a -> Field n a -> Field n a #

mconcat :: [Field n a] -> Field n a #

NFData a => NFData (Field n a) Source # 

Methods

rnf :: Field n a -> () #

HasField (Field n (PackedField (PackedList (Enumeration a)))) Source #

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

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

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

HasField (Field n (RepeatedField [Enumeration a])) Source #

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

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

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

HasField (Field n (OptionalField (Last (Enumeration a)))) Source #

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

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

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

HasField (Field n (RequiredField (Always (Enumeration a)))) Source #

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

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

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

HasField (Field n (RepeatedField [Message a])) Source #

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

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

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

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

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

(EncodeWire a, KnownNat n, Foldable f) => GEncode (K1 i (Field n (f a))) Source # 

Methods

gencode :: K1 i (Field n (f a)) a -> Put

(DecodeWire (PackedList a), KnownNat n) => GDecode (K1 i (Packed n a)) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get (K1 i (Packed n a) a)

(DecodeWire a, KnownNat n) => GDecode (K1 i (Field n (RequiredField (Always (Value a))))) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get (K1 i (Field n (RequiredField (Always (Value a)))) a)

(DecodeWire a, KnownNat n) => GDecode (K1 i (Repeated n a)) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get (K1 i (Repeated n a) a)

(Enum a, KnownNat n) => GDecode (K1 i (Field n (OptionalField (Last (Enumeration a))))) Source # 
(Enum a, KnownNat n) => GDecode (K1 i (Field n (RequiredField (Always (Enumeration a))))) Source # 
(DecodeWire a, KnownNat n) => GDecode (K1 i (Field n (OptionalField (Last (Value a))))) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get (K1 i (Field n (OptionalField (Last (Value a)))) a)

(Decode a, Monoid (Message a), KnownNat n) => GDecode (K1 i (Field n (OptionalField (Maybe (Message a))))) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get (K1 i (Field n (OptionalField (Maybe (Message a)))) a)

(Decode a, Monoid (Message a), KnownNat n) => GDecode (K1 i (Field n (RequiredField (Always (Message a))))) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get (K1 i (Field n (RequiredField (Always (Message a)))) a)

type FieldType (Field n (PackedField (PackedList (Enumeration a)))) Source # 
type FieldType (Field n (PackedField (PackedList (Value a)))) Source # 
type FieldType (Field n (PackedField (PackedList (Value a)))) = [a]
type FieldType (Field n (RepeatedField [Enumeration a])) Source # 
type FieldType (Field n (RepeatedField [Value a])) Source # 
type FieldType (Field n (RepeatedField [Value a])) = [a]
type FieldType (Field n (OptionalField (Last (Enumeration a)))) Source # 
type FieldType (Field n (OptionalField (Last (Value a)))) Source # 
type FieldType (Field n (RequiredField (Always (Enumeration a)))) Source # 
type FieldType (Field n (RequiredField (Always (Value a)))) Source # 
type FieldType (Field n (RepeatedField [Message a])) Source # 
type FieldType (Field n (RepeatedField [Message a])) = [a]
type FieldType (Field n (OptionalField (Maybe (Message a)))) Source # 
type FieldType (Field n (RequiredField (Always (Message a)))) Source # 

Values

Selectors

Each field value needs to specify the way it should be encoded.

There are three built-in value selectors: Value, Enumeration and Message.

If you're unsure what value selector to use, Value is probably the correct one.

data Value a Source #

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

Instances

Functor Value Source # 

Methods

fmap :: (a -> b) -> Value a -> Value b #

(<$) :: a -> Value b -> Value a #

Foldable Value Source # 

Methods

fold :: Monoid m => Value m -> m #

foldMap :: Monoid m => (a -> m) -> Value a -> m #

foldr :: (a -> b -> b) -> b -> Value a -> b #

foldr' :: (a -> b -> b) -> b -> Value a -> b #

foldl :: (b -> a -> b) -> b -> Value a -> b #

foldl' :: (b -> a -> b) -> b -> Value a -> b #

foldr1 :: (a -> a -> a) -> Value a -> a #

foldl1 :: (a -> a -> a) -> Value a -> a #

toList :: Value a -> [a] #

null :: Value a -> Bool #

length :: Value a -> Int #

elem :: Eq a => a -> Value a -> Bool #

maximum :: Ord a => Value a -> a #

minimum :: Ord a => Value a -> a #

sum :: Num a => Value a -> a #

product :: Num a => Value a -> a #

Traversable Value Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Value a -> f (Value b) #

sequenceA :: Applicative f => Value (f a) -> f (Value a) #

mapM :: Monad m => (a -> m b) -> Value a -> m (Value b) #

sequence :: Monad m => Value (m a) -> m (Value a) #

Bounded a => Bounded (Value a) Source # 

Methods

minBound :: Value a #

maxBound :: Value a #

Enum a => Enum (Value a) Source # 

Methods

succ :: Value a -> Value a #

pred :: Value a -> Value a #

toEnum :: Int -> Value a #

fromEnum :: Value a -> Int #

enumFrom :: Value a -> [Value a] #

enumFromThen :: Value a -> Value a -> [Value a] #

enumFromTo :: Value a -> Value a -> [Value a] #

enumFromThenTo :: Value a -> Value a -> Value a -> [Value a] #

Eq a => Eq (Value a) Source # 

Methods

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

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

Ord a => Ord (Value a) Source # 

Methods

compare :: Value a -> Value a -> Ordering #

(<) :: Value a -> Value a -> Bool #

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

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

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

max :: Value a -> Value a -> Value a #

min :: Value a -> Value a -> Value a #

Show a => Show (Value a) Source # 

Methods

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

show :: Value a -> String #

showList :: [Value a] -> ShowS #

Monoid a => Monoid (Value a) Source # 

Methods

mempty :: Value a #

mappend :: Value a -> Value a -> Value a #

mconcat :: [Value a] -> Value a #

NFData a => NFData (Value a) Source # 

Methods

rnf :: Value a -> () #

DecodeWire a => DecodeWire (Maybe (Value a)) Source # 
DecodeWire a => DecodeWire (Last (Value a)) Source # 
DecodeWire (PackedList (Value Bool)) Source # 
DecodeWire (PackedList (Value Double)) Source # 
DecodeWire (PackedList (Value Float)) Source # 
DecodeWire (PackedList (Value Int32)) Source # 
DecodeWire (PackedList (Value Int64)) Source # 
DecodeWire (PackedList (Value Word32)) Source # 
DecodeWire (PackedList (Value Word64)) Source # 
DecodeWire (PackedList (Value (Fixed Int32))) Source # 
DecodeWire (PackedList (Value (Fixed Int64))) Source # 
DecodeWire (PackedList (Value (Fixed Word32))) Source # 
DecodeWire (PackedList (Value (Fixed Word64))) Source # 
DecodeWire (PackedList (Value (Signed Int32))) Source # 
DecodeWire (PackedList (Value (Signed Int64))) Source # 
DecodeWire a => DecodeWire (Always (Value a)) Source # 
DecodeWire a => DecodeWire (Value a) Source # 
EncodeWire a => EncodeWire [Value a] Source # 

Methods

encodeWire :: Tag -> [Value a] -> Put Source #

EncodeWire a => EncodeWire (Maybe (Value a)) Source # 

Methods

encodeWire :: Tag -> Maybe (Value a) -> Put Source #

EncodeWire a => EncodeWire (Last (Value a)) Source # 

Methods

encodeWire :: Tag -> Last (Value a) -> Put Source #

EncodeWire (PackedList (Value Bool)) Source # 
EncodeWire (PackedList (Value Double)) Source # 
EncodeWire (PackedList (Value Float)) Source # 
EncodeWire (PackedList (Value Int32)) Source # 
EncodeWire (PackedList (Value Int64)) Source # 
EncodeWire (PackedList (Value Word32)) Source # 
EncodeWire (PackedList (Value Word64)) Source # 
EncodeWire (PackedList (Value (Fixed Int32))) Source # 
EncodeWire (PackedList (Value (Fixed Int64))) Source # 
EncodeWire (PackedList (Value (Fixed Word32))) Source # 
EncodeWire (PackedList (Value (Fixed Word64))) Source # 
EncodeWire (PackedList (Value (Signed Int32))) Source # 
EncodeWire (PackedList (Value (Signed Int64))) Source # 
EncodeWire a => EncodeWire (Always (Value a)) Source # 

Methods

encodeWire :: Tag -> Always (Value a) -> Put Source #

EncodeWire a => EncodeWire (Value a) Source # 

Methods

encodeWire :: Tag -> Value a -> Put Source #

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

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

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

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

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

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

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

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

(DecodeWire a, KnownNat n) => GDecode (K1 i (Field n (RequiredField (Always (Value a))))) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get (K1 i (Field n (RequiredField (Always (Value a)))) a)

(DecodeWire a, KnownNat n) => GDecode (K1 i (Field n (OptionalField (Last (Value a))))) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get (K1 i (Field n (OptionalField (Last (Value a)))) a)

type Required n (Value a) Source # 
type Required n (Value a) = Field n (RequiredField (Always (Value a)))
type Optional n (Value a) Source # 
type Optional n (Value a) = Field n (OptionalField (Last (Value a)))
type FieldType (Field n (PackedField (PackedList (Value a)))) Source # 
type FieldType (Field n (PackedField (PackedList (Value a)))) = [a]
type FieldType (Field n (RepeatedField [Value a])) Source # 
type FieldType (Field n (RepeatedField [Value a])) = [a]
type FieldType (Field n (OptionalField (Last (Value a)))) Source # 
type FieldType (Field n (RequiredField (Always (Value a)))) Source # 

data Enumeration a Source #

Enumeration fields use fromEnum and toEnum when encoding and decoding messages.

Instances

Functor Enumeration Source # 

Methods

fmap :: (a -> b) -> Enumeration a -> Enumeration b #

(<$) :: a -> Enumeration b -> Enumeration a #

Foldable Enumeration Source # 

Methods

fold :: Monoid m => Enumeration m -> m #

foldMap :: Monoid m => (a -> m) -> Enumeration a -> m #

foldr :: (a -> b -> b) -> b -> Enumeration a -> b #

foldr' :: (a -> b -> b) -> b -> Enumeration a -> b #

foldl :: (b -> a -> b) -> b -> Enumeration a -> b #

foldl' :: (b -> a -> b) -> b -> Enumeration a -> b #

foldr1 :: (a -> a -> a) -> Enumeration a -> a #

foldl1 :: (a -> a -> a) -> Enumeration a -> a #

toList :: Enumeration a -> [a] #

null :: Enumeration a -> Bool #

length :: Enumeration a -> Int #

elem :: Eq a => a -> Enumeration a -> Bool #

maximum :: Ord a => Enumeration a -> a #

minimum :: Ord a => Enumeration a -> a #

sum :: Num a => Enumeration a -> a #

product :: Num a => Enumeration a -> a #

Traversable Enumeration Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Enumeration a -> f (Enumeration b) #

sequenceA :: Applicative f => Enumeration (f a) -> f (Enumeration a) #

mapM :: Monad m => (a -> m b) -> Enumeration a -> m (Enumeration b) #

sequence :: Monad m => Enumeration (m a) -> m (Enumeration a) #

Bounded a => Bounded (Enumeration a) Source # 
Enum a => Enum (Enumeration a) Source # 
Eq a => Eq (Enumeration a) Source # 
Ord a => Ord (Enumeration a) Source # 
Show a => Show (Enumeration a) Source # 
Monoid a => Monoid (Enumeration a) Source # 
NFData a => NFData (Enumeration a) Source # 

Methods

rnf :: Enumeration a -> () #

Enum a => DecodeWire (Maybe (Enumeration a)) Source # 
Enum a => DecodeWire (PackedList (Enumeration a)) Source # 
Enum a => DecodeWire (Enumeration a) Source # 
Enum a => DecodeWire (Always (Enumeration a)) Source # 
(Foldable f, Enum a) => EncodeWire (f (Enumeration a)) Source # 

Methods

encodeWire :: Tag -> f (Enumeration a) -> Put Source #

Enum a => EncodeWire (PackedList (Enumeration a)) Source # 
HasField (Field n (PackedField (PackedList (Enumeration a)))) Source #

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

HasField (Field n (RepeatedField [Enumeration a])) Source #

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

HasField (Field n (OptionalField (Last (Enumeration a)))) Source #

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

HasField (Field n (RequiredField (Always (Enumeration a)))) Source #

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

(Enum a, KnownNat n) => GDecode (K1 i (Field n (OptionalField (Last (Enumeration a))))) Source # 
(Enum a, KnownNat n) => GDecode (K1 i (Field n (RequiredField (Always (Enumeration a))))) Source # 
type Required n (Enumeration a) Source # 
type Optional n (Enumeration a) Source # 
type FieldType (Field n (PackedField (PackedList (Enumeration a)))) Source # 
type FieldType (Field n (RepeatedField [Enumeration a])) Source # 
type FieldType (Field n (OptionalField (Last (Enumeration a)))) Source # 
type FieldType (Field n (RequiredField (Always (Enumeration a)))) Source # 

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

 instance Encode Inner
instance Decode Inner

 data Outer = Outer
   { outerField :: Required '1' (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 '2' (Value Float)} deriving (Generic, Show)
instance Encode Inner
instance Decode Inner

data Outer a = Outer{outer :: Required '3' (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)

Instances

Functor Message Source # 

Methods

fmap :: (a -> b) -> Message a -> Message b #

(<$) :: a -> Message b -> Message a #

Foldable Message Source # 

Methods

fold :: Monoid m => Message m -> m #

foldMap :: Monoid m => (a -> m) -> Message a -> m #

foldr :: (a -> b -> b) -> b -> Message a -> b #

foldr' :: (a -> b -> b) -> b -> Message a -> b #

foldl :: (b -> a -> b) -> b -> Message a -> b #

foldl' :: (b -> a -> b) -> b -> Message a -> b #

foldr1 :: (a -> a -> a) -> Message a -> a #

foldl1 :: (a -> a -> a) -> Message a -> a #

toList :: Message a -> [a] #

null :: Message a -> Bool #

length :: Message a -> Int #

elem :: Eq a => a -> Message a -> Bool #

maximum :: Ord a => Message a -> a #

minimum :: Ord a => Message a -> a #

sum :: Num a => Message a -> a #

product :: Num a => Message a -> a #

Traversable Message Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Message a -> f (Message b) #

sequenceA :: Applicative f => Message (f a) -> f (Message a) #

mapM :: Monad m => (a -> m b) -> Message a -> m (Message b) #

sequence :: Monad m => Message (m a) -> m (Message a) #

Eq m => Eq (Message m) Source # 

Methods

(==) :: Message m -> Message m -> Bool #

(/=) :: Message m -> Message m -> Bool #

Ord m => Ord (Message m) Source # 

Methods

compare :: Message m -> Message m -> Ordering #

(<) :: Message m -> Message m -> Bool #

(<=) :: Message m -> Message m -> Bool #

(>) :: Message m -> Message m -> Bool #

(>=) :: Message m -> Message m -> Bool #

max :: Message m -> Message m -> Message m #

min :: Message m -> Message m -> Message m #

Show m => Show (Message m) Source # 

Methods

showsPrec :: Int -> Message m -> ShowS #

show :: Message m -> String #

showList :: [Message m] -> ShowS #

(Generic m, GMessageMonoid (Rep m)) => Monoid (Message m) Source # 

Methods

mempty :: Message m #

mappend :: Message m -> Message m -> Message m #

mconcat :: [Message m] -> Message m #

(Generic m, GMessageNFData (Rep m)) => NFData (Message m) Source # 

Methods

rnf :: Message m -> () #

Decode m => DecodeWire (Message m) Source # 
(Foldable f, Encode m) => EncodeWire (f (Message m)) Source # 

Methods

encodeWire :: Tag -> f (Message m) -> Put Source #

HasField (Field n (RepeatedField [Message a])) Source #

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

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

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

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

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

(Decode a, Monoid (Message a), KnownNat n) => GDecode (K1 i (Field n (OptionalField (Maybe (Message a))))) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get (K1 i (Field n (OptionalField (Maybe (Message a)))) a)

(Decode a, Monoid (Message a), KnownNat n) => GDecode (K1 i (Field n (RequiredField (Always (Message a))))) Source # 

Methods

gdecode :: HashMap Tag [WireField] -> Get (K1 i (Field n (RequiredField (Always (Message a)))) a)

type Required n (Message a) Source # 
type Optional n (Message a) Source # 
type FieldType (Field n (RepeatedField [Message a])) Source # 
type FieldType (Field n (RepeatedField [Message a])) = [a]
type FieldType (Field n (OptionalField (Maybe (Message a)))) Source # 
type FieldType (Field n (RequiredField (Always (Message a)))) Source # 

Wire Coding

Some primitive values can be more compactly represented. Fields that typically contain negative or very large numbers should use the Signed or Fixed wrappers to select their respective (efficient) formats.

newtype Signed a Source #

Signed integers are stored in a zz-encoded form.

Constructors

Signed a 

Instances

Functor Signed Source # 

Methods

fmap :: (a -> b) -> Signed a -> Signed b #

(<$) :: a -> Signed b -> Signed a #

Foldable Signed Source # 

Methods

fold :: Monoid m => Signed m -> m #

foldMap :: Monoid m => (a -> m) -> Signed a -> m #

foldr :: (a -> b -> b) -> b -> Signed a -> b #

foldr' :: (a -> b -> b) -> b -> Signed a -> b #

foldl :: (b -> a -> b) -> b -> Signed a -> b #

foldl' :: (b -> a -> b) -> b -> Signed a -> b #

foldr1 :: (a -> a -> a) -> Signed a -> a #

foldl1 :: (a -> a -> a) -> Signed a -> a #

toList :: Signed a -> [a] #

null :: Signed a -> Bool #

length :: Signed a -> Int #

elem :: Eq a => a -> Signed a -> Bool #

maximum :: Ord a => Signed a -> a #

minimum :: Ord a => Signed a -> a #

sum :: Num a => Signed a -> a #

product :: Num a => Signed a -> a #

Traversable Signed Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Signed a -> f (Signed b) #

sequenceA :: Applicative f => Signed (f a) -> f (Signed a) #

mapM :: Monad m => (a -> m b) -> Signed a -> m (Signed b) #

sequence :: Monad m => Signed (m a) -> m (Signed a) #

Bounded a => Bounded (Signed a) Source # 

Methods

minBound :: Signed a #

maxBound :: Signed a #

Enum a => Enum (Signed a) Source # 

Methods

succ :: Signed a -> Signed a #

pred :: Signed a -> Signed a #

toEnum :: Int -> Signed a #

fromEnum :: Signed a -> Int #

enumFrom :: Signed a -> [Signed a] #

enumFromThen :: Signed a -> Signed a -> [Signed a] #

enumFromTo :: Signed a -> Signed a -> [Signed a] #

enumFromThenTo :: Signed a -> Signed a -> Signed a -> [Signed a] #

Eq a => Eq (Signed a) Source # 

Methods

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

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

Floating a => Floating (Signed a) Source # 

Methods

pi :: Signed a #

exp :: Signed a -> Signed a #

log :: Signed a -> Signed a #

sqrt :: Signed a -> Signed a #

(**) :: Signed a -> Signed a -> Signed a #

logBase :: Signed a -> Signed a -> Signed a #

sin :: Signed a -> Signed a #

cos :: Signed a -> Signed a #

tan :: Signed a -> Signed a #

asin :: Signed a -> Signed a #

acos :: Signed a -> Signed a #

atan :: Signed a -> Signed a #

sinh :: Signed a -> Signed a #

cosh :: Signed a -> Signed a #

tanh :: Signed a -> Signed a #

asinh :: Signed a -> Signed a #

acosh :: Signed a -> Signed a #

atanh :: Signed a -> Signed a #

log1p :: Signed a -> Signed a #

expm1 :: Signed a -> Signed a #

log1pexp :: Signed a -> Signed a #

log1mexp :: Signed a -> Signed a #

Fractional a => Fractional (Signed a) Source # 

Methods

(/) :: Signed a -> Signed a -> Signed a #

recip :: Signed a -> Signed a #

fromRational :: Rational -> Signed a #

Integral a => Integral (Signed a) Source # 

Methods

quot :: Signed a -> Signed a -> Signed a #

rem :: Signed a -> Signed a -> Signed a #

div :: Signed a -> Signed a -> Signed a #

mod :: Signed a -> Signed a -> Signed a #

quotRem :: Signed a -> Signed a -> (Signed a, Signed a) #

divMod :: Signed a -> Signed a -> (Signed a, Signed a) #

toInteger :: Signed a -> Integer #

Num a => Num (Signed a) Source # 

Methods

(+) :: Signed a -> Signed a -> Signed a #

(-) :: Signed a -> Signed a -> Signed a #

(*) :: Signed a -> Signed a -> Signed a #

negate :: Signed a -> Signed a #

abs :: Signed a -> Signed a #

signum :: Signed a -> Signed a #

fromInteger :: Integer -> Signed a #

Ord a => Ord (Signed a) Source # 

Methods

compare :: Signed a -> Signed a -> Ordering #

(<) :: Signed a -> Signed a -> Bool #

(<=) :: Signed a -> Signed a -> Bool #

(>) :: Signed a -> Signed a -> Bool #

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

max :: Signed a -> Signed a -> Signed a #

min :: Signed a -> Signed a -> Signed a #

Real a => Real (Signed a) Source # 

Methods

toRational :: Signed a -> Rational #

RealFloat a => RealFloat (Signed a) Source # 
RealFrac a => RealFrac (Signed a) Source # 

Methods

properFraction :: Integral b => Signed a -> (b, Signed a) #

truncate :: Integral b => Signed a -> b #

round :: Integral b => Signed a -> b #

ceiling :: Integral b => Signed a -> b #

floor :: Integral b => Signed a -> b #

Show a => Show (Signed a) Source # 

Methods

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

show :: Signed a -> String #

showList :: [Signed a] -> ShowS #

Monoid a => Monoid (Signed a) Source # 

Methods

mempty :: Signed a #

mappend :: Signed a -> Signed a -> Signed a #

mconcat :: [Signed a] -> Signed a #

Bits a => Bits (Signed a) Source # 

Methods

(.&.) :: Signed a -> Signed a -> Signed a #

(.|.) :: Signed a -> Signed a -> Signed a #

xor :: Signed a -> Signed a -> Signed a #

complement :: Signed a -> Signed a #

shift :: Signed a -> Int -> Signed a #

rotate :: Signed a -> Int -> Signed a #

zeroBits :: Signed a #

bit :: Int -> Signed a #

setBit :: Signed a -> Int -> Signed a #

clearBit :: Signed a -> Int -> Signed a #

complementBit :: Signed a -> Int -> Signed a #

testBit :: Signed a -> Int -> Bool #

bitSizeMaybe :: Signed a -> Maybe Int #

bitSize :: Signed a -> Int #

isSigned :: Signed a -> Bool #

shiftL :: Signed a -> Int -> Signed a #

unsafeShiftL :: Signed a -> Int -> Signed a #

shiftR :: Signed a -> Int -> Signed a #

unsafeShiftR :: Signed a -> Int -> Signed a #

rotateL :: Signed a -> Int -> Signed a #

rotateR :: Signed a -> Int -> Signed a #

popCount :: Signed a -> Int #

NFData a => NFData (Signed a) Source # 

Methods

rnf :: Signed a -> () #

DecodeWire (Signed Int32) Source # 
DecodeWire (Signed Int64) Source # 
DecodeWire (PackedList (Value (Signed Int32))) Source # 
DecodeWire (PackedList (Value (Signed Int64))) Source # 
EncodeWire (Signed Int32) Source # 
EncodeWire (Signed Int64) Source # 
EncodeWire (PackedList (Value (Signed Int32))) Source # 
EncodeWire (PackedList (Value (Signed Int64))) Source # 

newtype Fixed a Source #

Fixed integers are stored in little-endian form without additional encoding.

Constructors

Fixed a 

Instances

Functor Fixed Source # 

Methods

fmap :: (a -> b) -> Fixed a -> Fixed b #

(<$) :: a -> Fixed b -> Fixed a #

Foldable Fixed Source # 

Methods

fold :: Monoid m => Fixed m -> m #

foldMap :: Monoid m => (a -> m) -> Fixed a -> m #

foldr :: (a -> b -> b) -> b -> Fixed a -> b #

foldr' :: (a -> b -> b) -> b -> Fixed a -> b #

foldl :: (b -> a -> b) -> b -> Fixed a -> b #

foldl' :: (b -> a -> b) -> b -> Fixed a -> b #

foldr1 :: (a -> a -> a) -> Fixed a -> a #

foldl1 :: (a -> a -> a) -> Fixed a -> a #

toList :: Fixed a -> [a] #

null :: Fixed a -> Bool #

length :: Fixed a -> Int #

elem :: Eq a => a -> Fixed a -> Bool #

maximum :: Ord a => Fixed a -> a #

minimum :: Ord a => Fixed a -> a #

sum :: Num a => Fixed a -> a #

product :: Num a => Fixed a -> a #

Traversable Fixed Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Fixed a -> f (Fixed b) #

sequenceA :: Applicative f => Fixed (f a) -> f (Fixed a) #

mapM :: Monad m => (a -> m b) -> Fixed a -> m (Fixed b) #

sequence :: Monad m => Fixed (m a) -> m (Fixed a) #

Bounded a => Bounded (Fixed a) Source # 

Methods

minBound :: Fixed a #

maxBound :: Fixed a #

Enum a => Enum (Fixed a) Source # 

Methods

succ :: Fixed a -> Fixed a #

pred :: Fixed a -> Fixed a #

toEnum :: Int -> Fixed a #

fromEnum :: Fixed a -> Int #

enumFrom :: Fixed a -> [Fixed a] #

enumFromThen :: Fixed a -> Fixed a -> [Fixed a] #

enumFromTo :: Fixed a -> Fixed a -> [Fixed a] #

enumFromThenTo :: Fixed a -> Fixed a -> Fixed a -> [Fixed a] #

Eq a => Eq (Fixed a) Source # 

Methods

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

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

Floating a => Floating (Fixed a) Source # 

Methods

pi :: Fixed a #

exp :: Fixed a -> Fixed a #

log :: Fixed a -> Fixed a #

sqrt :: Fixed a -> Fixed a #

(**) :: Fixed a -> Fixed a -> Fixed a #

logBase :: Fixed a -> Fixed a -> Fixed a #

sin :: Fixed a -> Fixed a #

cos :: Fixed a -> Fixed a #

tan :: Fixed a -> Fixed a #

asin :: Fixed a -> Fixed a #

acos :: Fixed a -> Fixed a #

atan :: Fixed a -> Fixed a #

sinh :: Fixed a -> Fixed a #

cosh :: Fixed a -> Fixed a #

tanh :: Fixed a -> Fixed a #

asinh :: Fixed a -> Fixed a #

acosh :: Fixed a -> Fixed a #

atanh :: Fixed a -> Fixed a #

log1p :: Fixed a -> Fixed a #

expm1 :: Fixed a -> Fixed a #

log1pexp :: Fixed a -> Fixed a #

log1mexp :: Fixed a -> Fixed a #

Fractional a => Fractional (Fixed a) Source # 

Methods

(/) :: Fixed a -> Fixed a -> Fixed a #

recip :: Fixed a -> Fixed a #

fromRational :: Rational -> Fixed a #

Integral a => Integral (Fixed a) Source # 

Methods

quot :: Fixed a -> Fixed a -> Fixed a #

rem :: Fixed a -> Fixed a -> Fixed a #

div :: Fixed a -> Fixed a -> Fixed a #

mod :: Fixed a -> Fixed a -> Fixed a #

quotRem :: Fixed a -> Fixed a -> (Fixed a, Fixed a) #

divMod :: Fixed a -> Fixed a -> (Fixed a, Fixed a) #

toInteger :: Fixed a -> Integer #

Num a => Num (Fixed a) Source # 

Methods

(+) :: Fixed a -> Fixed a -> Fixed a #

(-) :: Fixed a -> Fixed a -> Fixed a #

(*) :: Fixed a -> Fixed a -> Fixed a #

negate :: Fixed a -> Fixed a #

abs :: Fixed a -> Fixed a #

signum :: Fixed a -> Fixed a #

fromInteger :: Integer -> Fixed a #

Ord a => Ord (Fixed a) Source # 

Methods

compare :: Fixed a -> Fixed a -> Ordering #

(<) :: Fixed a -> Fixed a -> Bool #

(<=) :: Fixed a -> Fixed a -> Bool #

(>) :: Fixed a -> Fixed a -> Bool #

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

max :: Fixed a -> Fixed a -> Fixed a #

min :: Fixed a -> Fixed a -> Fixed a #

Real a => Real (Fixed a) Source # 

Methods

toRational :: Fixed a -> Rational #

RealFloat a => RealFloat (Fixed a) Source # 
RealFrac a => RealFrac (Fixed a) Source # 

Methods

properFraction :: Integral b => Fixed a -> (b, Fixed a) #

truncate :: Integral b => Fixed a -> b #

round :: Integral b => Fixed a -> b #

ceiling :: Integral b => Fixed a -> b #

floor :: Integral b => Fixed a -> b #

Show a => Show (Fixed a) Source # 

Methods

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

show :: Fixed a -> String #

showList :: [Fixed a] -> ShowS #

Monoid a => Monoid (Fixed a) Source # 

Methods

mempty :: Fixed a #

mappend :: Fixed a -> Fixed a -> Fixed a #

mconcat :: [Fixed a] -> Fixed a #

Bits a => Bits (Fixed a) Source # 

Methods

(.&.) :: Fixed a -> Fixed a -> Fixed a #

(.|.) :: Fixed a -> Fixed a -> Fixed a #

xor :: Fixed a -> Fixed a -> Fixed a #

complement :: Fixed a -> Fixed a #

shift :: Fixed a -> Int -> Fixed a #

rotate :: Fixed a -> Int -> Fixed a #

zeroBits :: Fixed a #

bit :: Int -> Fixed a #

setBit :: Fixed a -> Int -> Fixed a #

clearBit :: Fixed a -> Int -> Fixed a #

complementBit :: Fixed a -> Int -> Fixed a #

testBit :: Fixed a -> Int -> Bool #

bitSizeMaybe :: Fixed a -> Maybe Int #

bitSize :: Fixed a -> Int #

isSigned :: Fixed a -> Bool #

shiftL :: Fixed a -> Int -> Fixed a #

unsafeShiftL :: Fixed a -> Int -> Fixed a #

shiftR :: Fixed a -> Int -> Fixed a #

unsafeShiftR :: Fixed a -> Int -> Fixed a #

rotateL :: Fixed a -> Int -> Fixed a #

rotateR :: Fixed a -> Int -> Fixed a #

popCount :: Fixed a -> Int #

NFData a => NFData (Fixed a) Source # 

Methods

rnf :: Fixed a -> () #

DecodeWire (Fixed Int32) Source # 
DecodeWire (Fixed Int64) Source # 
DecodeWire (Fixed Word32) Source # 
DecodeWire (Fixed Word64) Source # 
DecodeWire (PackedList (Value (Fixed Int32))) Source # 
DecodeWire (PackedList (Value (Fixed Int64))) Source # 
DecodeWire (PackedList (Value (Fixed Word32))) Source # 
DecodeWire (PackedList (Value (Fixed Word64))) Source # 
EncodeWire (Fixed Int32) Source # 

Methods

encodeWire :: Tag -> Fixed Int32 -> Put Source #

EncodeWire (Fixed Int64) Source # 

Methods

encodeWire :: Tag -> Fixed Int64 -> Put Source #

EncodeWire (Fixed Word32) Source # 
EncodeWire (Fixed Word64) Source # 
EncodeWire (PackedList (Value (Fixed Int32))) Source # 
EncodeWire (PackedList (Value (Fixed Int64))) Source # 
EncodeWire (PackedList (Value (Fixed Word32))) Source # 
EncodeWire (PackedList (Value (Fixed Word64))) Source #