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.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"]})
>>> toModulePath "foo/bar/././baz/../boggle.proto"
Right (Path {components = "Foo" :| ["Bar","Boggle"]})
>>> toModulePath "./foo.proto"
Right (Path {components = "Foo" :| []})

NB: We ignore preceding single . characters >>> toModulePath ".foo.proto" Right (Path {components = Foo :| []})

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

Instances details
Show DotProtoTypeInfo Source # 
Instance details

Defined in Proto3.Suite.DotProto.Internal

data DotProtoKind Source #

Whether a definition is an enumeration or a message

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

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

Instances

Instances details
Show QualifiedField Source # 
Instance details

Defined in Proto3.Suite.DotProto.Internal

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