| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Proto3.Suite.DotProto.Internal
Description
This module provides misc internal helpers and utilities
Synopsis
- foldMapM :: (Foldable t, Monad m, Monoid b, Semigroup b) => (a -> m b) -> t a -> m b
- type GettingM r s a = forall m. Applicative m => (a -> Compose m (Const r) a) -> s -> Compose m (Const r) s
- foldMapOfM :: (Applicative m, Monoid r) => GettingM r s a -> (a -> m r) -> s -> m r
- mapKeysM :: (Monad m, Ord k2) => (k1 -> m k2) -> Map k1 a -> m (Map k2 a)
- dieLines :: MonadIO m => Text -> m a
- toModulePath :: FilePath -> Either String Path
- importProto :: (MonadIO m, MonadError CompileError m) => [FilePath] -> FilePath -> FilePath -> m DotProto
- type FindProtoResult = Either String (Maybe (Path, FilePath))
- findProto :: MonadIO m => [FilePath] -> FilePath -> m FindProtoResult
- badModulePathErrorMsg :: FilePath -> String -> Text
- importNotFoundErrorMsg :: [FilePath] -> FilePath -> FilePath -> Text
- toplevelNotFoundErrorMsg :: [FilePath] -> FilePath -> Text
- absolutePathErrorMsg :: Text
- type TypeContext = Map DotProtoIdentifier DotProtoTypeInfo
- data DotProtoTypeInfo = DotProtoTypeInfo {}
- tiParent :: Lens' DotProtoTypeInfo DotProtoIdentifier
- data DotProtoKind
- dotProtoTypeContext :: MonadError CompileError m => DotProto -> m TypeContext
- definitionTypeContext :: MonadError CompileError m => Path -> DotProtoDefinition -> m TypeContext
- isMessage :: TypeContext -> DotProtoIdentifier -> Bool
- boolOption :: String -> [DotProtoOption] -> Maybe Bool
- isPacked :: [DotProtoOption] -> Bool
- isUnpacked :: [DotProtoOption] -> Bool
- isPackable :: TypeContext -> DotProtoPrimType -> Bool
- isMap :: DotProtoType -> Bool
- concatDotProtoIdentifier :: MonadError CompileError m => DotProtoIdentifier -> DotProtoIdentifier -> m DotProtoIdentifier
- toPascalCase :: String -> String
- toCamelCase :: String -> String
- toUpperFirst :: String -> String
- segmentBy :: (a -> Bool) -> [a] -> [Either [a] [a]]
- suffixBy :: forall a. (a -> Bool) -> [a] -> Either [a] ([a], [a])
- typeLikeName :: MonadError CompileError m => String -> m String
- fieldLikeName :: String -> String
- prefixedEnumFieldName :: String -> String -> String
- prefixedConName :: MonadError CompileError m => String -> String -> m String
- prefixedMethodName :: MonadError CompileError m => String -> String -> m String
- prefixedFieldName :: MonadError CompileError m => String -> String -> m String
- dpIdentUnqualName :: MonadError CompileError m => DotProtoIdentifier -> m String
- dpIdentQualName :: MonadError CompileError m => DotProtoIdentifier -> m String
- nestedTypeName :: MonadError CompileError m => DotProtoIdentifier -> String -> m String
- qualifiedMessageName :: MonadError CompileError m => DotProtoIdentifier -> DotProtoIdentifier -> m String
- qualifiedMessageTypeName :: MonadError CompileError m => TypeContext -> DotProtoIdentifier -> DotProtoIdentifier -> m String
- data QualifiedField = QualifiedField {}
- data FieldInfo
- data OneofField = OneofField {
- oneofType :: String
- subfields :: [OneofSubfield]
- data OneofSubfield = OneofSubfield {}
- getQualifiedFields :: MonadError CompileError m => String -> [DotProtoMessagePart] -> m [QualifiedField]
- foldQF :: (FieldName -> FieldNumber -> a) -> (OneofField -> a) -> QualifiedField -> a
- fieldBinder :: FieldNumber -> String
- oneofSubBinder :: OneofSubfield -> String
- oneofSubDisjunctBinder :: [OneofSubfield] -> String
- 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
- internalError :: MonadError CompileError m => String -> m a
- invalidTypeNameError :: MonadError CompileError m => String -> m a
- _unimplementedError :: MonadError CompileError m => String -> m a
- invalidMethodNameError :: MonadError CompileError m => DotProtoIdentifier -> m a
- noSuchTypeError :: MonadError CompileError m => DotProtoIdentifier -> m a
- protoPackageName :: MonadError CompileError m => DotProtoPackageSpec -> m DotProtoIdentifier
Utilities
foldMapM :: (Foldable t, Monad m, Monoid b, Semigroup b) => (a -> m b) -> t a -> m b Source #
Like foldMap, but with an effectful projection.
type GettingM r s a = forall m. Applicative m => (a -> Compose m (Const r) a) -> s -> Compose m (Const r) s Source #
Like Getting, but allows for retrieving the r
element in some Applicative context m.
foldMapOfM :: (Applicative m, Monoid r) => GettingM r s a -> (a -> m r) -> s -> m r Source #
>>>:set -XOverloadedStrings
Reading files
toModulePath :: FilePath -> Either String Path Source #
toModulePath takes an include-relative path to a .proto file and produces a "module path" which is used during code generation.
Note that, with the exception of the '.proto' portion of the input filepath,
this function interprets . in the filename components as if they were
additional slashes (assuming that the . is not the first character, which
is merely ignored). So e.g. "googleprotobuftimestamp.proto" and
"google.protobuf.timestamp.proto" map to the same module path.
>>>toModulePath "/absolute/path/fails.proto"Left "expected include-relative path"
>>>toModulePath "relative/path/to/file_without_proto_suffix_fails"Left "expected .proto suffix"
>>>toModulePath "relative/path/to/file_without_proto_suffix_fails.txt"Left "expected .proto suffix"
>>>toModulePath "../foo.proto"Left "expected include-relative path, but the path started with ../"
>>>toModulePath "foo..proto"Left "path contained unexpected .. after canonicalization, please use form x.y.z.proto"
>>>toModulePath "foo/bar/baz..proto"Left "path contained unexpected .. after canonicalization, please use form x.y.z.proto"
>>>toModulePath "foo.bar../baz.proto"Left "path contained unexpected .. after canonicalization, please use form x.y.z.proto"
>>>toModulePath "google/protobuf/timestamp.proto"Right (Path {components = "Google" :| ["Protobuf","Timestamp"]})
>>>toModulePath "a/b/c/google.protobuf.timestamp.proto"Right (Path {components = "A" :| ["B","C","Google","Protobuf","Timestamp"]})
>>>toModulePath "foo/FiLeName_underscore.and.then.some.dots.proto"Right (Path {components = "Foo" :| ["FiLeName_underscore","And","Then","Some","Dots"]})
importProto :: (MonadIO m, MonadError CompileError m) => [FilePath] -> FilePath -> FilePath -> m DotProto Source #
importProto searchPaths toplevel inc attempts to import include-relative
inc after locating it somewhere in the searchPaths; toplevel is simply
the path of toplevel .proto being processed so we can report it in an error
message. This function terminates the program if it cannot find the file to
import or if it cannot construct a valid module path from it.
findProto :: MonadIO m => [FilePath] -> FilePath -> m FindProtoResult Source #
Attempts to locate the first (if any) filename that exists on the given search paths, and constructs the "module path" from the given include-relative filename (2nd parameter). Terminates the program with an error if the given pathname is not relative.
Pretty Error Messages
Type context
type TypeContext = Map DotProtoIdentifier DotProtoTypeInfo Source #
A mapping from .proto type identifiers to their type information
data DotProtoTypeInfo Source #
Information about messages and enumerations
Constructors
| DotProtoTypeInfo | |
Fields
| |
Instances
| Show DotProtoTypeInfo Source # | |
Defined in Proto3.Suite.DotProto.Internal Methods showsPrec :: Int -> DotProtoTypeInfo -> ShowS # show :: DotProtoTypeInfo -> String # showList :: [DotProtoTypeInfo] -> ShowS # | |
data DotProtoKind Source #
Whether a definition is an enumeration or a message
Constructors
| DotProtoKindEnum | |
| DotProtoKindMessage |
Instances
Generating type contexts from ASTs
dotProtoTypeContext :: MonadError CompileError m => DotProto -> m TypeContext Source #
definitionTypeContext :: MonadError CompileError m => Path -> DotProtoDefinition -> m TypeContext Source #
isMessage :: TypeContext -> DotProtoIdentifier -> Bool Source #
boolOption :: String -> [DotProtoOption] -> Maybe Bool Source #
isPacked :: [DotProtoOption] -> Bool Source #
isUnpacked :: [DotProtoOption] -> Bool Source #
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.
isMap :: DotProtoType -> Bool Source #
Name resolution
concatDotProtoIdentifier :: MonadError CompileError m => DotProtoIdentifier -> DotProtoIdentifier -> m DotProtoIdentifier Source #
toPascalCase :: String -> String Source #
sends a snake-case string toPascalCase xs'xs to a pascal-cased string. Trailing underscores are not dropped
from the input string and exactly double underscores are replaced by a single underscore.
toCamelCase :: String -> String Source #
sends a snake-case string toCamelCase xsxs to a camel-cased string.
toUpperFirst :: String -> String Source #
Uppercases the first character of a string.
Examples
>>>toUpperFirst "abc""Abc"
>>>toUpperFirst """"
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.
prefixedConName :: MonadError CompileError m => String -> String -> m String Source #
prefixedMethodName :: MonadError CompileError m => String -> String -> m String Source #
produces a Haskell record selector name for the service method prefixedMethodName service methodmethod by
joining the names service, method under concatenation on a camel-casing transformation.
prefixedFieldName :: MonadError CompileError m => String -> String -> m String Source #
constructs a Haskell record selector name by prepending prefixedFieldName prefix fieldprefix in camel-case
to the message field/service method name field.
dpIdentUnqualName :: MonadError CompileError m => DotProtoIdentifier -> m String Source #
dpIdentQualName :: MonadError CompileError m => DotProtoIdentifier -> m String Source #
nestedTypeName :: MonadError CompileError m => DotProtoIdentifier -> String -> m String Source #
Given a DotProtoIdentifier for the parent type and the unqualified name
of this type, generate the corresponding Haskell name
qualifiedMessageName :: MonadError CompileError m => DotProtoIdentifier -> DotProtoIdentifier -> m String Source #
qualifiedMessageTypeName :: MonadError CompileError m => TypeContext -> DotProtoIdentifier -> DotProtoIdentifier -> m String Source #
Codegen bookkeeping helpers
data QualifiedField Source #
Bookeeping for qualified fields
Constructors
| QualifiedField | |
Fields | |
Instances
| Show QualifiedField Source # | |
Defined in Proto3.Suite.DotProto.Internal Methods showsPrec :: Int -> QualifiedField -> ShowS # show :: QualifiedField -> String # showList :: [QualifiedField] -> ShowS # | |
Bookkeeping for fields
Constructors
| FieldOneOf OneofField | |
| FieldNormal FieldName FieldNumber DotProtoType [DotProtoOption] |
data OneofField Source #
Bookkeeping for oneof fields
Constructors
| OneofField | |
Fields
| |
Instances
| Show OneofField Source # | |
Defined in Proto3.Suite.DotProto.Internal Methods showsPrec :: Int -> OneofField -> ShowS # show :: OneofField -> String # showList :: [OneofField] -> ShowS # | |
data OneofSubfield Source #
Bookkeeping for oneof subfields
Constructors
| OneofSubfield | |
Fields | |
Instances
| Show OneofSubfield Source # | |
Defined in Proto3.Suite.DotProto.Internal Methods showsPrec :: Int -> OneofSubfield -> ShowS # show :: OneofSubfield -> String # showList :: [OneofSubfield] -> ShowS # | |
getQualifiedFields :: MonadError CompileError m => String -> [DotProtoMessagePart] -> m [QualifiedField] Source #
Arguments
| :: (FieldName -> FieldNumber -> a) | projection for normal fields |
| -> (OneofField -> a) | projection for oneof fields |
| -> QualifiedField | |
| -> a |
Project qualified fields, given a projection function per field type.
fieldBinder :: FieldNumber -> String Source #
oneofSubBinder :: OneofSubfield -> String Source #
oneofSubDisjunctBinder :: [OneofSubfield] -> String Source #
Errors
data CompileError Source #
Constructors
Instances
| Eq CompileError Source # | |
Defined in Proto3.Suite.DotProto.Internal | |
| Show CompileError Source # | |
Defined in Proto3.Suite.DotProto.Internal Methods showsPrec :: Int -> CompileError -> ShowS # show :: CompileError -> String # showList :: [CompileError] -> ShowS # | |
internalError :: MonadError CompileError m => String -> m a Source #
invalidTypeNameError :: MonadError CompileError m => String -> m a Source #
_unimplementedError :: MonadError CompileError m => String -> m a Source #
invalidMethodNameError :: MonadError CompileError m => DotProtoIdentifier -> m a Source #
noSuchTypeError :: MonadError CompileError m => DotProtoIdentifier -> m a Source #