| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Proto3.Suite.DotProto
Synopsis
- class Pretty a where
- pPrintPrec :: PrettyLevel -> Rational -> a -> Doc
- pPrint :: a -> Doc
- pPrintList :: PrettyLevel -> [a] -> Doc
- data DotProtoReservedField
- data DotProtoField
- data DotProtoMessagePart
- data RPCMethod = RPCMethod {}
- data DotProtoServicePart
- data Streaming
- data DotProtoEnumPart
- type DotProtoEnumValue = Int32
- data DotProtoType
- data Packing
- data DotProtoPrimType
- data DotProtoValue
- data DotProto = DotProto {}
- data DotProtoMeta = DotProtoMeta {}
- data DotProtoDefinition
- data DotProtoOption = DotProtoOption {}
- data DotProtoPackageSpec
- data DotProtoImportQualifier
- data DotProtoImport = DotProtoImport {}
- data DotProtoIdentifier
- newtype Path = Path {}
- newtype PackageName = PackageName {}
- newtype FieldName = FieldName {}
- newtype MessageName = MessageName {}
- fakePath :: Path
- parseProto :: Path -> String -> Either ParseError DotProto
- parseProtoFile :: MonadIO m => Path -> FilePath -> m (Either ParseError DotProto)
- typeLikeName :: MonadError CompileError m => String -> m String
- fieldLikeName :: String -> String
- prefixedEnumFieldName :: String -> String -> String
- data RenderingOptions = RenderingOptions {}
- defRenderingOptions :: RenderingOptions
- defSelectorName :: DotProtoIdentifier -> DotProtoIdentifier -> FieldNumber -> Doc
- defEnumMemberName :: DotProtoIdentifier -> DotProtoIdentifier -> Doc
- renderDotProto :: RenderingOptions -> DotProto -> Doc
- toProtoFile :: RenderingOptions -> DotProto -> String
- toProtoFileDef :: DotProto -> String
- packageFromDefs :: String -> [DotProtoDefinition] -> DotProto
Documentation
Pretty printing class. The precedence level is used in a similar way as in
the Show class. Minimal complete definition is either pPrintPrec or
pPrint.
Minimal complete definition
Instances
data DotProtoReservedField Source #
Constructors
| SingleField Int | |
| FieldRange Int Int | |
| ReservedIdentifier String |
Instances
| Eq DotProtoReservedField Source # | |
Defined in Proto3.Suite.DotProto.AST Methods (==) :: DotProtoReservedField -> DotProtoReservedField -> Bool # (/=) :: DotProtoReservedField -> DotProtoReservedField -> Bool # | |
| Show DotProtoReservedField Source # | |
Defined in Proto3.Suite.DotProto.AST Methods showsPrec :: Int -> DotProtoReservedField -> ShowS # show :: DotProtoReservedField -> String # showList :: [DotProtoReservedField] -> ShowS # | |
| Arbitrary DotProtoReservedField Source # | |
Defined in Proto3.Suite.DotProto.AST Methods arbitrary :: Gen DotProtoReservedField # shrink :: DotProtoReservedField -> [DotProtoReservedField] # | |
| Pretty DotProtoReservedField Source # | |
Defined in Proto3.Suite.DotProto.Rendering Methods pPrintPrec :: PrettyLevel -> Rational -> DotProtoReservedField -> Doc # pPrint :: DotProtoReservedField -> Doc # pPrintList :: PrettyLevel -> [DotProtoReservedField] -> Doc # | |
data DotProtoField Source #
Constructors
| DotProtoField | |
| DotProtoEmptyField | |
Instances
| Eq DotProtoField Source # | |
Defined in Proto3.Suite.DotProto.AST Methods (==) :: DotProtoField -> DotProtoField -> Bool # (/=) :: DotProtoField -> DotProtoField -> Bool # | |
| Show DotProtoField Source # | |
Defined in Proto3.Suite.DotProto.AST Methods showsPrec :: Int -> DotProtoField -> ShowS # show :: DotProtoField -> String # showList :: [DotProtoField] -> ShowS # | |
| Arbitrary DotProtoField Source # | |
Defined in Proto3.Suite.DotProto.AST | |
data DotProtoMessagePart Source #
Constructors
Instances
| Eq DotProtoMessagePart Source # | |
Defined in Proto3.Suite.DotProto.AST Methods (==) :: DotProtoMessagePart -> DotProtoMessagePart -> Bool # (/=) :: DotProtoMessagePart -> DotProtoMessagePart -> Bool # | |
| Show DotProtoMessagePart Source # | |
Defined in Proto3.Suite.DotProto.AST Methods showsPrec :: Int -> DotProtoMessagePart -> ShowS # show :: DotProtoMessagePart -> String # showList :: [DotProtoMessagePart] -> ShowS # | |
| Arbitrary DotProtoMessagePart Source # | |
Defined in Proto3.Suite.DotProto.AST Methods | |
Constructors
| RPCMethod | |
data DotProtoServicePart Source #
Constructors
| DotProtoServiceRPCMethod RPCMethod | |
| DotProtoServiceOption DotProtoOption | |
| DotProtoServiceEmpty |
Instances
| Eq DotProtoServicePart Source # | |
Defined in Proto3.Suite.DotProto.AST Methods (==) :: DotProtoServicePart -> DotProtoServicePart -> Bool # (/=) :: DotProtoServicePart -> DotProtoServicePart -> Bool # | |
| Show DotProtoServicePart Source # | |
Defined in Proto3.Suite.DotProto.AST Methods showsPrec :: Int -> DotProtoServicePart -> ShowS # show :: DotProtoServicePart -> String # showList :: [DotProtoServicePart] -> ShowS # | |
| Arbitrary DotProtoServicePart Source # | |
Defined in Proto3.Suite.DotProto.AST Methods | |
| Pretty DotProtoServicePart Source # | |
Defined in Proto3.Suite.DotProto.Rendering Methods pPrintPrec :: PrettyLevel -> Rational -> DotProtoServicePart -> Doc # pPrint :: DotProtoServicePart -> Doc # pPrintList :: PrettyLevel -> [DotProtoServicePart] -> Doc # | |
Constructors
| Streaming | |
| NonStreaming |
data DotProtoEnumPart Source #
Constructors
| DotProtoEnumField DotProtoIdentifier DotProtoEnumValue [DotProtoOption] | |
| DotProtoEnumOption DotProtoOption | |
| DotProtoEnumEmpty |
Instances
| Eq DotProtoEnumPart Source # | |
Defined in Proto3.Suite.DotProto.AST Methods (==) :: DotProtoEnumPart -> DotProtoEnumPart -> Bool # (/=) :: DotProtoEnumPart -> DotProtoEnumPart -> Bool # | |
| Show DotProtoEnumPart Source # | |
Defined in Proto3.Suite.DotProto.AST Methods showsPrec :: Int -> DotProtoEnumPart -> ShowS # show :: DotProtoEnumPart -> String # showList :: [DotProtoEnumPart] -> ShowS # | |
| Arbitrary DotProtoEnumPart Source # | |
Defined in Proto3.Suite.DotProto.AST | |
type DotProtoEnumValue = Int32 Source #
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
| Eq DotProtoType Source # | |
Defined in Proto3.Suite.DotProto.AST | |
| Show DotProtoType Source # | |
Defined in Proto3.Suite.DotProto.AST Methods showsPrec :: Int -> DotProtoType -> ShowS # show :: DotProtoType -> String # showList :: [DotProtoType] -> ShowS # | |
| Arbitrary DotProtoType Source # | |
Defined in Proto3.Suite.DotProto.AST | |
| Pretty DotProtoType Source # | |
Defined in Proto3.Suite.DotProto.Rendering Methods pPrintPrec :: PrettyLevel -> Rational -> DotProtoType -> Doc # pPrint :: DotProtoType -> Doc # pPrintList :: PrettyLevel -> [DotProtoType] -> Doc # | |
Constructors
| PackedField | |
| UnpackedField |
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
| Eq DotProtoPrimType Source # | |
Defined in Proto3.Suite.DotProto.AST Methods (==) :: DotProtoPrimType -> DotProtoPrimType -> Bool # (/=) :: DotProtoPrimType -> DotProtoPrimType -> Bool # | |
| Show DotProtoPrimType Source # | |
Defined in Proto3.Suite.DotProto.AST Methods showsPrec :: Int -> DotProtoPrimType -> ShowS # show :: DotProtoPrimType -> String # showList :: [DotProtoPrimType] -> ShowS # | |
| Arbitrary DotProtoPrimType Source # | |
Defined in Proto3.Suite.DotProto.AST | |
| Pretty DotProtoPrimType Source # | |
Defined in Proto3.Suite.DotProto.Rendering Methods pPrintPrec :: PrettyLevel -> Rational -> DotProtoPrimType -> Doc # pPrint :: DotProtoPrimType -> Doc # pPrintList :: PrettyLevel -> [DotProtoPrimType] -> Doc # | |
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
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 | |
data DotProtoMeta Source #
Tracks misc metadata about the AST
Constructors
| DotProtoMeta | |
Fields
| |
Instances
| Eq DotProtoMeta Source # | |
Defined in Proto3.Suite.DotProto.AST | |
| Show DotProtoMeta Source # | |
Defined in Proto3.Suite.DotProto.AST Methods showsPrec :: Int -> DotProtoMeta -> ShowS # show :: DotProtoMeta -> String # showList :: [DotProtoMeta] -> ShowS # | |
| Arbitrary DotProtoMeta Source # | |
Defined in Proto3.Suite.DotProto.AST | |
data DotProtoDefinition Source #
Top-level protocol definitions
Constructors
| DotProtoMessage String DotProtoIdentifier [DotProtoMessagePart] | |
| DotProtoEnum String DotProtoIdentifier [DotProtoEnumPart] | |
| DotProtoService String DotProtoIdentifier [DotProtoServicePart] |
Instances
| Eq DotProtoDefinition Source # | |
Defined in Proto3.Suite.DotProto.AST Methods (==) :: DotProtoDefinition -> DotProtoDefinition -> Bool # (/=) :: DotProtoDefinition -> DotProtoDefinition -> Bool # | |
| Show DotProtoDefinition Source # | |
Defined in Proto3.Suite.DotProto.AST Methods showsPrec :: Int -> DotProtoDefinition -> ShowS # show :: DotProtoDefinition -> String # showList :: [DotProtoDefinition] -> ShowS # | |
| Arbitrary DotProtoDefinition Source # | |
Defined in Proto3.Suite.DotProto.AST | |
data DotProtoOption Source #
An option id/value pair, can be attached to many types of statements
Constructors
| DotProtoOption | |
Instances
data DotProtoPackageSpec Source #
The namespace declaration
Constructors
| DotProtoPackageSpec DotProtoIdentifier | |
| DotProtoNoPackage |
Instances
| Eq DotProtoPackageSpec Source # | |
Defined in Proto3.Suite.DotProto.AST Methods (==) :: DotProtoPackageSpec -> DotProtoPackageSpec -> Bool # (/=) :: DotProtoPackageSpec -> DotProtoPackageSpec -> Bool # | |
| Show DotProtoPackageSpec Source # | |
Defined in Proto3.Suite.DotProto.AST Methods showsPrec :: Int -> DotProtoPackageSpec -> ShowS # show :: DotProtoPackageSpec -> String # showList :: [DotProtoPackageSpec] -> ShowS # | |
| Arbitrary DotProtoPackageSpec Source # | |
Defined in Proto3.Suite.DotProto.AST Methods | |
| Pretty DotProtoPackageSpec Source # | |
Defined in Proto3.Suite.DotProto.Rendering Methods pPrintPrec :: PrettyLevel -> Rational -> DotProtoPackageSpec -> Doc # pPrint :: DotProtoPackageSpec -> Doc # pPrintList :: PrettyLevel -> [DotProtoPackageSpec] -> Doc # | |
data DotProtoImportQualifier Source #
Instances
data DotProtoImport Source #
Top-level import declaration
Constructors
| DotProtoImport | |
Instances
data DotProtoIdentifier Source #
Constructors
| Single String | |
| Dots Path | |
| Qualified DotProtoIdentifier DotProtoIdentifier | |
| Anonymous |
Instances
newtype PackageName Source #
The name of the package
Constructors
| PackageName | |
Fields | |
Instances
| Eq PackageName Source # | |
Defined in Proto3.Suite.DotProto.AST | |
| Ord PackageName Source # | |
Defined in Proto3.Suite.DotProto.AST Methods compare :: PackageName -> PackageName -> Ordering # (<) :: PackageName -> PackageName -> Bool # (<=) :: PackageName -> PackageName -> Bool # (>) :: PackageName -> PackageName -> Bool # (>=) :: PackageName -> PackageName -> Bool # max :: PackageName -> PackageName -> PackageName # min :: PackageName -> PackageName -> PackageName # | |
| Show PackageName Source # | |
Defined in Proto3.Suite.DotProto.AST Methods showsPrec :: Int -> PackageName -> ShowS # show :: PackageName -> String # showList :: [PackageName] -> ShowS # | |
| IsString PackageName Source # | |
Defined in Proto3.Suite.DotProto.AST Methods fromString :: String -> PackageName # | |
The name of some field
Constructors
| FieldName | |
Fields | |
Instances
| Eq FieldName Source # | |
| Ord FieldName Source # | |
| Show FieldName Source # | |
| IsString FieldName Source # | |
Defined in Proto3.Suite.DotProto.AST Methods fromString :: String -> FieldName # | |
newtype MessageName Source #
The name of a message
Constructors
| MessageName | |
Fields | |
Instances
| Eq MessageName Source # | |
Defined in Proto3.Suite.DotProto.AST | |
| Ord MessageName Source # | |
Defined in Proto3.Suite.DotProto.AST Methods compare :: MessageName -> MessageName -> Ordering # (<) :: MessageName -> MessageName -> Bool # (<=) :: MessageName -> MessageName -> Bool # (>) :: MessageName -> MessageName -> Bool # (>=) :: MessageName -> MessageName -> Bool # max :: MessageName -> MessageName -> MessageName # min :: MessageName -> MessageName -> MessageName # | |
| Show MessageName Source # | |
Defined in Proto3.Suite.DotProto.AST Methods showsPrec :: Int -> MessageName -> ShowS # show :: MessageName -> String # showList :: [MessageName] -> ShowS # | |
| IsString MessageName Source # | |
Defined in Proto3.Suite.DotProto.AST Methods fromString :: String -> MessageName # | |
parseProto :: Path -> String -> Either ParseError DotProto Source #
parseProto mp inp attempts to parse inp as a DotProto. mp is the
module path to be injected into the AST as part of DotProtoMeta metadata on
a successful parse.
parseProtoFile :: MonadIO m => Path -> FilePath -> m (Either ParseError DotProto) Source #
parseProtoFile mp fp reads and parses the .proto file found at fp. mp
is used downstream during code generation when we need to generate names
which are a function of the source .proto file's filename and its path
relative to some --includeDir.
typeLikeName :: MonadError CompileError m => String -> m String Source #
produces either the pascal-cased version of the string typeLikeName xsxs if it begins with an alphabetical
character or underscore - which is replaced with X. A CompileError is emitted if the starting character is
non-alphabetic or if xs == "".
fieldLikeName :: String -> String Source #
is the casing transformation used to produce record selectors from message fields. If
fieldLikeName fieldfield is prefixed by a span of uppercase characters then that prefix will be lowercased while the remaining string
is left unchanged.
data RenderingOptions Source #
Options for rendering a .proto file.
Constructors
| RenderingOptions | |
Fields
| |
defRenderingOptions :: RenderingOptions Source #
Default rendering options.
defSelectorName :: DotProtoIdentifier -> DotProtoIdentifier -> FieldNumber -> Doc Source #
The default choice of field name for a selector.
defEnumMemberName :: DotProtoIdentifier -> DotProtoIdentifier -> Doc Source #
The default choice of enum member name for an enum
renderDotProto :: RenderingOptions -> DotProto -> Doc Source #
Traverses a DotProto AST and generates a .proto file from it
toProtoFile :: RenderingOptions -> DotProto -> String Source #
Render protobufs metadata as a .proto file stringy
toProtoFileDef :: DotProto -> String Source #
Render protobufs metadata as a .proto file string, using the default rendering options.
packageFromDefs :: String -> [DotProtoDefinition] -> DotProto Source #