| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Proto3.Suite.DotProto.Generate
Description
This module provides functions to generate Haskell declarations for protobuf messages
Synopsis
- data CompileError
- type TypeContext = Map DotProtoIdentifier DotProtoTypeInfo
- compileDotProtoFile :: [FilePath] -> FilePath -> [FilePath] -> FilePath -> IO (Either CompileError ())
- compileDotProtoFileOrDie :: [FilePath] -> FilePath -> [FilePath] -> FilePath -> IO ()
- hsModuleForDotProto :: MonadError CompileError m => ([HsImportDecl], [HsDecl]) -> DotProto -> TypeContext -> m HsModule
- renderHsModuleForDotProto :: MonadError CompileError m => ([HsImportDecl], [HsDecl]) -> DotProto -> TypeContext -> m String
- readDotProtoWithContext :: [FilePath] -> FilePath -> IO (Either CompileError (DotProto, TypeContext))
- isPackable :: TypeContext -> DotProtoPrimType -> Bool
- fieldLikeName :: String -> String
- prefixedEnumFieldName :: String -> String -> String
- typeLikeName :: MonadError CompileError m => String -> m String
Documentation
data CompileError Source #
Constructors
Instances
| Eq CompileError Source # | |
Defined in Proto3.Suite.DotProto.Generate | |
| Show CompileError Source # | |
Defined in Proto3.Suite.DotProto.Generate Methods showsPrec :: Int -> CompileError -> ShowS # show :: CompileError -> String # showList :: [CompileError] -> ShowS # | |
type TypeContext = Map DotProtoIdentifier DotProtoTypeInfo Source #
A mapping from .proto type identifiers to their type information
Arguments
| :: [FilePath] | Haskell modules containing instances used to override default generated instances |
| -> FilePath | Output directory |
| -> [FilePath] | List of search paths |
| -> FilePath | Path to |
| -> IO (Either CompileError ()) |
Generate a Haskell module corresponding to a .proto file
compileDotProtoFileOrDie Source #
Arguments
| :: [FilePath] | Haskell modules containing instances used to override default generated instances |
| -> FilePath | Output directory |
| -> [FilePath] | List of search paths |
| -> FilePath | Path to |
| -> IO () |
As compileDotProtoFile, except terminates the program with an error
message on failure.
Arguments
| :: MonadError CompileError m | |
| => ([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 => ([HsImportDecl], [HsDecl]) -> DotProto -> TypeContext -> m String Source #
Compile a DotProto AST into a DotProtoPrimType representing the Haskell
source of a module implementing types and instances for the .proto
messages and enums.
readDotProtoWithContext :: [FilePath] -> FilePath -> IO (Either CompileError (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.
Utilities
isPackable :: TypeContext -> DotProtoPrimType -> Bool Source #
Returns True if the given primitive type is packable. The TypeContext
is used to distinguish Named enums and messages, only the former of which are
packable.
Exposed for unit-testing
fieldLikeName :: String -> String Source #
typeLikeName :: MonadError CompileError m => String -> m String Source #