Safe Haskell | None |
---|---|
Language | Haskell98 |
Text.ProtocolBuffers exposes the client API. This merely re-exports parts of the other modules in protocol-buffers. The exposed parts are:
import Text.ProtocolBuffers.Basic ( Seq,isValidUTF8,toUtf8,utf8,Utf8(Utf8),Int32,Int64,Word32,Word64 , WireTag,FieldId,WireType,FieldType,EnumCode,WireSize , Mergeable(mergeAppend,mergeConcat),Default(defaultValue)) import Text.ProtocolBuffers.Extensions ( Key,ExtKey(getExt,putExt,clearExt),MessageAPI(getVal,isSet) , getKeyFieldId,getKeyFieldType,getKeyDefaultValue) import Text.ProtocolBuffers.Identifiers import Text.ProtocolBuffers.Reflections ( ReflectDescriptor(..),ReflectEnum(..),ProtoName(..),HsDefault(..),EnumInfoApp , KeyInfo,FieldInfo(..),DescriptorInfo(..),EnumInfo(..),ProtoInfo(..),makePNF ) import Text.ProtocolBuffers.TextMessage ( messagePutText, messageGetText ) import Text.ProtocolBuffers.WireMessage ( Wire,Put,Get,runPut,runGet,runGetOnLazy , messageSize,messagePut,messageGet,messagePutM,messageGetM , messageWithLengthSize,messageWithLengthPut,messageWithLengthGet,messageWithLengthPutM,messageWithLengthGetM , messageAsFieldSize,messageAsFieldPutM,messageAsFieldGetM)
The message serialization is taken care of by WireMessage
operations, especially messagePut
and messageGet
. The
MessageAPI
provides the useful polymorphic getVal
and isSet
where getVal
looks up default values and also works with extension
keys. The Utf8
newtype is used to indicate the format in the
underlying lazy ByteString
. Messages and values can be combined
with the right-biased Mergeable
operations. The mergeEmpty
should
not be used as required values are filled in with undefined errors,
please use defaultValue
instead.
The Utf8 type is a newtype of the Lazy ByteString. It can be safely
constructed by checking for errors with toUtf8
, which returns 'Left
Int' indicating the index where an error is detected. It can be
deconstructed with utf8
.
Synopsis
- data Int32
- data Int64
- data Word32
- data Word64
- data Seq a
- class Default a where
- defaultValue :: a
- class Default a => Mergeable a where
- mergeAppend :: a -> a -> a
- mergeConcat :: Foldable t => t a -> a
- type WireSize = Int64
- data EnumCode
- data FieldType
- data WireType
- data FieldId
- data WireTag
- newtype Utf8 = Utf8 ByteString
- utf8 :: Utf8 -> ByteString
- isValidUTF8 :: ByteString -> Maybe Int
- toUtf8 :: ByteString -> Either Int Utf8
- class MessageAPI msg a b | msg a -> b where
- class ExtKey c where
- data Key c msg v
- getKeyFieldId :: Key c msg v -> FieldId
- getKeyFieldType :: Key c msg v -> FieldType
- getKeyDefaultValue :: Key c msg v -> v
- module Text.ProtocolBuffers.Identifiers
- class ReflectDescriptor m where
- getMessageInfo :: m -> GetMessageInfo
- reflectDescriptorInfo :: m -> DescriptorInfo
- class ReflectEnum e where
- reflectEnum :: EnumInfoApp e
- reflectEnumInfo :: e -> EnumInfo
- parentOfEnum :: e -> Maybe DescriptorInfo
- type EnumInfoApp e = [(EnumCode, String, e)]
- data EnumInfo = EnumInfo {
- enumName :: ProtoName
- enumFilePath :: [FilePath]
- enumValues :: [(EnumCode, String)]
- enumJsonInstances :: Bool
- data HsDefault
- data FieldInfo = FieldInfo {
- fieldName :: ProtoFName
- fieldNumber :: FieldId
- wireTag :: WireTag
- packedTag :: Maybe (WireTag, WireTag)
- wireTagLength :: WireSize
- isPacked :: Bool
- isRequired :: Bool
- canRepeat :: Bool
- mightPack :: Bool
- typeCode :: FieldType
- typeName :: Maybe ProtoName
- hsRawDefault :: Maybe ByteString
- hsDefault :: Maybe HsDefault
- type KeyInfo = (ProtoName, FieldInfo)
- data DescriptorInfo = DescriptorInfo {
- descName :: ProtoName
- descFilePath :: [FilePath]
- isGroup :: Bool
- fields :: Seq FieldInfo
- descOneofs :: Seq OneofInfo
- keys :: Seq KeyInfo
- extRanges :: [(FieldId, FieldId)]
- knownKeys :: Seq FieldInfo
- storeUnknown :: Bool
- lazyFields :: Bool
- makeLenses :: Bool
- jsonInstances :: Bool
- data ProtoInfo = ProtoInfo {
- protoMod :: ProtoName
- protoFilePath :: [FilePath]
- protoSource :: FilePath
- extensionKeys :: Seq KeyInfo
- messages :: [DescriptorInfo]
- enums :: [EnumInfo]
- oneofs :: [OneofInfo]
- knownKeyMap :: Map ProtoName (Seq FieldInfo)
- data ProtoName = ProtoName {
- protobufName :: FIName Utf8
- haskellPrefix :: [MName String]
- parentModule :: [MName String]
- baseName :: MName String
- makePNF :: ByteString -> [String] -> [String] -> String -> ProtoName
- messagePutText :: TextMsg a => a -> String
- messageGetText :: (TextMsg a, Stream s Identity Char) => s -> Either String a
- runPut :: Put -> ByteString
- type Put = PutM ()
- data Get a
- runGet :: Get a -> ByteString -> Result a
- class Wire b
- messageSize :: (ReflectDescriptor msg, Wire msg) => msg -> WireSize
- messageWithLengthSize :: (ReflectDescriptor msg, Wire msg) => msg -> WireSize
- messageAsFieldSize :: (ReflectDescriptor msg, Wire msg) => FieldId -> msg -> WireSize
- messagePut :: (ReflectDescriptor msg, Wire msg) => msg -> ByteString
- messageWithLengthPut :: (ReflectDescriptor msg, Wire msg) => msg -> ByteString
- messagePutM :: (ReflectDescriptor msg, Wire msg) => msg -> Put
- messageWithLengthPutM :: (ReflectDescriptor msg, Wire msg) => msg -> Put
- messageAsFieldPutM :: (ReflectDescriptor msg, Wire msg) => FieldId -> msg -> Put
- messageGet :: (ReflectDescriptor msg, Wire msg) => ByteString -> Either String (msg, ByteString)
- messageWithLengthGet :: (ReflectDescriptor msg, Wire msg) => ByteString -> Either String (msg, ByteString)
- messageGetM :: (ReflectDescriptor msg, Wire msg) => Get msg
- messageWithLengthGetM :: (ReflectDescriptor msg, Wire msg) => Get msg
- messageAsFieldGetM :: (ReflectDescriptor msg, Wire msg) => Get (FieldId, msg)
- runGetOnLazy :: Get r -> ByteString -> Either String (r, ByteString)
- module Text.ProtocolBuffers.ProtoJSON
Documentation
32-bit signed integer type
Instances
64-bit signed integer type
Instances
32-bit unsigned integer type
Instances
64-bit unsigned integer type
Instances
General-purpose finite sequences.
Instances
Monad Seq | |
Functor Seq | |
MonadFix Seq | Since: containers-0.5.11 |
Defined in Data.Sequence.Internal | |
Applicative Seq | Since: containers-0.5.4 |
Foldable Seq | |
Defined in Data.Sequence.Internal fold :: Monoid m => Seq m -> m # foldMap :: Monoid m => (a -> m) -> Seq a -> m # foldr :: (a -> b -> b) -> b -> Seq a -> b # foldr' :: (a -> b -> b) -> b -> Seq a -> b # foldl :: (b -> a -> b) -> b -> Seq a -> b # foldl' :: (b -> a -> b) -> b -> Seq a -> b # foldr1 :: (a -> a -> a) -> Seq a -> a # foldl1 :: (a -> a -> a) -> Seq a -> a # elem :: Eq a => a -> Seq a -> Bool # maximum :: Ord a => Seq a -> a # | |
Traversable Seq | |
ToJSON1 Seq | |
Defined in Data.Aeson.Types.ToJSON | |
FromJSON1 Seq | |
Alternative Seq | Since: containers-0.5.4 |
MonadPlus Seq | |
Eq1 Seq | Since: containers-0.5.9 |
Ord1 Seq | Since: containers-0.5.9 |
Defined in Data.Sequence.Internal | |
Read1 Seq | Since: containers-0.5.9 |
Defined in Data.Sequence.Internal | |
Show1 Seq | Since: containers-0.5.9 |
MonadZip Seq |
|
UnzipWith Seq | |
Defined in Data.Sequence.Internal unzipWith' :: (x -> (a, b)) -> Seq x -> (Seq a, Seq b) | |
ExtKey Seq Source # | |
MessageAPI msg (msg -> Seq a) (Seq a) Source # | |
Default v => MessageAPI msg (Key Seq msg v) (Seq v) Source # | |
IsList (Seq a) | |
Eq a => Eq (Seq a) | |
Data a => Data (Seq a) | |
Defined in Data.Sequence.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Seq a -> c (Seq a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Seq a) # dataTypeOf :: Seq a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Seq a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Seq a)) # gmapT :: (forall b. Data b => b -> b) -> Seq a -> Seq a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Seq a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Seq a -> r # gmapQ :: (forall d. Data d => d -> u) -> Seq a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Seq a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) # | |
Ord a => Ord (Seq a) | |
Read a => Read (Seq a) | |
Show a => Show (Seq a) | |
a ~ Char => IsString (Seq a) | Since: containers-0.5.7 |
Defined in Data.Sequence.Internal fromString :: String -> Seq a # | |
Semigroup (Seq a) | Since: containers-0.5.7 |
Monoid (Seq a) | |
ToJSON a => ToJSON (Seq a) | |
Defined in Data.Aeson.Types.ToJSON | |
FromJSON a => FromJSON (Seq a) | |
NFData a => NFData (Seq a) | |
Defined in Data.Sequence.Internal | |
Default (Seq a) Source # | |
Defined in Text.ProtocolBuffers.Basic defaultValue :: Seq a Source # | |
Mergeable (Seq a) Source # | |
Defined in Text.ProtocolBuffers.Basic | |
TextType a => TextType (Seq a) Source # | |
type Item (Seq a) | |
Defined in Data.Sequence.Internal |
class Default a where Source #
The Default class has the default-default values of types. See
http://code.google.com/apis/protocolbuffers/docs/proto.html#optional
and also note that Enum
types have a defaultValue
that is the
first one in the .proto
file (there is always at least one
value). Instances of this for messages hold any default value
defined in the .proto
file. defaultValue
is where the
MessageAPI
function getVal
looks when an optional field is not
set.
defaultValue :: a Source #
The defaultValue
is never undefined or an error to evalute.
This makes it much more useful compared to mergeEmpty
. In a
default message all Optional field values are set to Nothing
and Repeated field values are empty.
Instances
class Default a => Mergeable a where Source #
The Mergeable
class is not a Monoid
, mergeEmpty
is not a
left or right unit like mempty
. The default mergeAppend
is to
take the second parameter and discard the first one. The
mergeConcat
defaults to foldl
associativity.
NOTE: mergeEmpty
has been removed in protocol buffers version 2.
Use defaultValue
instead. New strict fields would mean that required
fields in messages will be automatic errors with mergeEmpty
.
Nothing
mergeAppend :: a -> a -> a Source #
mergeAppend
is the right-biased merge of two values. A
message (or group) is merged recursively. Required field are
always taken from the second message. Optional field values are
taken from the most defined message or the second message if
both are set. Repeated fields have the sequences concatenated.
Note that strings and bytes are NOT concatenated.
mergeConcat :: Foldable t => t a -> a Source #
mergeConcat
is F.foldl mergeAppend defaultValue
and this
default definition is not overridden in any of the code except
for the (Seq a) instance.
Instances
type WireSize = Int64 Source #
WireSize
is the Int64 size type associated with the lazy
bytestrings used in the Put
and Get
monads.
EnumCode
is the Int32 assoicated with a
EnumValueDescriptorProto and is in the range 0 to 2^31-1.
Instances
Bounded EnumCode Source # | |
Eq EnumCode Source # | |
Data EnumCode Source # | |
Defined in Text.ProtocolBuffers.Basic gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EnumCode -> c EnumCode # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EnumCode # toConstr :: EnumCode -> Constr # dataTypeOf :: EnumCode -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EnumCode) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EnumCode) # gmapT :: (forall b. Data b => b -> b) -> EnumCode -> EnumCode # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EnumCode -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EnumCode -> r # gmapQ :: (forall d. Data d => d -> u) -> EnumCode -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> EnumCode -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> EnumCode -> m EnumCode # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EnumCode -> m EnumCode # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EnumCode -> m EnumCode # | |
Num EnumCode Source # | |
Ord EnumCode Source # | |
Defined in Text.ProtocolBuffers.Basic | |
Read EnumCode Source # | |
Show EnumCode Source # | |
FieldType
is the integer associated with the
FieldDescriptorProto's Type. The allowed range is currently 1 to
18, as shown below (excerpt from descritor.proto)
// 0 is reserved for errors. // Order is weird for historical reasons. TYPE_DOUBLE = 1; TYPE_FLOAT = 2; TYPE_INT64 = 3; // Not ZigZag encoded. Negative numbers // take 10 bytes. Use TYPE_SINT64 if negative // values are likely. TYPE_UINT64 = 4; TYPE_INT32 = 5; // Not ZigZag encoded. Negative numbers // take 10 bytes. Use TYPE_SINT32 if negative // values are likely. TYPE_FIXED64 = 6; TYPE_FIXED32 = 7; TYPE_BOOL = 8; TYPE_STRING = 9; TYPE_GROUP = 10; // Tag-delimited aggregate. TYPE_MESSAGE = 11; // Length-delimited aggregate. // New in version 2. TYPE_BYTES = 12; TYPE_UINT32 = 13; TYPE_ENUM = 14; TYPE_SFIXED32 = 15; TYPE_SFIXED64 = 16; TYPE_SINT32 = 17; // Uses ZigZag encoding. TYPE_SINT64 = 18; // Uses ZigZag encoding.
Instances
WireType
is the 3 bit wire encoding value, and is currently in
the range 0 to 5, leaving 6 and 7 currently invalid.
- 0 Varint : int32, int64, uint32, uint64, sint32, sint64, bool, enum
- 1 64-bit : fixed64, sfixed64, double
- 2 Length-delimited : string, bytes, embedded messages
- 3 Start group : groups (deprecated)
- 4 End group : groups (deprecated)
- 5 32-bit : fixed32, sfixed32, float
Instances
Bounded WireType Source # | |
Enum WireType Source # | |
Defined in Text.ProtocolBuffers.Basic | |
Eq WireType Source # | |
Data WireType Source # | |
Defined in Text.ProtocolBuffers.Basic gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WireType -> c WireType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WireType # toConstr :: WireType -> Constr # dataTypeOf :: WireType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c WireType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WireType) # gmapT :: (forall b. Data b => b -> b) -> WireType -> WireType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WireType -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WireType -> r # gmapQ :: (forall d. Data d => d -> u) -> WireType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> WireType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> WireType -> m WireType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WireType -> m WireType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WireType -> m WireType # | |
Num WireType Source # | |
Ord WireType Source # | |
Defined in Text.ProtocolBuffers.Basic | |
Read WireType Source # | |
Show WireType Source # | |
FieldId
is the field number which can be in the range 1 to
2^29-1 but the value from 19000 to 19999 are forbidden (so sayeth
Google).
Instances
Bounded FieldId Source # | |
Enum FieldId Source # | |
Eq FieldId Source # | |
Data FieldId Source # | |
Defined in Text.ProtocolBuffers.Basic gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldId -> c FieldId # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FieldId # toConstr :: FieldId -> Constr # dataTypeOf :: FieldId -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FieldId) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FieldId) # gmapT :: (forall b. Data b => b -> b) -> FieldId -> FieldId # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldId -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldId -> r # gmapQ :: (forall d. Data d => d -> u) -> FieldId -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldId -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldId -> m FieldId # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldId -> m FieldId # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldId -> m FieldId # | |
Num FieldId Source # | |
Ord FieldId Source # | |
Read FieldId Source # | |
Show FieldId Source # | |
Ix FieldId Source # | |
Defined in Text.ProtocolBuffers.Basic |
WireTag
is the 32 bit value with the upper 29 bits being the
FieldId
and the lower 3 bits being the WireType
Instances
Utf8
is used to mark ByteString
values that (should) contain
valid utf8 encoded strings. This type is used to represent
TYPE_STRING
values.
Instances
utf8 :: Utf8 -> ByteString Source #
isValidUTF8 :: ByteString -> Maybe Int Source #
class MessageAPI msg a b | msg a -> b where Source #
getVal :: msg -> a -> b Source #
Access data in a message. The first argument is always the message. The second argument can be one of 4 categories.
- The field name of a required field acts a simple retrieval of the data from the message.
- The field name of an optional field will retreive the data if it is set or lookup the default value if it is not set.
- The field name of a repeated field always retrieves the
(possibly empty)
Seq
of values. - A Key for an optional or repeated value will act as the field name does above, but if there is a type mismatch or parse error it will use the defaultValue for optional types and an empty sequence for repeated types.
isSet :: msg -> a -> Bool Source #
Check whether data is present in the message.
- Required fields always return
True
. - Optional fields return whether a value is present.
- Repeated field return
False
if there are no values, otherwise they returnTrue
. - Keys return as optional or repeated, but checks only if the field # is present. This assumes that there are no collisions where more that one key refers to the same field number of this message type.
Instances
MessageAPI msg (msg -> Word64) Word64 Source # | |
MessageAPI msg (msg -> Word32) Word32 Source # | |
MessageAPI msg (msg -> Int64) Int64 Source # | |
MessageAPI msg (msg -> Int32) Int32 Source # | |
MessageAPI msg (msg -> Float) Float Source # | |
MessageAPI msg (msg -> Double) Double Source # | |
MessageAPI msg (msg -> Utf8) Utf8 Source # | |
MessageAPI msg (msg -> ByteString) ByteString Source # | |
Defined in Text.ProtocolBuffers.Extensions getVal :: msg -> (msg -> ByteString) -> ByteString Source # isSet :: msg -> (msg -> ByteString) -> Bool Source # | |
(Default msg, Default a) => MessageAPI msg (msg -> Maybe a) a Source # | |
MessageAPI msg (msg -> Seq a) (Seq a) Source # | |
Default v => MessageAPI msg (Key Maybe msg v) v Source # | |
Default v => MessageAPI msg (Key Seq msg v) (Seq v) Source # | |
The ExtKey
class has three functions for user of the API:
putExt
, getExt
, and clearExt
. The wireGetKey
is used in
generated code.
There are two instances of this class, Maybe
for optional message
fields and Seq
for repeated message fields. This class allows
for uniform treatment of these two kinds of extension fields.
putExt :: Key c msg v -> c v -> msg -> msg Source #
Change or clear the value of a key in a message. Passing
Nothing
with an optional key or an empty Seq
with a repeated
key clears the value. This function thus maintains the invariant
that having a field number in the ExtField
map means that the
field is set and not empty.
This should be only way to set the contents of a extension field.
getExt :: Key c msg v -> msg -> Either String (c v) Source #
Access the key in the message. Optional have type (Key Maybe
msg v)
and return type (Maybe v)
while repeated fields have
type (Key Seq msg v)
and return type (Seq v)
.
There are a few sources of errors with the lookup of the key:
- It may find unparsed bytes from loading the message.
getExt
will attempt to parse the bytes as the key's value type, and may fail. The parsing is done with theparseWireExt
method (which is not exported to user API). - The wrong optional-key versus repeated-key type is a failure
- The wrong type of the value might be found in the map and
- cause a failure
The failures above should only happen if two different keys are used with the same field number.
The Key
data type is used with the ExtKey
class to put, get,
and clear external fields of messages. The Key
can also be used
with the MessagesAPI
to get a possibly default value and to check
whether a key has been set in a message.
The Key
type (opaque to the user) has a phantom type of Maybe
or Seq that corresponds to Optional or Repeated fields. And a
second phantom type that matches the message type it must be used
with. The third type parameter corresponds to the Haskell value
type.
The Key
is a GADT that puts all the needed class instances into
scope. The actual content is the FieldId
( numeric key), the
FieldType
(for sanity checks), and Maybe v
(a non-standard
default value).
When code is generated all of the known keys are taken into account in the deserialization from the wire. Unknown extension fields are read as a collection of raw byte sequences. If a key is then presented it will be used to parse the bytes.
There is no guarantee for what happens if two Keys disagree about
the type of a field; in particular there may be undefined values
and runtime errors. The data constructor for Key
has to be
exported to the generated code, but is not exposed to the user by
Text.ProtocolBuffers.
getKeyFieldId :: Key c msg v -> FieldId Source #
This allows reflection, in this case it gives the numerical
FieldId
of the key, from 1 to 2^29-1 (excluding 19,000 through
19,999).
getKeyFieldType :: Key c msg v -> FieldType Source #
This allows reflection, in this case it gives the FieldType
enumeration value (1 to 18) of the
Text.DescriptorProtos.FieldDescriptorProto.Type of the field.
getKeyDefaultValue :: Key c msg v -> v Source #
This will return the default value for a given Key
, which is
set in the '.proto' file, or if unset it is the defaultValue
of
that type.
class ReflectDescriptor m where Source #
getMessageInfo :: m -> GetMessageInfo Source #
This is obtained via read
on the stored show
output of the DescriptorInfo
in
the module file. It is used in getting messages from the wire.
Must not inspect argument
reflectDescriptorInfo Source #
:: m | |
-> DescriptorInfo | Must not inspect argument |
class ReflectEnum e where Source #
reflectEnum :: EnumInfoApp e Source #
:: e | |
-> EnumInfo | Must not inspect argument |
:: e | |
-> Maybe DescriptorInfo | Must not inspect argument |
type EnumInfoApp e = [(EnumCode, String, e)] Source #
EnumInfo | |
|
Instances
Eq EnumInfo Source # | |
Data EnumInfo Source # | |
Defined in Text.ProtocolBuffers.Reflections gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EnumInfo -> c EnumInfo # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EnumInfo # toConstr :: EnumInfo -> Constr # dataTypeOf :: EnumInfo -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EnumInfo) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EnumInfo) # gmapT :: (forall b. Data b => b -> b) -> EnumInfo -> EnumInfo # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EnumInfo -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EnumInfo -> r # gmapQ :: (forall d. Data d => d -> u) -> EnumInfo -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> EnumInfo -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> EnumInfo -> m EnumInfo # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EnumInfo -> m EnumInfo # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EnumInfo -> m EnumInfo # | |
Ord EnumInfo Source # | |
Defined in Text.ProtocolBuffers.Reflections | |
Read EnumInfo Source # | |
Show EnumInfo Source # | |
HsDefault
stores the parsed default from the proto file in a
form that will make a nice literal in the
Language.Haskell.Exts.Syntax code generation by hprotoc
.
Note that Utf8 labeled byte sequences have been stripped to just
ByteString
here as this is sufficient for code generation.
On 25 August 2010 20:12, George van den Driessche georgevdd@google.com sent Chris Kuklewicz a patch to MakeReflections.parseDefEnum to ensure that HsDef'Enum holds the mangled form of the name.
HsDef'Bool Bool | |
HsDef'ByteString ByteString | |
HsDef'RealFloat SomeRealFloat | |
HsDef'Integer Integer | |
HsDef'Enum String |
Instances
Eq HsDefault Source # | |
Data HsDefault Source # | |
Defined in Text.ProtocolBuffers.Reflections gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsDefault -> c HsDefault # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsDefault # toConstr :: HsDefault -> Constr # dataTypeOf :: HsDefault -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsDefault) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsDefault) # gmapT :: (forall b. Data b => b -> b) -> HsDefault -> HsDefault # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDefault -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDefault -> r # gmapQ :: (forall d. Data d => d -> u) -> HsDefault -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDefault -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDefault -> m HsDefault # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDefault -> m HsDefault # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDefault -> m HsDefault # | |
Ord HsDefault Source # | |
Defined in Text.ProtocolBuffers.Reflections | |
Read HsDefault Source # | |
Show HsDefault Source # | |
FieldInfo | |
|
Instances
Eq FieldInfo Source # | |
Data FieldInfo Source # | |
Defined in Text.ProtocolBuffers.Reflections gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldInfo -> c FieldInfo # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FieldInfo # toConstr :: FieldInfo -> Constr # dataTypeOf :: FieldInfo -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FieldInfo) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FieldInfo) # gmapT :: (forall b. Data b => b -> b) -> FieldInfo -> FieldInfo # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldInfo -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldInfo -> r # gmapQ :: (forall d. Data d => d -> u) -> FieldInfo -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldInfo -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldInfo -> m FieldInfo # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldInfo -> m FieldInfo # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldInfo -> m FieldInfo # | |
Ord FieldInfo Source # | |
Defined in Text.ProtocolBuffers.Reflections | |
Read FieldInfo Source # | |
Show FieldInfo Source # | |
data DescriptorInfo Source #
DescriptorInfo | |
|
Instances
ProtoInfo | |
|
Instances
Eq ProtoInfo Source # | |
Data ProtoInfo Source # | |
Defined in Text.ProtocolBuffers.Reflections gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ProtoInfo -> c ProtoInfo # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ProtoInfo # toConstr :: ProtoInfo -> Constr # dataTypeOf :: ProtoInfo -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ProtoInfo) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ProtoInfo) # gmapT :: (forall b. Data b => b -> b) -> ProtoInfo -> ProtoInfo # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ProtoInfo -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ProtoInfo -> r # gmapQ :: (forall d. Data d => d -> u) -> ProtoInfo -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ProtoInfo -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ProtoInfo -> m ProtoInfo # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ProtoInfo -> m ProtoInfo # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ProtoInfo -> m ProtoInfo # | |
Ord ProtoInfo Source # | |
Defined in Text.ProtocolBuffers.Reflections | |
Read ProtoInfo Source # | |
Show ProtoInfo Source # | |
This is fully qualified name data type for code generation. The
haskellPrefix
was possibly specified on the hprotoc
command
line. The parentModule
is a combination of the module prefix
from the '.proto' file and any nested levels of definition.
The name components are likely to have been mangled to ensure the
baseName
started with an uppercase letter, in ['A'..'Z']
.
ProtoName | |
|
Instances
Eq ProtoName Source # | |
Data ProtoName Source # | |
Defined in Text.ProtocolBuffers.Reflections gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ProtoName -> c ProtoName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ProtoName # toConstr :: ProtoName -> Constr # dataTypeOf :: ProtoName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ProtoName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ProtoName) # gmapT :: (forall b. Data b => b -> b) -> ProtoName -> ProtoName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ProtoName -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ProtoName -> r # gmapQ :: (forall d. Data d => d -> u) -> ProtoName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ProtoName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ProtoName -> m ProtoName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ProtoName -> m ProtoName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ProtoName -> m ProtoName # | |
Ord ProtoName Source # | |
Defined in Text.ProtocolBuffers.Reflections | |
Read ProtoName Source # | |
Show ProtoName Source # | |
makePNF :: ByteString -> [String] -> [String] -> String -> ProtoName Source #
makePNF
is used by the generated code to create a ProtoName with less newtype noise.
messagePutText :: TextMsg a => a -> String Source #
This writes message as text-format protobuf to Lexeme
messageGetText :: (TextMsg a, Stream s Identity Char) => s -> Either String a Source #
This reads message as text-format protobuf from any Parsec-compatible source. Input must be completely consumed.
runPut :: Put -> ByteString #
Run the PutM
monad with a serialiser
The Wire
class is for internal use, and may change. If there
is a mis-match between the FieldType
and the type of b
then you
will get a failure at runtime.
Users should stick to the message functions defined in Text.ProtocolBuffers.WireMessage and exported to use user by Text.ProtocolBuffers. These are less likely to change.
Instances
Wire Bool Source # | |
Wire Double Source # | |
Defined in Text.ProtocolBuffers.WireMessage | |
Wire Float Source # | |
Wire Int Source # | |
Wire Int32 Source # | |
Wire Int64 Source # | |
Wire Word32 Source # | |
Defined in Text.ProtocolBuffers.WireMessage | |
Wire Word64 Source # | |
Defined in Text.ProtocolBuffers.WireMessage | |
Wire ByteString Source # | |
Defined in Text.ProtocolBuffers.WireMessage wireSize :: FieldType -> ByteString -> WireSize Source # wirePut :: FieldType -> ByteString -> Put Source # wirePutWithSize :: FieldType -> ByteString -> PutM WireSize Source # wireGet :: FieldType -> Get ByteString Source # wireGetPacked :: FieldType -> Get (Seq ByteString) Source # | |
Wire Utf8 Source # | |
messageSize :: (ReflectDescriptor msg, Wire msg) => msg -> WireSize Source #
This computes the size of the message's fields with tags on the wire with no initial tag or length (in bytes). This is also the length of the message as placed between group start and stop tags.
messageWithLengthSize :: (ReflectDescriptor msg, Wire msg) => msg -> WireSize Source #
This computes the size of the message fields as in messageSize
and add the length of the encoded size to the total. Thus this is
the the length of the message including the encoded length header,
but without any leading tag.
messageAsFieldSize :: (ReflectDescriptor msg, Wire msg) => FieldId -> msg -> WireSize Source #
This computes the size of the messageWithLengthSize
and then
adds the length an initial tag with the given FieldId
.
messagePut :: (ReflectDescriptor msg, Wire msg) => msg -> ByteString Source #
This is runPut
applied to messagePutM
. It result in a
ByteString
with a length of messageSize
bytes.
messageWithLengthPut :: (ReflectDescriptor msg, Wire msg) => msg -> ByteString Source #
This is runPut
applied to messageWithLengthPutM
. It results
in a ByteString
with a length of messageWithLengthSize
bytes.
messagePutM :: (ReflectDescriptor msg, Wire msg) => msg -> Put Source #
messageWithLengthPutM :: (ReflectDescriptor msg, Wire msg) => msg -> Put Source #
messageAsFieldPutM :: (ReflectDescriptor msg, Wire msg) => FieldId -> msg -> Put Source #
messageGet :: (ReflectDescriptor msg, Wire msg) => ByteString -> Either String (msg, ByteString) Source #
This consumes the ByteString
to decode a message. It assumes
the ByteString
is merely a sequence of the tagged fields of the
message, and consumes until a group stop tag is detected or the
entire input is consumed. Any ByteString
past the end of the
stop tag is returned as well.
This is runGetOnLazy
applied to messageGetM
.
messageWithLengthGet :: (ReflectDescriptor msg, Wire msg) => ByteString -> Either String (msg, ByteString) Source #
This runGetOnLazy
applied to messageWithLengthGetM
.
This first reads the encoded length of the message and will then
succeed when it has consumed precisely this many additional bytes.
The ByteString
after this point will be returned.
messageGetM :: (ReflectDescriptor msg, Wire msg) => Get msg Source #
This reads the tagged message fields until the stop tag or the end of input is reached.
This is actually wireGet 10 msg
messageWithLengthGetM :: (ReflectDescriptor msg, Wire msg) => Get msg Source #
This reads the encoded message length and then the message.
This is actually wireGet 11 msg
messageAsFieldGetM :: (ReflectDescriptor msg, Wire msg) => Get (FieldId, msg) Source #
runGetOnLazy :: Get r -> ByteString -> Either String (r, ByteString) Source #
This is like runGet
, without the ability to pass in more input
beyond the initial ByteString. Thus the ByteString
argument is
taken to be the entire input. To be able to incrementally feed in
more input you should use runGet
and respond to Partial
differently.