| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Proto3.Suite.DotProto.AST
Contents
Description
Fairly straightforward AST encoding of the .proto grammar
Synopsis
- newtype MessageName = MessageName {}
- newtype FieldName = FieldName {}
- newtype PackageName = PackageName {}
- data DotProtoIdentifier
- data DotProtoImport = DotProtoImport {}
- data DotProtoImportQualifier
- data DotProtoPackageSpec
- data DotProtoOption = DotProtoOption {}
- data DotProtoDefinition
- data DotProtoMeta = DotProtoMeta {}
- data DotProto = DotProto {}
- data DotProtoValue
- data DotProtoPrimType
- data Packing
- newtype Path = Path {}
- fakePath :: Path
- data DotProtoType
- type DotProtoEnumValue = Int32
- data DotProtoEnumPart
- data Streaming
- data DotProtoServicePart
- data RPCMethod = RPCMethod {}
- data DotProtoMessagePart
- data DotProtoField
- data DotProtoReservedField
Types
newtype MessageName Source #
The name of a message
Constructors
| MessageName | |
Fields | |
Instances
The name of some field
Constructors
| FieldName | |
Fields | |
Instances
| Eq FieldName Source # | |
| Data FieldName Source # | |
Defined in Proto3.Suite.DotProto.AST Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldName -> c FieldName Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FieldName Source # toConstr :: FieldName -> Constr Source # dataTypeOf :: FieldName -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FieldName) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FieldName) Source # gmapT :: (forall b. Data b => b -> b) -> FieldName -> FieldName Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldName -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldName -> r Source # gmapQ :: (forall d. Data d => d -> u) -> FieldName -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldName -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldName -> m FieldName Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldName -> m FieldName Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldName -> m FieldName Source # | |
| Ord FieldName Source # | |
Defined in Proto3.Suite.DotProto.AST | |
| Show FieldName Source # | |
| IsString FieldName Source # | |
Defined in Proto3.Suite.DotProto.AST Methods fromString :: String -> FieldName Source # | |
| Generic FieldName Source # | |
| type Rep FieldName Source # | |
Defined in Proto3.Suite.DotProto.AST | |
newtype PackageName Source #
The name of the package
Constructors
| PackageName | |
Fields | |
Instances
data DotProtoIdentifier Source #
Constructors
| Single String | |
| Dots Path | |
| Qualified DotProtoIdentifier DotProtoIdentifier | |
| Anonymous |
Instances
data DotProtoImport Source #
Top-level import declaration
Constructors
| DotProtoImport | |
Instances
data DotProtoImportQualifier Source #
Instances
data DotProtoPackageSpec Source #
The namespace declaration
Constructors
| DotProtoPackageSpec DotProtoIdentifier | |
| DotProtoNoPackage |
Instances
data DotProtoOption Source #
An option id/value pair, can be attached to many types of statements
Constructors
| DotProtoOption | |
Instances
data DotProtoDefinition Source #
Top-level protocol definitions
Constructors
| DotProtoMessage String DotProtoIdentifier [DotProtoMessagePart] | |
| DotProtoEnum String DotProtoIdentifier [DotProtoEnumPart] | |
| DotProtoService String DotProtoIdentifier [DotProtoServicePart] |
Instances
data DotProtoMeta Source #
Tracks misc metadata about the AST
Constructors
| DotProtoMeta | |
Fields
| |
Instances
This data structure represents a .proto file The actual source order of protobuf statements isn't meaningful so statements are sorted by type during parsing. A .proto file with more than one package declaration is considered invalid.
Constructors
| DotProto | |
Fields | |
Instances
data DotProtoValue Source #
Matches the definition of constant in the proto3 language spec
These are only used as rvalues
Constructors
| Identifier DotProtoIdentifier | |
| StringLit String | |
| IntLit Int | |
| FloatLit Double | |
| BoolLit Bool |
Instances
data DotProtoPrimType Source #
Constructors
| Int32 | |
| Int64 | |
| SInt32 | |
| SInt64 | |
| UInt32 | |
| UInt64 | |
| Fixed32 | |
| Fixed64 | |
| SFixed32 | |
| SFixed64 | |
| String | |
| Bytes | |
| Bool | |
| Float | |
| Double | |
| Named DotProtoIdentifier | A named type, referring to another message or enum defined in the same file |
Instances
Constructors
| PackedField | |
| UnpackedField |
Instances
Constructors
| Path | |
Fields | |
Instances
| Eq Path Source # | |
| Data Path Source # | |
Defined in Proto3.Suite.DotProto.AST Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Path -> c Path Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Path Source # toConstr :: Path -> Constr Source # dataTypeOf :: Path -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Path) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Path) Source # gmapT :: (forall b. Data b => b -> b) -> Path -> Path Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Path -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Path -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Path -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Path -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Path -> m Path Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Path -> m Path Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Path -> m Path Source # | |
| Ord Path Source # | |
Defined in Proto3.Suite.DotProto.AST | |
| Show Path Source # | |
| Generic Path Source # | |
| type Rep Path Source # | |
Defined in Proto3.Suite.DotProto.AST | |
data DotProtoType Source #
This type is an almagamation of the modifiers used in types. It corresponds to a syntax role but not a semantic role, not all modifiers are meaningful in every type context.
Constructors
| Prim DotProtoPrimType | |
| Repeated DotProtoPrimType | |
| NestedRepeated DotProtoPrimType | |
| Map DotProtoPrimType DotProtoPrimType |
Instances
type DotProtoEnumValue = Int32 Source #
data DotProtoEnumPart Source #
Constructors
| DotProtoEnumField DotProtoIdentifier DotProtoEnumValue [DotProtoOption] | |
| DotProtoEnumOption DotProtoOption | |
| DotProtoEnumEmpty |
Instances
Constructors
| Streaming | |
| NonStreaming |
Instances
data DotProtoServicePart Source #
Constructors
| DotProtoServiceRPCMethod RPCMethod | |
| DotProtoServiceOption DotProtoOption | |
| DotProtoServiceEmpty |
Instances
Constructors
| RPCMethod | |
Instances
data DotProtoMessagePart Source #
Constructors
Instances
data DotProtoField Source #
Constructors
| DotProtoField | |
| DotProtoEmptyField | |
Instances
data DotProtoReservedField Source #
Constructors
| SingleField Int | |
| FieldRange Int Int | |
| ReservedIdentifier String |