| Safe Haskell | None | 
|---|---|
| Language | Haskell98 | 
Text.ProtocolBuffers.Extensions
Description
The Extensions module contributes two main things.  The first
 is the definition and implementation of extensible message
 features.  This means that the ExtField data type is exported but
 its constructor is (in an ideal world) hidden.
This first part also includes the keys for the extension fields:
 the Key data type.  These are typically defined in code generated
 by hprotoc from '.proto' file definitions.
The second main part is the MessageAPI class which defines
 getVal and isSet.  These allow uniform access to normal and
 extension fields for users.
Access to extension fields is strictly through keys. There is not currently any way to query or change or clear any other extension field data.
This module is likely to get broken up into pieces.
Synopsis
- getKeyFieldId :: Key c msg v -> FieldId
- getKeyFieldType :: Key c msg v -> FieldType
- getKeyDefaultValue :: Key c msg v -> v
- data Key c msg v where
- class ExtKey c where
- class MessageAPI msg a b | msg a -> b where
- newtype PackedSeq a = PackedSeq {- unPackedSeq :: Seq a
 
- data EP = EP !WireType !ByteString
- wireSizeExtField :: ExtField -> WireSize
- wirePutExtField :: ExtField -> Put
- wirePutExtFieldWithSize :: ExtField -> PutM WireSize
- loadExtension :: (ReflectDescriptor a, ExtendMessage a) => FieldId -> WireType -> a -> Get a
- notExtension :: (ReflectDescriptor a, ExtendMessage a, Typeable a) => FieldId -> WireType -> a -> Get a
- wireGetKeyToUnPacked :: (ExtendMessage msg, GPB v) => Key Seq msg v -> msg -> Get msg
- wireGetKeyToPacked :: (ExtendMessage msg, GPB v) => Key PackedSeq msg v -> msg -> Get msg
- class (Mergeable a, Default a, Wire a, Show a, Typeable a, Eq a, Ord a) => GPB a
- newtype ExtField = ExtField (Map FieldId ExtFieldValue)
- class Typeable msg => ExtendMessage msg where- getExtField :: msg -> ExtField
- putExtField :: ExtField -> msg -> msg
- validExtRanges :: msg -> [(FieldId, FieldId)]
 
- data ExtFieldValue- = ExtFromWire !(Seq EP)
- | ExtOptional !FieldType !GPDyn
- | ExtRepeated !FieldType !GPDynSeq
- | ExtPacked !FieldType !GPDynSeq
 
Query functions for Key
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.
External types and classes
data Key c msg v where Source #
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.
Constructors
| Key :: (ExtKey c, ExtendMessage msg, GPB v) => FieldId -> FieldType -> Maybe v -> Key c msg v | 
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.
Methods
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. getExtwill attempt to parse the bytes as the key's value type, and may fail. The parsing is done with theparseWireExtmethod (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.
clearExt :: Key c msg v -> msg -> msg Source #
wireGetKey :: Key c msg v -> msg -> Get msg Source #
class MessageAPI msg a b | msg a -> b where Source #
Minimal complete definition
Methods
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) Seqof 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 Falseif 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 Methods 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 PackedSeq is needed to distinguish the packed repeated format from the repeated format.
 This is only used in the phantom type of Key.
Constructors
| PackedSeq | |
| Fields 
 | |
Instances
| ExtKey PackedSeq Source # | |
| Defined in Text.ProtocolBuffers.Extensions | |
Constructors
| EP !WireType !ByteString | 
Instances
| Eq EP Source # | |
| Data EP Source # | |
| Defined in Text.ProtocolBuffers.Extensions Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EP -> c EP # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EP # dataTypeOf :: EP -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EP) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EP) # gmapT :: (forall b. Data b => b -> b) -> EP -> EP # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EP -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EP -> r # gmapQ :: (forall d. Data d => d -> u) -> EP -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> EP -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> EP -> m EP # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EP -> m EP # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EP -> m EP # | |
| Ord EP Source # | |
| Show EP Source # | |
Internal types, functions, and classes
wireSizeExtField :: ExtField -> WireSize Source #
This is used by the generated code
wirePutExtField :: ExtField -> Put Source #
This is used by the generated code. The data is serialized in order of increasing field number.
loadExtension :: (ReflectDescriptor a, ExtendMessage a) => FieldId -> WireType -> a -> Get a Source #
get a value from the wire into the message's ExtField. This is used by generated code for extensions that were not known at compile time.
notExtension :: (ReflectDescriptor a, ExtendMessage a, Typeable a) => FieldId -> WireType -> a -> Get a Source #
wireGetKeyToUnPacked :: (ExtendMessage msg, GPB v) => Key Seq msg v -> msg -> Get msg Source #
wireKeyToUnPacked is used to load a repeated packed format into a repeated non-packed extension key
wireGetKeyToPacked :: (ExtendMessage msg, GPB v) => Key PackedSeq msg v -> msg -> Get msg Source #
wireKeyToPacked is used to load a repeated unpacked format into a repeated packed extension key
class (Mergeable a, Default a, Wire a, Show a, Typeable a, Eq a, Ord a) => GPB a Source #
Instances
| GPB Bool Source # | |
| Defined in Text.ProtocolBuffers.Extensions | |
| GPB Double Source # | |
| Defined in Text.ProtocolBuffers.Extensions | |
| GPB Float Source # | |
| Defined in Text.ProtocolBuffers.Extensions | |
| GPB Int32 Source # | |
| Defined in Text.ProtocolBuffers.Extensions | |
| GPB Int64 Source # | |
| Defined in Text.ProtocolBuffers.Extensions | |
| GPB Word32 Source # | |
| Defined in Text.ProtocolBuffers.Extensions | |
| GPB Word64 Source # | |
| Defined in Text.ProtocolBuffers.Extensions | |
| GPB ByteString Source # | |
| Defined in Text.ProtocolBuffers.Extensions | |
| GPB Utf8 Source # | |
| Defined in Text.ProtocolBuffers.Extensions | |
ExtField is a newtype'd map from the numeric FieldId key to the ExtFieldValue. This allows for the needed class instances.
Constructors
| ExtField (Map FieldId ExtFieldValue) | 
Instances
| Eq ExtField Source # | |
| Data ExtField Source # | |
| Defined in Text.ProtocolBuffers.Extensions Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ExtField -> c ExtField # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ExtField # toConstr :: ExtField -> Constr # dataTypeOf :: ExtField -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ExtField) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ExtField) # gmapT :: (forall b. Data b => b -> b) -> ExtField -> ExtField # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ExtField -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ExtField -> r # gmapQ :: (forall d. Data d => d -> u) -> ExtField -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ExtField -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ExtField -> m ExtField # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ExtField -> m ExtField # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ExtField -> m ExtField # | |
| Ord ExtField Source # | |
| Defined in Text.ProtocolBuffers.Extensions | |
| Show ExtField Source # | |
| Default ExtField Source # | |
| Defined in Text.ProtocolBuffers.Extensions Methods | |
| Mergeable ExtField Source # | |
| Defined in Text.ProtocolBuffers.Extensions | |
class Typeable msg => ExtendMessage msg where Source #
ExtendMessage abstracts the operations of storing and
 retrieving the ExtField from the message, and provides the
 reflection needed to know the valid field numbers.
This only used internally.
Methods
getExtField :: msg -> ExtField Source #
putExtField :: ExtField -> msg -> msg Source #
validExtRanges :: msg -> [(FieldId, FieldId)] Source #
data ExtFieldValue Source #
The WireType is used to ensure the Seq is homogeneous. The ByteString is the unparsed input after the tag.
Constructors
| ExtFromWire !(Seq EP) | |
| ExtOptional !FieldType !GPDyn | |
| ExtRepeated !FieldType !GPDynSeq | |
| ExtPacked !FieldType !GPDynSeq | 
Instances
| Eq ExtFieldValue Source # | |
| Defined in Text.ProtocolBuffers.Extensions Methods (==) :: ExtFieldValue -> ExtFieldValue -> Bool # (/=) :: ExtFieldValue -> ExtFieldValue -> Bool # | |
| Ord ExtFieldValue Source # | |
| Defined in Text.ProtocolBuffers.Extensions Methods compare :: ExtFieldValue -> ExtFieldValue -> Ordering # (<) :: ExtFieldValue -> ExtFieldValue -> Bool # (<=) :: ExtFieldValue -> ExtFieldValue -> Bool # (>) :: ExtFieldValue -> ExtFieldValue -> Bool # (>=) :: ExtFieldValue -> ExtFieldValue -> Bool # max :: ExtFieldValue -> ExtFieldValue -> ExtFieldValue # min :: ExtFieldValue -> ExtFieldValue -> ExtFieldValue # | |
| Show ExtFieldValue Source # | |
| Defined in Text.ProtocolBuffers.Extensions Methods showsPrec :: Int -> ExtFieldValue -> ShowS # show :: ExtFieldValue -> String # showList :: [ExtFieldValue] -> ShowS # | |