proto-lens-0.2.0.1: A lens-based implementation of protocol buffers in Haskell.

Safe HaskellNone
LanguageHaskell98

Data.ProtoLens.Message

Contents

Description

Datatypes for reflection of protocol buffer messages.

Synopsis

Reflection of Messages

class Default msg => Message msg where Source #

Every protocol buffer is an instance of Message. This class enables serialization by providing reflection of all of the fields that may be used by this type.

Minimal complete definition

descriptor

newtype Tag Source #

A tag that identifies a particular field of the message when converting to/from the wire format.

Constructors

Tag 

Fields

Instances

Eq Tag Source # 

Methods

(==) :: Tag -> Tag -> Bool #

(/=) :: Tag -> Tag -> Bool #

Num Tag Source # 

Methods

(+) :: Tag -> Tag -> Tag #

(-) :: Tag -> Tag -> Tag #

(*) :: Tag -> Tag -> Tag #

negate :: Tag -> Tag #

abs :: Tag -> Tag #

signum :: Tag -> Tag #

fromInteger :: Integer -> Tag #

Ord Tag Source # 

Methods

compare :: Tag -> Tag -> Ordering #

(<) :: Tag -> Tag -> Bool #

(<=) :: Tag -> Tag -> Bool #

(>) :: Tag -> Tag -> Bool #

(>=) :: Tag -> Tag -> Bool #

max :: Tag -> Tag -> Tag #

min :: Tag -> Tag -> Tag #

Show Tag Source # 

Methods

showsPrec :: Int -> Tag -> ShowS #

show :: Tag -> String #

showList :: [Tag] -> ShowS #

data MessageDescriptor msg Source #

The description of a particular protocol buffer message type.

Constructors

MessageDescriptor 

Fields

  • fieldsByTag :: Map Tag (FieldDescriptor msg)
     
  • fieldsByTextFormatName :: Map String (FieldDescriptor msg)

    This map is keyed by the name of the field used for text format protos. This is just the field name for every field except for group fields, which use their Message type name in text protos instead of their field name. For example, "optional group Foo" has the field name "foo" but in this map it is stored with the key Foo.

data FieldDescriptor msg where Source #

A description of a specific field of a protocol buffer.

The String parameter is the name of the field from the .proto file, as used in TextFormat, with the same behavior for groups as fieldsByTextFormatName. (Haddock doesn't support per-argument docs for GADTs.)

Constructors

FieldDescriptor :: String -> FieldTypeDescriptor value -> FieldAccessor msg value -> FieldDescriptor msg 

fieldDescriptorName :: FieldDescriptor msg -> String Source #

The original name of the field in the .proto file.

isRequired :: FieldDescriptor msg -> Bool Source #

Whether the given field is required. Specifically, if its FieldAccessor is a Required PlainField.

data FieldAccessor msg value where Source #

A Lens for accessing the value of an individual field in a protocol buffer message.

Constructors

PlainField :: WireDefault value -> Lens' msg value -> FieldAccessor msg value 
OptionalField :: Lens' msg (Maybe value) -> FieldAccessor msg value 
RepeatedField :: Packing -> Lens' msg [value] -> FieldAccessor msg value 
MapField :: (Ord key, Message entry) => Lens' entry key -> Lens' entry value -> Lens' msg (Map key value) -> FieldAccessor msg entry 

data WireDefault value where Source #

The default value (if any) for a PlainField on the wire.

Constructors

Required :: WireDefault value 
Optional :: (FieldDefault value, Eq value) => WireDefault value 

data Packing Source #

How a given repeated field is transmitted on the wire format.

Constructors

Packed 
Unpacked 

class FieldDefault value where Source #

A proto3 field type with an implicit default value.

This is distinct from Default to avoid orphan instances, and because Bool doesn't necessarily have a good Default instance for general usage.

Minimal complete definition

fieldDefault

Methods

fieldDefault :: value Source #

class (Enum a, Bounded a) => MessageEnum a where Source #

A class for protocol buffer enums that enables safe decoding.

Minimal complete definition

maybeToEnum, showEnum, readEnum

Methods

maybeToEnum :: Int -> Maybe a Source #

Convert the given Int to an enum value. Returns Nothing if no corresponding value was defined in the .proto file.

showEnum :: a -> String Source #

Get the name of this enum as defined in the .proto file.

readEnum :: String -> Maybe a Source #

Convert the given String to an enum value. Returns Nothing if no corresponding value was defined in the .proto file.

Building protocol buffers

class Default a where #

A class for types with a default value.

Methods

def :: a #

The default value for this type.

Instances

Default Double 

Methods

def :: Double #

Default Float 

Methods

def :: Float #

Default Int 

Methods

def :: Int #

Default Int8 

Methods

def :: Int8 #

Default Int16 

Methods

def :: Int16 #

Default Int32 

Methods

def :: Int32 #

Default Int64 

Methods

def :: Int64 #

Default Integer 

Methods

def :: Integer #

Default Ordering 

Methods

def :: Ordering #

Default Word 

Methods

def :: Word #

Default Word8 

Methods

def :: Word8 #

Default Word16 

Methods

def :: Word16 #

Default Word32 

Methods

def :: Word32 #

Default Word64 

Methods

def :: Word64 #

Default () 

Methods

def :: () #

Default CShort 

Methods

def :: CShort #

Default CUShort 

Methods

def :: CUShort #

Default CInt 

Methods

def :: CInt #

Default CUInt 

Methods

def :: CUInt #

Default CLong 

Methods

def :: CLong #

Default CULong 

Methods

def :: CULong #

Default CLLong 

Methods

def :: CLLong #

Default CULLong 

Methods

def :: CULLong #

Default CFloat 

Methods

def :: CFloat #

Default CDouble 

Methods

def :: CDouble #

Default CPtrdiff 

Methods

def :: CPtrdiff #

Default CSize 

Methods

def :: CSize #

Default CSigAtomic 

Methods

def :: CSigAtomic #

Default CClock 

Methods

def :: CClock #

Default CTime 

Methods

def :: CTime #

Default CUSeconds 

Methods

def :: CUSeconds #

Default CSUSeconds 

Methods

def :: CSUSeconds #

Default CIntPtr 

Methods

def :: CIntPtr #

Default CUIntPtr 

Methods

def :: CUIntPtr #

Default CIntMax 

Methods

def :: CIntMax #

Default CUIntMax 

Methods

def :: CUIntMax #

Default All 

Methods

def :: All #

Default Any 

Methods

def :: Any #

Default [a] 

Methods

def :: [a] #

Default (Maybe a) 

Methods

def :: Maybe a #

Integral a => Default (Ratio a) 

Methods

def :: Ratio a #

Default a => Default (IO a) 

Methods

def :: IO a #

(Default a, RealFloat a) => Default (Complex a) 

Methods

def :: Complex a #

Default a => Default (Dual a) 

Methods

def :: Dual a #

Default (Endo a) 

Methods

def :: Endo a #

Num a => Default (Sum a) 

Methods

def :: Sum a #

Num a => Default (Product a) 

Methods

def :: Product a #

Default (First a) 

Methods

def :: First a #

Default (Last a) 

Methods

def :: Last a #

Default r => Default (e -> r) 

Methods

def :: e -> r #

(Default a, Default b) => Default (a, b) 

Methods

def :: (a, b) #

(Default a, Default b, Default c) => Default (a, b, c) 

Methods

def :: (a, b, c) #

(Default a, Default b, Default c, Default d) => Default (a, b, c, d) 

Methods

def :: (a, b, c, d) #

(Default a, Default b, Default c, Default d, Default e) => Default (a, b, c, d, e) 

Methods

def :: (a, b, c, d, e) #

(Default a, Default b, Default c, Default d, Default e, Default f) => Default (a, b, c, d, e, f) 

Methods

def :: (a, b, c, d, e, f) #

(Default a, Default b, Default c, Default d, Default e, Default f, Default g) => Default (a, b, c, d, e, f, g) 

Methods

def :: (a, b, c, d, e, f, g) #

build :: Default a => (a -> a) -> a Source #

Utility function for building a message from a default value. For example:

instance Default A where ...
x, y :: Lens' A Int
m :: A
m = build ((x .~ 5) . (y .~ 7))

Utilities for constructing protocol buffer lenses

maybeLens :: b -> Lens' (Maybe b) b Source #

A helper lens for accessing optional fields. This is used as part of code generation, and should generally not be needed explicitly.

Note that maybeLens does not satisfy the lens laws, which expect that set l (view l x) == x. For example,

set (maybeLens 'a') (view (maybeLens 'a') Nothing) == Just 'a'

However, this is the behavior generally expected by users, and only matters if we're explicitly checking whether a field is set.

Internal utilities for parsing protocol buffers

reverseRepeatedFields :: Map k (FieldDescriptor msg) -> msg -> msg Source #

Reverse every repeated (list) field in the message.

During parsing, we store fields temporarily in reverse order, and then un-reverse them at the end. This helps avoid the quadratic blowup from repeatedly appending to lists. TODO: Benchmark how much of a problem this is in practice, and whether it's still a net win for small protobufs. If we decide on it more permanently, consider moving it to a more internal module.