proto3-suite-0.4.2: A low level library for writing out data in the Protocol Buffers wire format
Safe HaskellNone
LanguageHaskell2010

Proto3.Suite.DotProto

Synopsis

Documentation

class Pretty a where #

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

pPrintPrec | pPrint

Methods

pPrintPrec :: PrettyLevel -> Rational -> a -> Doc #

pPrint :: a -> Doc #

pPrintList :: PrettyLevel -> [a] -> Doc #

Instances

Instances details
Pretty Bool 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Pretty Char 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Pretty Double 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Pretty Float 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Pretty Int 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Pretty Integer 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Pretty Ordering 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Pretty () 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Methods

pPrintPrec :: PrettyLevel -> Rational -> () -> Doc #

pPrint :: () -> Doc #

pPrintList :: PrettyLevel -> [()] -> Doc #

Pretty FieldNumber Source # 
Instance details

Defined in Proto3.Suite.DotProto.Rendering

Pretty DotProtoReservedField Source # 
Instance details

Defined in Proto3.Suite.DotProto.Rendering

Pretty DotProtoServicePart Source # 
Instance details

Defined in Proto3.Suite.DotProto.Rendering

Pretty Streaming Source # 
Instance details

Defined in Proto3.Suite.DotProto.Rendering

Pretty DotProtoType Source # 
Instance details

Defined in Proto3.Suite.DotProto.Rendering

Pretty DotProtoPrimType Source # 
Instance details

Defined in Proto3.Suite.DotProto.Rendering

Pretty DotProtoValue Source # 
Instance details

Defined in Proto3.Suite.DotProto.Rendering

Pretty DotProtoOption Source # 
Instance details

Defined in Proto3.Suite.DotProto.Rendering

Pretty DotProtoPackageSpec Source # 
Instance details

Defined in Proto3.Suite.DotProto.Rendering

Pretty DotProtoImportQualifier Source # 
Instance details

Defined in Proto3.Suite.DotProto.Rendering

Pretty DotProtoImport Source # 
Instance details

Defined in Proto3.Suite.DotProto.Rendering

Pretty DotProtoIdentifier Source # 
Instance details

Defined in Proto3.Suite.DotProto.Rendering

Pretty a => Pretty [a] 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Methods

pPrintPrec :: PrettyLevel -> Rational -> [a] -> Doc #

pPrint :: [a] -> Doc #

pPrintList :: PrettyLevel -> [[a]] -> Doc #

Pretty a => Pretty (Maybe a) 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

(Pretty a, Pretty b) => Pretty (Either a b) 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Methods

pPrintPrec :: PrettyLevel -> Rational -> Either a b -> Doc #

pPrint :: Either a b -> Doc #

pPrintList :: PrettyLevel -> [Either a b] -> Doc #

(Pretty a, Pretty b) => Pretty (a, b) 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Methods

pPrintPrec :: PrettyLevel -> Rational -> (a, b) -> Doc #

pPrint :: (a, b) -> Doc #

pPrintList :: PrettyLevel -> [(a, b)] -> Doc #

(Pretty a, Pretty b, Pretty c) => Pretty (a, b, c) 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Methods

pPrintPrec :: PrettyLevel -> Rational -> (a, b, c) -> Doc #

pPrint :: (a, b, c) -> Doc #

pPrintList :: PrettyLevel -> [(a, b, c)] -> Doc #

(Pretty a, Pretty b, Pretty c, Pretty d) => Pretty (a, b, c, d) 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Methods

pPrintPrec :: PrettyLevel -> Rational -> (a, b, c, d) -> Doc #

pPrint :: (a, b, c, d) -> Doc #

pPrintList :: PrettyLevel -> [(a, b, c, d)] -> Doc #

(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e) => Pretty (a, b, c, d, e) 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Methods

pPrintPrec :: PrettyLevel -> Rational -> (a, b, c, d, e) -> Doc #

pPrint :: (a, b, c, d, e) -> Doc #

pPrintList :: PrettyLevel -> [(a, b, c, d, e)] -> Doc #

(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f) => Pretty (a, b, c, d, e, f) 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Methods

pPrintPrec :: PrettyLevel -> Rational -> (a, b, c, d, e, f) -> Doc #

pPrint :: (a, b, c, d, e, f) -> Doc #

pPrintList :: PrettyLevel -> [(a, b, c, d, e, f)] -> Doc #

(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f, Pretty g) => Pretty (a, b, c, d, e, f, g) 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Methods

pPrintPrec :: PrettyLevel -> Rational -> (a, b, c, d, e, f, g) -> Doc #

pPrint :: (a, b, c, d, e, f, g) -> Doc #

pPrintList :: PrettyLevel -> [(a, b, c, d, e, f, g)] -> Doc #

(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f, Pretty g, Pretty h) => Pretty (a, b, c, d, e, f, g, h) 
Instance details

Defined in Text.PrettyPrint.HughesPJClass

Methods

pPrintPrec :: PrettyLevel -> Rational -> (a, b, c, d, e, f, g, h) -> Doc #

pPrint :: (a, b, c, d, e, f, g, h) -> Doc #

pPrintList :: PrettyLevel -> [(a, b, c, d, e, f, g, h)] -> Doc #

data Streaming Source #

Constructors

Streaming 
NonStreaming 

Instances

Instances details
Eq Streaming Source # 
Instance details

Defined in Proto3.Suite.DotProto.AST

Show Streaming Source # 
Instance details

Defined in Proto3.Suite.DotProto.AST

Arbitrary Streaming Source # 
Instance details

Defined in Proto3.Suite.DotProto.AST

Pretty Streaming Source # 
Instance details

Defined in Proto3.Suite.DotProto.Rendering

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.

data Packing Source #

Constructors

PackedField 
UnpackedField 

Instances

Instances details
Eq Packing Source # 
Instance details

Defined in Proto3.Suite.DotProto.AST

Methods

(==) :: Packing -> Packing -> Bool #

(/=) :: Packing -> Packing -> Bool #

Show Packing Source # 
Instance details

Defined in Proto3.Suite.DotProto.AST

Arbitrary Packing Source # 
Instance details

Defined in Proto3.Suite.DotProto.AST

data DotProtoValue Source #

Matches the definition of constant in the proto3 language spec These are only used as rvalues

data DotProto Source #

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.

Instances

Instances details
Eq DotProto Source # 
Instance details

Defined in Proto3.Suite.DotProto.AST

Show DotProto Source # 
Instance details

Defined in Proto3.Suite.DotProto.AST

Arbitrary DotProto Source # 
Instance details

Defined in Proto3.Suite.DotProto.AST

data DotProtoMeta Source #

Tracks misc metadata about the AST

Constructors

DotProtoMeta 

Fields

  • metaModulePath :: Path

    The "module path" associated with the .proto file from which this AST was parsed. The "module path" is derived from the `--includeDir`-relative .proto filename passed to parseProtoFile. See toModulePath for details on how module path values are constructed. See modulePathModName to see how it is used during code generation.

data DotProtoOption Source #

An option id/value pair, can be attached to many types of statements

data DotProtoImportQualifier Source #

Instances

Instances details
Eq DotProtoImportQualifier Source # 
Instance details

Defined in Proto3.Suite.DotProto.AST

Ord DotProtoImportQualifier Source # 
Instance details

Defined in Proto3.Suite.DotProto.AST

Show DotProtoImportQualifier Source # 
Instance details

Defined in Proto3.Suite.DotProto.AST

Arbitrary DotProtoImportQualifier Source # 
Instance details

Defined in Proto3.Suite.DotProto.AST

Pretty DotProtoImportQualifier Source # 
Instance details

Defined in Proto3.Suite.DotProto.Rendering

newtype Path Source #

Constructors

Path 

Instances

Instances details
Eq Path Source # 
Instance details

Defined in Proto3.Suite.DotProto.AST

Methods

(==) :: Path -> Path -> Bool #

(/=) :: Path -> Path -> Bool #

Ord Path Source # 
Instance details

Defined in Proto3.Suite.DotProto.AST

Methods

compare :: Path -> Path -> Ordering #

(<) :: Path -> Path -> Bool #

(<=) :: Path -> Path -> Bool #

(>) :: Path -> Path -> Bool #

(>=) :: Path -> Path -> Bool #

max :: Path -> Path -> Path #

min :: Path -> Path -> Path #

Show Path Source # 
Instance details

Defined in Proto3.Suite.DotProto.AST

Methods

showsPrec :: Int -> Path -> ShowS #

show :: Path -> String #

showList :: [Path] -> ShowS #

newtype FieldName Source #

The name of some field

Constructors

FieldName 

Fields

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.

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.