protocol-buffers-2.4.0: Parse Google Protocol Buffer specifications

Safe HaskellNone
LanguageHaskell98

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

Documentation

data ProtoName 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'] .

Constructors

ProtoName 

Fields

Instances

Eq ProtoName Source # 
Data ProtoName Source # 

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 # 
Read ProtoName Source # 
Show ProtoName Source # 

data ProtoFName Source #

Constructors

ProtoFName 

Fields

Instances

Eq ProtoFName Source # 
Data ProtoFName Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ProtoFName -> c ProtoFName #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ProtoFName #

toConstr :: ProtoFName -> Constr #

dataTypeOf :: ProtoFName -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ProtoFName) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ProtoFName) #

gmapT :: (forall b. Data b => b -> b) -> ProtoFName -> ProtoFName #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ProtoFName -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ProtoFName -> r #

gmapQ :: (forall d. Data d => d -> u) -> ProtoFName -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ProtoFName -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ProtoFName -> m ProtoFName #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ProtoFName -> m ProtoFName #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ProtoFName -> m ProtoFName #

Ord ProtoFName Source # 
Read ProtoFName Source # 
Show ProtoFName Source # 

data ProtoInfo Source #

Constructors

ProtoInfo 

Fields

Instances

Eq ProtoInfo Source # 
Data ProtoInfo Source # 

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 # 
Read ProtoInfo Source # 
Show ProtoInfo Source # 

data DescriptorInfo Source #

Instances

Eq DescriptorInfo Source # 
Data DescriptorInfo Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DescriptorInfo -> c DescriptorInfo #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DescriptorInfo #

toConstr :: DescriptorInfo -> Constr #

dataTypeOf :: DescriptorInfo -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DescriptorInfo) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DescriptorInfo) #

gmapT :: (forall b. Data b => b -> b) -> DescriptorInfo -> DescriptorInfo #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DescriptorInfo -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DescriptorInfo -> r #

gmapQ :: (forall d. Data d => d -> u) -> DescriptorInfo -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DescriptorInfo -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DescriptorInfo -> m DescriptorInfo #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DescriptorInfo -> m DescriptorInfo #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DescriptorInfo -> m DescriptorInfo #

Ord DescriptorInfo Source # 
Read DescriptorInfo Source # 
Show DescriptorInfo Source # 

data FieldInfo Source #

Constructors

FieldInfo 

Fields

Instances

Eq FieldInfo Source # 
Data FieldInfo Source # 

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 # 
Read FieldInfo Source # 
Show FieldInfo Source # 

data HsDefault 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.

Instances

Eq HsDefault Source # 
Data HsDefault Source # 

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 # 
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.

Instances

Eq SomeRealFloat Source # 
Data SomeRealFloat Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SomeRealFloat -> c SomeRealFloat #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SomeRealFloat #

toConstr :: SomeRealFloat -> Constr #

dataTypeOf :: SomeRealFloat -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SomeRealFloat) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SomeRealFloat) #

gmapT :: (forall b. Data b => b -> b) -> SomeRealFloat -> SomeRealFloat #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SomeRealFloat -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SomeRealFloat -> r #

gmapQ :: (forall d. Data d => d -> u) -> SomeRealFloat -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SomeRealFloat -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SomeRealFloat -> m SomeRealFloat #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SomeRealFloat -> m SomeRealFloat #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SomeRealFloat -> m SomeRealFloat #

Ord SomeRealFloat Source # 
Read SomeRealFloat Source # 
Show SomeRealFloat Source # 

data EnumInfo Source #

Constructors

EnumInfo 

Fields

Instances

Eq EnumInfo Source # 
Data EnumInfo Source # 

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 # 
Read EnumInfo Source # 
Show EnumInfo Source # 

class ReflectDescriptor m where Source #

Minimal complete definition

reflectDescriptorInfo

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 :: m -> DescriptorInfo Source #

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.

Instances

Eq GetMessageInfo Source # 
Data GetMessageInfo Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GetMessageInfo -> c GetMessageInfo #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GetMessageInfo #

toConstr :: GetMessageInfo -> Constr #

dataTypeOf :: GetMessageInfo -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c GetMessageInfo) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GetMessageInfo) #

gmapT :: (forall b. Data b => b -> b) -> GetMessageInfo -> GetMessageInfo #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GetMessageInfo -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GetMessageInfo -> r #

gmapQ :: (forall d. Data d => d -> u) -> GetMessageInfo -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GetMessageInfo -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GetMessageInfo -> m GetMessageInfo #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GetMessageInfo -> m GetMessageInfo #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GetMessageInfo -> m GetMessageInfo #

Ord GetMessageInfo Source # 
Read GetMessageInfo Source # 
Show GetMessageInfo Source # 

data OneofInfo Source #

Instances

Eq OneofInfo Source # 
Data OneofInfo Source # 

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 # 
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.