Safe Haskell | None |
---|---|
Language | Haskell2010 |
Proto3.Suite
Description
Protocol Buffers v3 for Haskell
This package defines tools for working with protocol buffers version 3 in Haskell.
Specifically, it provides:
- Low-level functions for encoding and decoding messages
- Type classes for encoding and decoding messages, and instances for all wire formats identified in the specification
- A higher-level approach to encoding and decoding, based on GHC.Generics
- A way of creating .proto files from Haskell types.
See the Proto3.Suite.Tutorial module for more details.
Synopsis
- toLazyByteString :: Message a => a -> ByteString
- fromByteString :: Message a => ByteString -> Either ParseError a
- fromB64 :: Message a => ByteString -> Either ParseError a
- class Message a where
- encodeMessage :: FieldNumber -> a -> MessageBuilder
- decodeMessage :: FieldNumber -> Parser RawMessage a
- dotProto :: Proxy# a -> [DotProtoField]
- class MessageField a where
- encodeMessageField :: FieldNumber -> a -> MessageBuilder
- decodeMessageField :: Parser RawField a
- protoType :: Proxy# a -> DotProtoField
- class Primitive a where
- encodePrimitive :: FieldNumber -> a -> MessageBuilder
- decodePrimitive :: Parser RawPrimitive a
- primType :: Proxy# a -> DotProtoPrimType
- class HasDefault a where
- newtype FieldNumber = FieldNumber {}
- fieldNumber :: Word64 -> FieldNumber
- message :: (Message a, Named a) => Proxy# a -> DotProtoDefinition
- enum :: (Finite e, Named e) => Proxy# e -> DotProtoDefinition
- data RenderingOptions = RenderingOptions {}
- class Named a where
- class Enum a => Finite a where
- newtype Fixed a = Fixed {
- fixed :: a
- newtype Signed a = Signed {
- signed :: a
- newtype Enumerated a = Enumerated {
- enumerated :: Either Int a
- newtype Nested a = Nested {}
- newtype UnpackedVec a = UnpackedVec {
- unpackedvec :: Vector a
- newtype PackedVec a = PackedVec {}
- newtype NestedVec a = NestedVec {}
- newtype Commented (comment :: Symbol) a = Commented {
- unCommented :: a
- type (//) a (comment :: Symbol) = Commented comment a
- module Proto3.Suite.DotProto
Message Encoding/Decoding
toLazyByteString :: Message a => a -> ByteString Source #
Serialize a message as a lazy ByteString
.
fromByteString :: Message a => ByteString -> Either ParseError a Source #
Parse any message that can be decoded.
fromB64 :: Message a => ByteString -> Either ParseError a Source #
As fromByteString
, except the input bytestring is base64-encoded.
class Message a where Source #
This class captures those types which correspond to protocol buffer messages.
Minimal complete definition
Nothing
Methods
encodeMessage :: FieldNumber -> a -> MessageBuilder Source #
Encode a message
decodeMessage :: FieldNumber -> Parser RawMessage a Source #
Decode a message
dotProto :: Proxy# a -> [DotProtoField] Source #
Generate a .proto message from the type information.
encodeMessage :: (Generic a, GenericMessage (Rep a)) => FieldNumber -> a -> MessageBuilder Source #
Encode a message
decodeMessage :: (Generic a, GenericMessage (Rep a)) => FieldNumber -> Parser RawMessage a Source #
Decode a message
dotProto :: GenericMessage (Rep a) => Proxy# a -> [DotProtoField] Source #
Generate a .proto message from the type information.
Instances
Message Bar Source # | |
Defined in Proto3.Suite.Tutorial Methods encodeMessage :: FieldNumber -> Bar -> MessageBuilder Source # decodeMessage :: FieldNumber -> Parser RawMessage Bar Source # | |
Message Foo Source # | |
Defined in Proto3.Suite.Tutorial Methods encodeMessage :: FieldNumber -> Foo -> MessageBuilder Source # decodeMessage :: FieldNumber -> Parser RawMessage Foo Source # | |
(MessageField k, MessageField v) => Message (k, v) Source # | |
Defined in Proto3.Suite.Class Methods encodeMessage :: FieldNumber -> (k, v) -> MessageBuilder Source # decodeMessage :: FieldNumber -> Parser RawMessage (k, v) Source # dotProto :: Proxy# (k, v) -> [DotProtoField] Source # |
class MessageField a where Source #
This class captures those types which can appear as message fields in
the protocol buffers specification, i.e. Primitive
types, or lists of
Primitive
types
Minimal complete definition
Nothing
Methods
encodeMessageField :: FieldNumber -> a -> MessageBuilder Source #
Encode a message field
decodeMessageField :: Parser RawField a Source #
Decode a message field
encodeMessageField :: (HasDefault a, Primitive a) => FieldNumber -> a -> MessageBuilder Source #
Encode a message field
decodeMessageField :: (HasDefault a, Primitive a) => Parser RawField a Source #
Decode a message field
protoType :: Proxy# a -> DotProtoField Source #
Get the type which represents this type inside another message.
protoType :: Primitive a => Proxy# a -> DotProtoField Source #
Get the type which represents this type inside another message.
Instances
class Primitive a where Source #
This class captures those types which correspond to primitives in the protocol buffers specification.
It should be possible to fully reconstruct values of these types from
a single RawPrimitive
. Notably, then, Nested
is not Primitive
even
though it can be embedded
, since a nested message may by split up over
multiple embedded
fields.
Minimal complete definition
Methods
encodePrimitive :: FieldNumber -> a -> MessageBuilder Source #
Encode a primitive value
decodePrimitive :: Parser RawPrimitive a Source #
Decode a primitive value
primType :: Proxy# a -> DotProtoPrimType Source #
Get the type which represents this type inside another message.
primType :: Named a => Proxy# a -> DotProtoPrimType Source #
Get the type which represents this type inside another message.
Instances
class HasDefault a where Source #
A class for types with default values per the protocol buffers spec.
Minimal complete definition
Nothing
Methods
The default value for this type.
The default value for this type.
Instances
newtype FieldNumber #
A FieldNumber
identifies a field inside a protobufs message.
This library makes no attempt to generate these automatically, or even make sure that field numbers are provided in increasing order. Such things are left to other, higher-level libraries.
Constructors
FieldNumber | |
Fields |
Instances
fieldNumber :: Word64 -> FieldNumber #
Create a FieldNumber
given the (one-based) integer which would label
the field in the corresponding .proto file.
Documentation
message :: (Message a, Named a) => Proxy# a -> DotProtoDefinition Source #
Generate metadata for a message type.
enum :: (Finite e, Named e) => Proxy# e -> DotProtoDefinition Source #
Generate metadata for an enum type.
data RenderingOptions Source #
Options for rendering a .proto
file.
Constructors
RenderingOptions | |
Fields
|
This class captures those types whose names need to appear in .proto files.
It has a default implementation for any data type which is an instance of the
Generic
class, which will extract the name of the type constructor.
Minimal complete definition
Nothing
Methods
nameOf :: IsString string => Proxy# a -> string Source #
Get the name of a type constructor
nameOf :: (IsString string, GenericNamed (Rep a)) => Proxy# a -> string Source #
Get the name of a type constructor
class Enum a => Finite a where Source #
Enumerable types with finitely many values.
This class can be derived whenever a sum type is an instance of Generic
,
and only consists of zero-argument constructors. The derived instance should
be compatible with derived Enum
instances, in the sense that
map (toEnum . fst) enumerate
should enumerate all values of the type without runtime errors.
Minimal complete definition
Nothing
Methods
enumerate :: IsString string => Proxy# a -> [(string, Int)] Source #
Enumerate values of a finite type, along with names of constructors.
enumerate :: (IsString string, GenericFinite (Rep a)) => Proxy# a -> [(string, Int)] Source #
Enumerate values of a finite type, along with names of constructors.
Wire Formats
Fixed
provides a way to encode integers in the fixed-width wire formats.
Instances
Signed
provides a way to encode integers in the signed wire formats.
Instances
newtype Enumerated a Source #
Enumerated
lifts any type with an IsEnum
instance so that it can be encoded
with HasEncoding
.
Constructors
Enumerated | |
Fields
|
Instances
Nested
provides a way to nest protobuf messages within protobuf messages.
Instances
newtype UnpackedVec a Source #
Constructors
UnpackedVec | |
Fields
|
Instances
PackedVec
provides a way to encode packed lists of basic protobuf types into
the wire format.
Instances
Instances
newtype Commented (comment :: Symbol) a Source #
Commented
provides a way to add comments to generated .proto
files.
Constructors
Commented | |
Fields
|
Instances
Functor (Commented comment) Source # | |
Foldable (Commented comment) Source # | |
Defined in Proto3.Suite.Types Methods fold :: Monoid m => Commented comment m -> m # foldMap :: Monoid m => (a -> m) -> Commented comment a -> m # foldr :: (a -> b -> b) -> b -> Commented comment a -> b # foldr' :: (a -> b -> b) -> b -> Commented comment a -> b # foldl :: (b -> a -> b) -> b -> Commented comment a -> b # foldl' :: (b -> a -> b) -> b -> Commented comment a -> b # foldr1 :: (a -> a -> a) -> Commented comment a -> a # foldl1 :: (a -> a -> a) -> Commented comment a -> a # toList :: Commented comment a -> [a] # null :: Commented comment a -> Bool # length :: Commented comment a -> Int # elem :: Eq a => a -> Commented comment a -> Bool # maximum :: Ord a => Commented comment a -> a # minimum :: Ord a => Commented comment a -> a # | |
Traversable (Commented comment) Source # | |
Defined in Proto3.Suite.Types Methods traverse :: Applicative f => (a -> f b) -> Commented comment a -> f (Commented comment b) # sequenceA :: Applicative f => Commented comment (f a) -> f (Commented comment a) # mapM :: Monad m => (a -> m b) -> Commented comment a -> m (Commented comment b) # sequence :: Monad m => Commented comment (m a) -> m (Commented comment a) # | |
Eq a => Eq (Commented comment a) Source # | |
Ord a => Ord (Commented comment a) Source # | |
Defined in Proto3.Suite.Types Methods compare :: Commented comment a -> Commented comment a -> Ordering # (<) :: Commented comment a -> Commented comment a -> Bool # (<=) :: Commented comment a -> Commented comment a -> Bool # (>) :: Commented comment a -> Commented comment a -> Bool # (>=) :: Commented comment a -> Commented comment a -> Bool # max :: Commented comment a -> Commented comment a -> Commented comment a # min :: Commented comment a -> Commented comment a -> Commented comment a # | |
Show a => Show (Commented comment a) Source # | |
Generic (Commented comment a) Source # | |
Semigroup a => Semigroup (Commented comment a) Source # | |
Monoid a => Monoid (Commented comment a) Source # | |
Arbitrary a => Arbitrary (Commented comment a) Source # | |
NFData a => NFData (Commented comment a) Source # | |
Defined in Proto3.Suite.Types | |
(MessageField e, KnownSymbol comments) => MessageField (e // comments) Source # | |
Defined in Proto3.Suite.Class Methods encodeMessageField :: FieldNumber -> (e // comments) -> MessageBuilder Source # decodeMessageField :: Parser RawField (e // comments) Source # protoType :: Proxy# (e // comments) -> DotProtoField Source # | |
type Rep (Commented comment a) Source # | |
Defined in Proto3.Suite.Types |
type (//) a (comment :: Symbol) = Commented comment a Source #
A type operator synonym for Commented
, so that we can write C-style
comments on fields.
AST
module Proto3.Suite.DotProto