protocol-buffers-descriptor-2.4.4: Text.DescriptorProto.Options and code generated from the Google Protocol Buffer specification

Safe HaskellNone
LanguageHaskell98

Text.DescriptorProtos.Options

Description

This module provides a less verbose API for accessing the options of the various descriptor messages types. There are seven different option types. The EnumValueOptions are not currently settable in the proto file. To access extension keys the descendKey functions are provided as the descend functions ignore them. The toDP, toEP, toSP are type-specific descents that are demonstrated in the the tests below. They are useful in that they provide more information for the type-checker. The toFP, toEVP, and toMP are fully type-specific descents but are needed to make the tests below type-check, though they could have been used in test4, test5', and test7.

import Text.DescriptorProtos.Options
import Text.DescriptorProtos(fileDescriptorProto)

test1 :: D.FileOptions
test1 = options fileDescriptorProto

test2 :: Maybe D.MessageOptions
test2 = return fileDescriptorProto >>= descend "FieldDescriptorProto" >>= return . options

test3 :: Maybe D.EnumOptions
test3 = return fileDescriptorProto >>= toDP "FieldDescriptorProto" >>= descend "Type" >>= return . options

test4 :: Maybe D.EnumValueOptions
test4 = return fileDescriptorProto >>= toDP "FieldDescriptorProto" >>= toEP "Type" >>= descend "TYPE_DOUBLE" >>= return . options

test5 :: Maybe D.FieldOptions
test5 = return fileDescriptorProto >>= toDP "DescriptorProto" >>= toDP "ExtensionRange" >>= descend "start" >>= return . options

test6 :: Maybe D.ServiceOptions
test6 = return fileDescriptorProto >>= descend "ImaginaryService" >>= return . options

test7 :: Maybe D.MethodOptions
test7 = return fileDescriptorProto >>= toSP "ImaginaryService" >>= descend "ImaginaryMethod" >>= return . options

Documentation

descend :: DescendClass a c => String -> a -> Maybe c Source #

data FileDescriptorProto Source #

Instances

Eq FileDescriptorProto Source # 
Data FileDescriptorProto Source # 

Methods

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

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

toConstr :: FileDescriptorProto -> Constr #

dataTypeOf :: FileDescriptorProto -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord FileDescriptorProto Source # 
Show FileDescriptorProto Source # 
UnknownMessage FileDescriptorProto Source # 
GPB FileDescriptorProto Source # 
Wire FileDescriptorProto Source # 
TextMsg FileDescriptorProto Source # 
TextType FileDescriptorProto Source # 
ReflectDescriptor FileDescriptorProto Source # 
Mergeable FileDescriptorProto Source # 
Default FileDescriptorProto Source # 
DescendKey FileDescriptorProto Source # 
NameAndOptions FileDescriptorProto FileOptions Source # 
DescendClass FileDescriptorProto ServiceDescriptorProto Source # 
DescendClass FileDescriptorProto EnumDescriptorProto Source # 
DescendClass FileDescriptorProto DescriptorProto Source # 
MessageAPI msg' (msg' -> FileDescriptorProto) FileDescriptorProto Source # 

Methods

getVal :: msg' -> (msg' -> FileDescriptorProto) -> FileDescriptorProto #

isSet :: msg' -> (msg' -> FileDescriptorProto) -> Bool #

data DescriptorProto Source #

Instances

Eq DescriptorProto Source # 
Data DescriptorProto Source # 

Methods

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

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

toConstr :: DescriptorProto -> Constr #

dataTypeOf :: DescriptorProto -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord DescriptorProto Source # 
Show DescriptorProto Source # 
UnknownMessage DescriptorProto Source # 
GPB DescriptorProto Source # 
Wire DescriptorProto Source # 
TextMsg DescriptorProto Source # 
TextType DescriptorProto Source # 
ReflectDescriptor DescriptorProto Source # 
Mergeable DescriptorProto Source # 
Default DescriptorProto Source # 
DescendKey DescriptorProto Source # 
NameAndOptions DescriptorProto MessageOptions Source # 
DescendClass DescriptorProto FieldDescriptorProto Source # 
DescendClass DescriptorProto EnumDescriptorProto Source # 
DescendClass DescriptorProto DescriptorProto Source # 
DescendClass FileDescriptorProto DescriptorProto Source # 
MessageAPI msg' (msg' -> DescriptorProto) DescriptorProto Source # 

Methods

getVal :: msg' -> (msg' -> DescriptorProto) -> DescriptorProto #

isSet :: msg' -> (msg' -> DescriptorProto) -> Bool #

data EnumDescriptorProto Source #

Instances

Eq EnumDescriptorProto Source # 
Data EnumDescriptorProto Source # 

Methods

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

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

toConstr :: EnumDescriptorProto -> Constr #

dataTypeOf :: EnumDescriptorProto -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord EnumDescriptorProto Source # 
Show EnumDescriptorProto Source # 
UnknownMessage EnumDescriptorProto Source # 
GPB EnumDescriptorProto Source # 
Wire EnumDescriptorProto Source # 
TextMsg EnumDescriptorProto Source # 
TextType EnumDescriptorProto Source # 
ReflectDescriptor EnumDescriptorProto Source # 
Mergeable EnumDescriptorProto Source # 
Default EnumDescriptorProto Source # 
NameAndOptions EnumDescriptorProto EnumOptions Source # 
DescendClass EnumDescriptorProto EnumValueDescriptorProto Source # 
DescendClass DescriptorProto EnumDescriptorProto Source # 
DescendClass FileDescriptorProto EnumDescriptorProto Source # 
MessageAPI msg' (msg' -> EnumDescriptorProto) EnumDescriptorProto Source # 

Methods

getVal :: msg' -> (msg' -> EnumDescriptorProto) -> EnumDescriptorProto #

isSet :: msg' -> (msg' -> EnumDescriptorProto) -> Bool #

data EnumValueDescriptorProto Source #

Instances

Eq EnumValueDescriptorProto Source # 
Data EnumValueDescriptorProto Source # 

Methods

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

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

toConstr :: EnumValueDescriptorProto -> Constr #

dataTypeOf :: EnumValueDescriptorProto -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord EnumValueDescriptorProto Source # 
Show EnumValueDescriptorProto Source # 
UnknownMessage EnumValueDescriptorProto Source # 
GPB EnumValueDescriptorProto Source # 
Wire EnumValueDescriptorProto Source # 
TextMsg EnumValueDescriptorProto Source # 
TextType EnumValueDescriptorProto Source # 
ReflectDescriptor EnumValueDescriptorProto Source # 
Mergeable EnumValueDescriptorProto Source # 
Default EnumValueDescriptorProto Source # 
NameAndOptions EnumValueDescriptorProto EnumValueOptions Source # 
DescendClass EnumDescriptorProto EnumValueDescriptorProto Source # 
MessageAPI msg' (msg' -> EnumValueDescriptorProto) EnumValueDescriptorProto Source # 

Methods

getVal :: msg' -> (msg' -> EnumValueDescriptorProto) -> EnumValueDescriptorProto #

isSet :: msg' -> (msg' -> EnumValueDescriptorProto) -> Bool #

data FieldDescriptorProto Source #

Instances

Eq FieldDescriptorProto Source # 
Data FieldDescriptorProto Source # 

Methods

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

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

toConstr :: FieldDescriptorProto -> Constr #

dataTypeOf :: FieldDescriptorProto -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord FieldDescriptorProto Source # 
Show FieldDescriptorProto Source # 
UnknownMessage FieldDescriptorProto Source # 
GPB FieldDescriptorProto Source # 
Wire FieldDescriptorProto Source # 
TextMsg FieldDescriptorProto Source # 
TextType FieldDescriptorProto Source # 
ReflectDescriptor FieldDescriptorProto Source # 
Mergeable FieldDescriptorProto Source # 
Default FieldDescriptorProto Source # 
NameAndOptions FieldDescriptorProto FieldOptions Source # 
DescendClass DescriptorProto FieldDescriptorProto Source # 
MessageAPI msg' (msg' -> FieldDescriptorProto) FieldDescriptorProto Source # 

Methods

getVal :: msg' -> (msg' -> FieldDescriptorProto) -> FieldDescriptorProto #

isSet :: msg' -> (msg' -> FieldDescriptorProto) -> Bool #

data ServiceDescriptorProto Source #

Instances

Eq ServiceDescriptorProto Source # 
Data ServiceDescriptorProto Source # 

Methods

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

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

toConstr :: ServiceDescriptorProto -> Constr #

dataTypeOf :: ServiceDescriptorProto -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ServiceDescriptorProto Source # 
Show ServiceDescriptorProto Source # 
UnknownMessage ServiceDescriptorProto Source # 
GPB ServiceDescriptorProto Source # 
Wire ServiceDescriptorProto Source # 
TextMsg ServiceDescriptorProto Source # 
TextType ServiceDescriptorProto Source # 
ReflectDescriptor ServiceDescriptorProto Source # 
Mergeable ServiceDescriptorProto Source # 
Default ServiceDescriptorProto Source # 
NameAndOptions ServiceDescriptorProto ServiceOptions Source # 
DescendClass ServiceDescriptorProto MethodDescriptorProto Source # 
DescendClass FileDescriptorProto ServiceDescriptorProto Source # 
MessageAPI msg' (msg' -> ServiceDescriptorProto) ServiceDescriptorProto Source # 

Methods

getVal :: msg' -> (msg' -> ServiceDescriptorProto) -> ServiceDescriptorProto #

isSet :: msg' -> (msg' -> ServiceDescriptorProto) -> Bool #

data MethodDescriptorProto Source #

Instances

Eq MethodDescriptorProto Source # 
Data MethodDescriptorProto Source # 

Methods

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

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

toConstr :: MethodDescriptorProto -> Constr #

dataTypeOf :: MethodDescriptorProto -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord MethodDescriptorProto Source # 
Show MethodDescriptorProto Source # 
UnknownMessage MethodDescriptorProto Source # 
GPB MethodDescriptorProto Source # 
Wire MethodDescriptorProto Source # 
TextMsg MethodDescriptorProto Source # 
TextType MethodDescriptorProto Source # 
ReflectDescriptor MethodDescriptorProto Source # 
Mergeable MethodDescriptorProto Source # 
Default MethodDescriptorProto Source # 
NameAndOptions MethodDescriptorProto MethodOptions Source # 
DescendClass ServiceDescriptorProto MethodDescriptorProto Source # 
MessageAPI msg' (msg' -> MethodDescriptorProto) MethodDescriptorProto Source # 

Methods

getVal :: msg' -> (msg' -> MethodDescriptorProto) -> MethodDescriptorProto #

isSet :: msg' -> (msg' -> MethodDescriptorProto) -> Bool #

data EnumOptions Source #

Instances

Eq EnumOptions Source # 
Data EnumOptions Source # 

Methods

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

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

toConstr :: EnumOptions -> Constr #

dataTypeOf :: EnumOptions -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord EnumOptions Source # 
Show EnumOptions Source # 
UnknownMessage EnumOptions Source # 
ExtendMessage EnumOptions Source # 
GPB EnumOptions Source # 
Wire EnumOptions Source # 
TextMsg EnumOptions Source # 
TextType EnumOptions Source # 

Methods

tellT :: String -> EnumOptions -> Output #

getT :: Stream s Identity Char => String -> Parsec s () EnumOptions #

ReflectDescriptor EnumOptions Source # 
Mergeable EnumOptions Source # 
Default EnumOptions Source # 
NameAndOptions EnumDescriptorProto EnumOptions Source # 
MessageAPI msg' (msg' -> EnumOptions) EnumOptions Source # 

Methods

getVal :: msg' -> (msg' -> EnumOptions) -> EnumOptions #

isSet :: msg' -> (msg' -> EnumOptions) -> Bool #

data EnumValueOptions Source #

Instances

Eq EnumValueOptions Source # 
Data EnumValueOptions Source # 

Methods

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

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

toConstr :: EnumValueOptions -> Constr #

dataTypeOf :: EnumValueOptions -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord EnumValueOptions Source # 
Show EnumValueOptions Source # 
UnknownMessage EnumValueOptions Source # 
ExtendMessage EnumValueOptions Source # 
GPB EnumValueOptions Source # 
Wire EnumValueOptions Source # 
TextMsg EnumValueOptions Source # 
TextType EnumValueOptions Source # 
ReflectDescriptor EnumValueOptions Source # 
Mergeable EnumValueOptions Source # 
Default EnumValueOptions Source # 
NameAndOptions EnumValueDescriptorProto EnumValueOptions Source # 
MessageAPI msg' (msg' -> EnumValueOptions) EnumValueOptions Source # 

Methods

getVal :: msg' -> (msg' -> EnumValueOptions) -> EnumValueOptions #

isSet :: msg' -> (msg' -> EnumValueOptions) -> Bool #

data FieldOptions Source #

Instances

Eq FieldOptions Source # 
Data FieldOptions Source # 

Methods

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

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

toConstr :: FieldOptions -> Constr #

dataTypeOf :: FieldOptions -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord FieldOptions Source # 
Show FieldOptions Source # 
UnknownMessage FieldOptions Source # 
ExtendMessage FieldOptions Source # 
GPB FieldOptions Source # 
Wire FieldOptions Source # 
TextMsg FieldOptions Source # 
TextType FieldOptions Source # 

Methods

tellT :: String -> FieldOptions -> Output #

getT :: Stream s Identity Char => String -> Parsec s () FieldOptions #

ReflectDescriptor FieldOptions Source # 
Mergeable FieldOptions Source # 
Default FieldOptions Source # 
NameAndOptions FieldDescriptorProto FieldOptions Source # 
MessageAPI msg' (msg' -> FieldOptions) FieldOptions Source # 

Methods

getVal :: msg' -> (msg' -> FieldOptions) -> FieldOptions #

isSet :: msg' -> (msg' -> FieldOptions) -> Bool #

data FileOptions Source #

Instances

Eq FileOptions Source # 
Data FileOptions Source # 

Methods

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

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

toConstr :: FileOptions -> Constr #

dataTypeOf :: FileOptions -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord FileOptions Source # 
Show FileOptions Source # 
UnknownMessage FileOptions Source # 
ExtendMessage FileOptions Source # 
GPB FileOptions Source # 
Wire FileOptions Source # 
TextMsg FileOptions Source # 
TextType FileOptions Source # 

Methods

tellT :: String -> FileOptions -> Output #

getT :: Stream s Identity Char => String -> Parsec s () FileOptions #

ReflectDescriptor FileOptions Source # 
Mergeable FileOptions Source # 
Default FileOptions Source # 
NameAndOptions FileDescriptorProto FileOptions Source # 
MessageAPI msg' (msg' -> FileOptions) FileOptions Source # 

Methods

getVal :: msg' -> (msg' -> FileOptions) -> FileOptions #

isSet :: msg' -> (msg' -> FileOptions) -> Bool #

data MessageOptions Source #

Instances

Eq MessageOptions Source # 
Data MessageOptions Source # 

Methods

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

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

toConstr :: MessageOptions -> Constr #

dataTypeOf :: MessageOptions -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord MessageOptions Source # 
Show MessageOptions Source # 
UnknownMessage MessageOptions Source # 
ExtendMessage MessageOptions Source # 
GPB MessageOptions Source # 
Wire MessageOptions Source # 
TextMsg MessageOptions Source # 
TextType MessageOptions Source # 
ReflectDescriptor MessageOptions Source # 
Mergeable MessageOptions Source # 
Default MessageOptions Source # 
NameAndOptions DescriptorProto MessageOptions Source # 
MessageAPI msg' (msg' -> MessageOptions) MessageOptions Source # 

Methods

getVal :: msg' -> (msg' -> MessageOptions) -> MessageOptions #

isSet :: msg' -> (msg' -> MessageOptions) -> Bool #

data MethodOptions Source #

Instances

Eq MethodOptions Source # 
Data MethodOptions Source # 

Methods

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

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

toConstr :: MethodOptions -> Constr #

dataTypeOf :: MethodOptions -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord MethodOptions Source # 
Show MethodOptions Source # 
UnknownMessage MethodOptions Source # 
ExtendMessage MethodOptions Source # 
GPB MethodOptions Source # 
Wire MethodOptions Source # 
TextMsg MethodOptions Source # 
TextType MethodOptions Source # 

Methods

tellT :: String -> MethodOptions -> Output #

getT :: Stream s Identity Char => String -> Parsec s () MethodOptions #

ReflectDescriptor MethodOptions Source # 
Mergeable MethodOptions Source # 
Default MethodOptions Source # 
NameAndOptions MethodDescriptorProto MethodOptions Source # 
MessageAPI msg' (msg' -> MethodOptions) MethodOptions Source # 

Methods

getVal :: msg' -> (msg' -> MethodOptions) -> MethodOptions #

isSet :: msg' -> (msg' -> MethodOptions) -> Bool #

data ServiceOptions Source #

Instances

Eq ServiceOptions Source # 
Data ServiceOptions Source # 

Methods

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

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

toConstr :: ServiceOptions -> Constr #

dataTypeOf :: ServiceOptions -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ServiceOptions Source # 
Show ServiceOptions Source # 
UnknownMessage ServiceOptions Source # 
ExtendMessage ServiceOptions Source # 
GPB ServiceOptions Source # 
Wire ServiceOptions Source # 
TextMsg ServiceOptions Source # 
TextType ServiceOptions Source # 
ReflectDescriptor ServiceOptions Source # 
Mergeable ServiceOptions Source # 
Default ServiceOptions Source # 
NameAndOptions ServiceDescriptorProto ServiceOptions Source # 
MessageAPI msg' (msg' -> ServiceOptions) ServiceOptions Source # 

Methods

getVal :: msg' -> (msg' -> ServiceOptions) -> ServiceOptions #

isSet :: msg' -> (msg' -> ServiceOptions) -> Bool #