Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides functions to generate Haskell declarations for protobuf messages
Synopsis
- data CompileError
- = CircularImport FilePath
- | CompileParseError ParseError
- | InternalError String
- | InvalidPackageName DotProtoIdentifier
- | InvalidMethodName DotProtoIdentifier
- | InvalidModuleName String
- | InvalidTypeName String
- | InvalidMapKeyType String
- | NoPackageDeclaration
- | NoSuchType DotProtoIdentifier
- | NonzeroFirstEnumeration String DotProtoIdentifier Int32
- | EmptyEnumeration String
- | Unimplemented String
- data StringType = StringType String String
- data RecordStyle
- parseStringType :: String -> Either String StringType
- type TypeContext = Map DotProtoIdentifier DotProtoTypeInfo
- data CompileArgs = CompileArgs {}
- compileDotProtoFile :: CompileArgs -> IO (Either CompileError ())
- compileDotProtoFileOrDie :: CompileArgs -> IO ()
- renameProtoFile :: MonadError CompileError m => String -> m String
- hsModuleForDotProto :: MonadError CompileError m => StringType -> RecordStyle -> ([HsImportDecl], [HsDecl]) -> DotProto -> TypeContext -> m HsModule
- renderHsModuleForDotProto :: MonadError CompileError m => StringType -> RecordStyle -> ([HsImportDecl], [HsDecl]) -> DotProto -> TypeContext -> m String
- readDotProtoWithContext :: (MonadError CompileError m, MonadIO m) => [FilePath] -> FilePath -> m (DotProto, TypeContext)
Documentation
data CompileError Source #
Instances
Eq CompileError Source # | |
Defined in Proto3.Suite.DotProto.Internal (==) :: CompileError -> CompileError -> Bool Source # (/=) :: CompileError -> CompileError -> Bool Source # | |
Show CompileError Source # | |
Defined in Proto3.Suite.DotProto.Internal |
data StringType Source #
StringType String String | Qualified module name, then unqualified type name. |
data RecordStyle Source #
Instances
Eq RecordStyle Source # | |
Defined in Proto3.Suite.DotProto.Generate (==) :: RecordStyle -> RecordStyle -> Bool Source # (/=) :: RecordStyle -> RecordStyle -> Bool Source # | |
Read RecordStyle Source # | |
Defined in Proto3.Suite.DotProto.Generate | |
Show RecordStyle Source # | |
Defined in Proto3.Suite.DotProto.Generate |
type TypeContext = Map DotProtoIdentifier DotProtoTypeInfo Source #
A mapping from .proto type identifiers to their type information
data CompileArgs Source #
CompileArgs | |
|
compileDotProtoFile :: CompileArgs -> IO (Either CompileError ()) Source #
Generate a Haskell module corresponding to a .proto
file
compileDotProtoFileOrDie :: CompileArgs -> IO () Source #
Same as compileDotProtoFile
, except terminates the program with an error
message on failure.
renameProtoFile :: MonadError CompileError m => String -> m String Source #
Renaming protobuf file names to valid Haskell module names.
By convention, protobuf filenames are snake case. rnProtoFile
renames
snake-cased protobuf filenames by:
- Replacing occurrences of one or more underscores followed by an alphabetical character with one less underscore.
- Capitalizing the first character following the string of underscores.
Examples
>>>
renameProtoFile @(Either CompileError) "abc_xyz"
Right "AbcXyz"
>>>
renameProtoFile @(Either CompileError) "abc_1bc"
Left (InvalidModuleName "abc_1bc")
>>>
renameProtoFile @(Either CompileError) "_"
Left (InvalidModuleName "_")
:: MonadError CompileError m | |
=> StringType | the module and the type for string |
-> RecordStyle | kind of records to generate |
-> ([HsImportDecl], [HsDecl]) | Extra user-define instances that override default generated instances |
-> DotProto | |
-> TypeContext | |
-> m HsModule |
Compile a Haskell module AST given a DotProto
package AST.
Instances given in eis
override those otherwise generated.
renderHsModuleForDotProto :: MonadError CompileError m => StringType -> RecordStyle -> ([HsImportDecl], [HsDecl]) -> DotProto -> TypeContext -> m String Source #
readDotProtoWithContext :: (MonadError CompileError m, MonadIO m) => [FilePath] -> FilePath -> m (DotProto, TypeContext) Source #
Parses the file at the given path and produces an AST along with a
TypeContext
representing all types from imported .proto
files, using the
first parameter as a list of paths to search for imported files. Terminates
with exit code 1 when an included file cannot be found in the search path.