proto3-suite-0.7.0: A higher-level API to the proto3-wire library
Safe HaskellNone
LanguageHaskell2010

Proto3.Suite.DotProto.Internal

Description

This module provides misc internal helpers and utilities

Synopsis

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 #

Given an effectful projection from a into a monoid r, retrieve the sum of all a values in an s structure as targetted by the GettingM optic. Note that the Monoid constraint on r is implicit via Const, but we note it in the type for clarity.

mapKeysM :: (Monad m, Ord k2) => (k1 -> m k2) -> Map k1 a -> m (Map k2 a) Source #

>>> :set -XOverloadedStrings

dieLines :: MonadIO m => Text -> m a Source #

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

data DotProtoKind Source #

Whether a definition is an enumeration or a message

Instances

Instances details
Bounded DotProtoKind Source # 
Instance details

Defined in Proto3.Suite.DotProto.Internal

Enum DotProtoKind Source # 
Instance details

Defined in Proto3.Suite.DotProto.Internal

Eq DotProtoKind Source # 
Instance details

Defined in Proto3.Suite.DotProto.Internal

Ord DotProtoKind Source # 
Instance details

Defined in Proto3.Suite.DotProto.Internal

Show DotProtoKind Source # 
Instance details

Defined in Proto3.Suite.DotProto.Internal

Generating type contexts from ASTs

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.

Name resolution

toPascalCase :: String -> String Source #

toPascalCase xs' sends a snake-case string 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 #

toCamelCase xs sends a snake-case string xs to a camel-cased string.

toUpperFirst :: String -> String Source #

Uppercases the first character of a string.

Examples

Expand
>>> toUpperFirst "abc"
"Abc"
>>> toUpperFirst ""
""

segmentBy :: (a -> Bool) -> [a] -> [Either [a] [a]] Source #

segmentBy p xs partitions xs into segments of Either [a] [a] with:

  • Right sublists containing elements satisfying p, otherwise;
  • Left sublists containing elements that do not satisfy p

Examples

Expand
>>> segmentBy (\c -> c == '_') "abc_123_xyz"
[Left "abc",Right "_",Left "123",Right "_",Left "xyz"]

suffixBy :: forall a. (a -> Bool) -> [a] -> Either [a] ([a], [a]) Source #

suffixBy p xs yields Right (xs', suf) if suf is the longest suffix satisfying p and xs' is the rest of the rest, otherwise the string is given back as Left xs signifying xs had no suffix satisfying p.

typeLikeName :: MonadError CompileError m => String -> m String Source #

typeLikeName xs produces either the pascal-cased version of the string xs 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 #

fieldLikeName field is the casing transformation used to produce record selectors from message fields. If field is prefixed by a span of uppercase characters then that prefix will be lowercased while the remaining string is left unchanged.

prefixedMethodName :: MonadError CompileError m => String -> String -> m String Source #

prefixedMethodName service method produces a Haskell record selector name for the service method method by joining the names service, method under concatenation on a camel-casing transformation.

prefixedFieldName :: MonadError CompileError m => String -> String -> m String Source #

prefixedFieldName prefix field constructs a Haskell record selector name by prepending prefix in camel-case to the message field/service method name field.

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

Codegen bookkeeping helpers

data QualifiedField Source #

Bookeeping for qualified fields

data FieldInfo Source #

Bookkeeping for fields

Instances

Instances details
Show FieldInfo Source # 
Instance details

Defined in Proto3.Suite.DotProto.Internal

data OneofField Source #

Bookkeeping for oneof fields

Constructors

OneofField 

Instances

Instances details
Show OneofField Source # 
Instance details

Defined in Proto3.Suite.DotProto.Internal

foldQF 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.

Errors