| Safe Haskell | None |
|---|
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 vise versa.
The Data.TypeLevel dependency is required due to http://hackage.haskell.org/trac/ghc/ticket/7459. I believe the partial fix already committed will allow migrating to GHC.TypeLits once GHC 7.8.1 is released.
Given a message definition:
{-# LANGUAGE DeriveGeneric #-}
import Data.Int
import Data.ProtocolBuffers
import Data.TypeLevel (D1, D2, D3)
import Data.Text
import GHC.Generics (Generic)
data Foo = Foo
{ field1 :: Required D1 (Value Int64) -- ^ The last field with tag = 1
, field2 :: Optional D2 (Value Text) -- ^ The last field with tag = 2
, field3 :: Repeated D3 (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.
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 FooRight (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 msg42>>>getField $ field2 msgNothing>>>getField $ field3 msg[True,False]
Some Protocol Buffers features are not currently implemented:
- class Encode a where
- encodeMessage :: Encode a => a -> Put
- encodeLengthPrefixedMessage :: Encode a => a -> Put
- class Decode a where
- decodeMessage :: Decode a => Get a
- decodeLengthPrefixedMessage :: Decode a => Get a
- type family Required n a :: *
- type family Optional n a :: *
- type Repeated n a = Field n (RepeatedField [a])
- type Packed n a = Field n (PackedField (PackedList a))
- class HasField a where
- data Field n a
- data Value a
- data Enumeration a
- data Message m
- newtype Signed a = Signed a
- newtype Fixed a = Fixed a
Message Serialization
Encoding
encodeMessage :: Encode a => a -> PutSource
Encode a Protocol Buffers message.
encodeLengthPrefixedMessage :: Encode a => a -> PutSource
Encode a Protocol Buffers message prefixed with a zz-encoded 32-bit integer describing it's length.
Decoding
decodeMessage :: Decode a => Get aSource
Decode a Protocol Buffers message.
decodeLengthPrefixedMessage :: Decode a => Get aSource
Decode a Protocol Buffers message prefixed with a zz-encoded 32-bit integer describing it's 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 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.
Functions for wrapping and unwrapping record fields. When applied they will have types similar to these:
getField::RequiredD1(ValueText) ->TextputField::Text->RequiredD1(ValueText)getField::OptionalD2(ValueInt32) ->MaybeInt32putField::MaybeInt32->OptionalD2(ValueInt32)getField::RepeatedD3(ValueDouble) -> [Double]putField:: [Double] ->RepeatedD3(ValueDouble)getField::PackedD4(ValueWord64) -> [Word64]putField:: [Word64] ->PackedD4(ValueWord64)
Methods
getField :: a -> FieldType aSource
Extract a value from it's Field representation.
putField :: FieldType a -> aSource
Wrap it back up again.
field :: Functor f => (FieldType a -> f (FieldType a)) -> a -> f aSource
An isomorphism lens compatible with the lens package
Instances
| HasField (Field n (PackedField (PackedList (Enumeration a)))) | Iso: |
| HasField (Field n (PackedField (PackedList (Value a)))) | |
| HasField (Field n (RepeatedField [Enumeration a])) | Iso: |
| HasField (Field n (RepeatedField [Value a])) | |
| HasField (Field n (OptionalField (Last (Enumeration a)))) | Iso: |
| HasField (Field n (OptionalField (Last (Value a)))) | |
| HasField (Field n (RequiredField (Always (Enumeration a)))) | Iso: |
| HasField (Field n (RequiredField (Always (Value a)))) | |
| HasField (Field n (RepeatedField [Message a])) | |
| HasField (Field n (OptionalField (Maybe (Message a)))) | |
| HasField (Field n (RequiredField (Always (Message a)))) |
Selectors
Follow these rules to define fields supported by the generic encoder/decoder:
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
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.
Value selects the normal/typical way for encoding scalar (primitive) values.
Instances
data Enumeration a Source
Enumeration fields use fromEnum and toEnum when encoding and decoding messages.
Instances
| Functor Enumeration | |
| Typeable1 Enumeration | |
| Foldable Enumeration | |
| Traversable Enumeration | |
| Bounded a => Bounded (Enumeration a) | |
| Enum a => Enum (Enumeration a) | |
| Eq a => Eq (Enumeration a) | |
| Ord a => Ord (Enumeration a) | |
| Show a => Show (Enumeration a) | |
| Monoid a => Monoid (Enumeration a) | |
| NFData a => NFData (Enumeration a) | |
| Enum a => DecodeWire (Enumeration (Maybe a)) | |
| Enum a => DecodeWire (Enumeration (Always a)) | |
| (Foldable f, Enum a) => EncodeWire (Enumeration (f a)) | |
| HasField (Field n (PackedField (PackedList (Enumeration a)))) | Iso: |
| HasField (Field n (RepeatedField [Enumeration a])) | Iso: |
| HasField (Field n (OptionalField (Last (Enumeration a)))) | Iso: |
| HasField (Field n (RequiredField (Always (Enumeration a)))) | Iso: |
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
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)))) |
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.
Signed integers are stored in a zz-encoded form.
Constructors
| Signed a |
Instances
| Functor Signed | |
| Typeable1 Signed | |
| Foldable Signed | |
| Traversable Signed | |
| Bounded a => Bounded (Signed a) | |
| Enum a => Enum (Signed a) | |
| Eq a => Eq (Signed a) | |
| Floating a => Floating (Signed a) | |
| Fractional a => Fractional (Signed a) | |
| Integral a => Integral (Signed a) | |
| Num a => Num (Signed a) | |
| Ord a => Ord (Signed a) | |
| Real a => Real (Signed a) | |
| RealFloat a => RealFloat (Signed a) | |
| RealFrac a => RealFrac (Signed a) | |
| Show a => Show (Signed a) | |
| Monoid a => Monoid (Signed a) | |
| Bits a => Bits (Signed a) | |
| NFData a => NFData (Signed a) | |
| DecodeWire (Signed Int32) | |
| DecodeWire (Signed Int64) | |
| DecodeWire (PackedList (Value (Signed Int32))) | |
| DecodeWire (PackedList (Value (Signed Int64))) | |
| EncodeWire (Signed Int32) | |
| EncodeWire (Signed Int64) | |
| EncodeWire (PackedList (Value (Signed Int32))) | |
| EncodeWire (PackedList (Value (Signed Int64))) |
Fixed integers are stored in little-endian form without additional encoding.
Constructors
| Fixed a |
Instances