| Safe Haskell | None | 
|---|---|
| Language | Haskell98 | 
Text.ProtocolBuffers.Reflections
Description
A strong feature of the protocol-buffers package is that it does
 not contain any structures defined by descriptor.proto!  This
 prevents me hitting any annoying circular dependencies.  The
 structures defined here are included in each module created by
 hprotoc.  They are optimized for use in code generation.
These values can be inspected at runtime by the user's code, but I have yet to write much documentation. Luckily the record field names are somewhat descriptive.
The other reflection is using the fileDescriptorProto which
 is put into the top level module created by hprotoc.
Synopsis
- data ProtoName = ProtoName {- protobufName :: FIName Utf8
- haskellPrefix :: [MName String]
- parentModule :: [MName String]
- baseName :: MName String
 
- data ProtoFName = ProtoFName {}
- data ProtoInfo = ProtoInfo {- protoMod :: ProtoName
- protoFilePath :: [FilePath]
- protoSource :: FilePath
- extensionKeys :: Seq KeyInfo
- messages :: [DescriptorInfo]
- enums :: [EnumInfo]
- oneofs :: [OneofInfo]
- knownKeyMap :: Map ProtoName (Seq 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 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 HsDefault
- data SomeRealFloat
- data EnumInfo = EnumInfo {- enumName :: ProtoName
- enumFilePath :: [FilePath]
- enumValues :: [(EnumCode, String)]
- enumJsonInstances :: Bool
 
- type EnumInfoApp e = [(EnumCode, String, e)]
- class ReflectDescriptor m where- getMessageInfo :: m -> GetMessageInfo
- reflectDescriptorInfo :: m -> DescriptorInfo
 
- class ReflectEnum e where- reflectEnum :: EnumInfoApp e
- reflectEnumInfo :: e -> EnumInfo
- parentOfEnum :: e -> Maybe DescriptorInfo
 
- data GetMessageInfo = GetMessageInfo {}
- data OneofInfo = OneofInfo {}
- makePNF :: ByteString -> [String] -> [String] -> String -> ProtoName
- toRF :: (RealFloat a, Fractional a) => SomeRealFloat -> a
- fromRF :: (RealFloat a, Fractional a) => a -> SomeRealFloat
Documentation
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'] .
Constructors
| ProtoName | |
| Fields 
 | |
Instances
| Eq ProtoName Source # | |
| Data ProtoName Source # | |
| Defined in Text.ProtocolBuffers.Reflections Methods 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 # | |
data ProtoFName Source #
Constructors
| ProtoFName | |
| Fields 
 | |
Instances
Constructors
| ProtoInfo | |
| Fields 
 | |
Instances
| Eq ProtoInfo Source # | |
| Data ProtoInfo Source # | |
| Defined in Text.ProtocolBuffers.Reflections Methods 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 # | |
data DescriptorInfo Source #
Constructors
| DescriptorInfo | |
| Fields 
 | |
Instances
Constructors
| FieldInfo | |
| Fields 
 | |
Instances
| Eq FieldInfo Source # | |
| Data FieldInfo Source # | |
| Defined in Text.ProtocolBuffers.Reflections Methods 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 # | |
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.
Constructors
| 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 Methods 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 # | |
data SomeRealFloat Source #
SomeRealFloat projects Double/Float to Rational or a special IEEE type.
 This is needed to track protobuf-2.3.0 which allows nan and inf and -inf default values.
Constructors
| SRF'Rational Rational | |
| SRF'nan | |
| SRF'ninf | |
| SRF'inf | 
Instances
Constructors
| EnumInfo | |
| Fields 
 | |
Instances
| Eq EnumInfo Source # | |
| Data EnumInfo Source # | |
| Defined in Text.ProtocolBuffers.Reflections Methods 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 # | |
type EnumInfoApp e = [(EnumCode, String, e)] Source #
class ReflectDescriptor m where Source #
Minimal complete definition
Methods
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 #
Arguments
| :: m | |
| -> DescriptorInfo | Must not inspect argument | 
class ReflectEnum e where Source #
Minimal complete definition
Methods
reflectEnum :: EnumInfoApp e Source #
Arguments
| :: e | |
| -> EnumInfo | Must not inspect argument | 
Arguments
| :: e | |
| -> Maybe DescriptorInfo | Must not inspect argument | 
data GetMessageInfo Source #
GetMessageInfo is used in getting messages from the wire.  It
 supplies the Set of precomposed wire tags that must be found in
 the message as well as a Set of all allowed tags (including known
 extension fields and all required wire tags).
Extension fields not in the allowedTags set are still loaded, but
 only as ByteString blobs that will have to interpreted later.
Constructors
| GetMessageInfo | |
| Fields 
 | |
Instances
Constructors
| OneofInfo | |
| Fields 
 | |
Instances
| Eq OneofInfo Source # | |
| Data OneofInfo Source # | |
| Defined in Text.ProtocolBuffers.Reflections Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OneofInfo -> c OneofInfo # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OneofInfo # toConstr :: OneofInfo -> Constr # dataTypeOf :: OneofInfo -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OneofInfo) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OneofInfo) # gmapT :: (forall b. Data b => b -> b) -> OneofInfo -> OneofInfo # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OneofInfo -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OneofInfo -> r # gmapQ :: (forall d. Data d => d -> u) -> OneofInfo -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> OneofInfo -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> OneofInfo -> m OneofInfo # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OneofInfo -> m OneofInfo # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OneofInfo -> m OneofInfo # | |
| Ord OneofInfo Source # | |
| Defined in Text.ProtocolBuffers.Reflections | |
| Read OneofInfo Source # | |
| Show OneofInfo Source # | |
makePNF :: ByteString -> [String] -> [String] -> String -> ProtoName Source #
makePNF is used by the generated code to create a ProtoName with less newtype noise.
toRF :: (RealFloat a, Fractional a) => SomeRealFloat -> a Source #
fromRF :: (RealFloat a, Fractional a) => a -> SomeRealFloat Source #