protobuf-simple: Simple Protocol Buffers library (proto2)

This is a package candidate release! Here you can preview how this package release will appear once published to the main package index (which can be accomplished via the 'maintain' link below). Please note that once a package has been published to the main package index it cannot be undone! Please consult the package uploading documentation for more information.

[maintain] [Publish]

An Haskell implementation of Google's Protocol Buffers version 2 with an emphasis on simplicity. The implementation consists of a library for encoding and decoding of data and the protoc executable for generating Haskell types from proto files. In fact, the types that are used in the tests are generated with the following command:

$ protoc data/Types.proto

In the example below, the CustomType is a Haskell type that was generated with the protoc executable. The encCustomType function encodes a CustomType into a ByteString. The decCustomType function decodes a ByteString into either a CustomType or an error.

module Codec where

import Data.ByteString.Lazy (ByteString)
import Data.ProtoBuf (decode, encode)
import Types.CustomType (CustomType(..))

encCustomType :: CustomType -> ByteString
encCustomType = encode

decCustomType :: ByteString -> Either String CustomType
decCustomType = decode

The library exposes two modules, Data.ProtoBuf, which is used for encoding and decoding and Data.ProtoBufInt, which is an internal module that is used by the generated types.


[Skip to Readme]

Properties

Versions 0.1.0.0, 0.1.0.1, 0.1.0.2, 0.1.0.2, 0.1.0.3, 0.1.0.4, 0.1.0.5, 0.1.1.0, 0.1.1.1
Change log None available
Dependencies base (>=4 && <5), binary (>=0.7), bytestring (>=0.9), containers (>=0.4), data-binary-ieee754 (>=0.4), directory, filepath, mtl (>=2.0), parsec, split, text (>=0.11) [details]
License MIT
Copyright (c) 2015-2016 Martijn Rijkeboer <mrr@sru-systems.com>
Author Martijn Rijkeboer <mrr@sru-systems.com>
Maintainer Martijn Rijkeboer <mrr@sru-systems.com>
Category Data
Home page https://github.com/sru-systems/protobuf-simple
Source repo head: git clone https://github.com/sru-systems/protobuf-simple
Uploaded by mrijkeboer at 2016-09-26T08:46:31Z

Modules

[Index]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees


Readme for protobuf-simple-0.1.0.2

[back to package description]

Protobuf-simple

An Haskell implementation of Google's Protocol Buffers version 2 with an emphasis on simplicity. The implementation consists of a library for encoding and decoding of data and the protoc executable for generating Haskell types from proto files. In fact, the types that are used in the tests are generated with the following command:

$ protoc data/Types.proto

In the example below, the CustomType is a Haskell type that was generated with the protoc executable. The encCustomType function encodes a CustomType into a ByteString. The decCustomType function decodes a ByteString into either a CustomType or an error.

module Codec where

import Data.ByteString.Lazy (ByteString)
import Data.ProtoBuf (decode, encode)
import Types.CustomType (CustomType(..))

encCustomType :: CustomType -> ByteString
encCustomType = encode

decCustomType :: ByteString -> Either String CustomType
decCustomType = decode

The library exposes two modules, Data.ProtoBuf, which is used for encoding and decoding and Data.ProtoBufInt, which is an internal module that is used by the generated types.

Supported Data Types

The following Protocol Buffer types, with their Haskell counterparts, are supported:

Compatibility

Besides testing that decoding inverses encoding, the compatibility with other implementations is tested by decoding binary files that were created with protobuf-net (C#).

Other Implementations

There are currently multiple Protocol Buffers implementations available. This library was created for the following reasons. Firstly, I wanted to use Data.Text for the string type instead of Data.ByteString as the protocol-buffers library does. Secondly, I wanted to use newtypes for messages with only one field. Finally, I wanted to use simpler data types than the protobuf library does.

For example, the protobuf library uses the following (example from the manual):

data Foo = Foo
  { field1 :: Required 1 (Value Int64)
  , field2 :: Optional 2 (Value Text)
  , field3 :: Repeated 3 (Value Bool)
  } deriving (Generic, Show)

Whereas protobuf-simple would use the following:

data Foo = Foo
  { field1 :: Int64
  , field2 :: Maybe Text
  , field3 :: Seq Bool
  } deriving (Show, Eq, Ord)

Not Implemented

The following Protocol Buffers features are currently not implemented:

License

Protobuf-simple is released under the MIT License.