Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
) instanceEncode
Foo instanceDecode
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:
- 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 :: Nat) (a :: *) :: *
- type family Optional (n :: Nat) (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 :: Nat) 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 -> 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
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 Optional (n :: Nat) (a :: *) :: * Source #
Optional fields. Values that are not found will return Nothing
.
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
)
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
HasField (Field n (PackedField (PackedList (Enumeration a)))) Source # | Iso: |
HasField (Field n (PackedField (PackedList (Value a)))) Source # | |
HasField (Field n (RepeatedField [Enumeration a])) Source # | Iso: |
HasField (Field n (RepeatedField [Value a])) Source # | |
HasField (Field n (OptionalField (Last (Enumeration a)))) Source # | Iso: |
HasField (Field n (OptionalField (Last (Value a)))) Source # | |
HasField (Field n (RequiredField (Always (Enumeration a)))) Source # | Iso: |
HasField (Field n (RequiredField (Always (Value a)))) Source # | |
HasField (Field n (RepeatedField [Message a])) Source # | |
HasField (Field n (OptionalField (Maybe (Message a)))) Source # | |
HasField (Field n (RequiredField (Always (Message a)))) Source # | |
Selectors
Follow these rules to define fields supported by the generic encoder/decoder:
data Field (n :: Nat) 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
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.
data Enumeration a Source #
Enumeration
fields use fromEnum
and toEnum
when encoding and decoding messages.
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)
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.
Signed a |
Fixed integers are stored in little-endian form without additional encoding.
Fixed a |