Skip to content

Commit

Permalink
Properly implement import public. (google#329)
Browse files Browse the repository at this point in the history
Fixes google#19.

After this change, if `bar.proto` contains the line

    import public foo.proto

Then it turns into

```
module Proto.Bar(..., module Proto.Foo) where

import Proto.Foo  -- unqualified, to allow the reexport of its definitions
```

The previous hacky approach was: `Proto.Bar` doesn't reexport `Proto.Foo`;
instead, if another file `baz.proto` imports `bar.proto`, *then* the codegen
of `Proto.Baz` imports `Proto.Foo` as well as `Proto.Bar`.  This approach
let us avoid module-level exports, but had two limitations:

1) It violated the principle of "strict dependencies", since `Proto.Baz`
   is importing what is essentially a transitive dependency.
2) Non-codegen modules that import a proto module can't benefit from
   `import public` statements.
  • Loading branch information
judah committed Aug 28, 2019
1 parent 95de4f7 commit 25665e0
Show file tree
Hide file tree
Showing 5 changed files with 67 additions and 23 deletions.
6 changes: 6 additions & 0 deletions Changelog.md
Original file line number Diff line number Diff line change
@@ -1,6 +1,12 @@
# Changelog for `proto-lens-protoc`

## Pending

### Breaking Changes
- Reexport transitive definitions from modules generated for `.proto` files
with `import public` statements (#329).

### Backwards-Compatible Changes
- Fix a potential naming conflict when message types and enum values
are the same except for case.

Expand Down
8 changes: 4 additions & 4 deletions app/protoc-gen-haskell.hs
Original file line number Diff line number Diff line change
Expand Up @@ -41,6 +41,7 @@ import Data.ProtoLens.Compiler.Combinators
( prettyPrint
, prettyPrintModule
, getModuleName
, Module
)
import Data.ProtoLens.Compiler.Generate
import Data.ProtoLens.Compiler.Plugin
Expand Down Expand Up @@ -80,14 +81,13 @@ generateFiles modifyImports header files toGenerate = let
modulePrefix = "Proto"
filesByName = analyzeProtoFiles modulePrefix files
-- The contents of the generated Haskell file for a given .proto file.
modulesToBuild :: ProtoFile -> [Module]
modulesToBuild f = let
deps = descriptor f ^. dependency
imports = Set.toAscList $ Set.fromList
[ haskellModule (filesByName ! exportName)
| dep <- deps
, exportName <- exports (filesByName ! dep)
]
$ map (haskellModule . (filesByName !)) deps
in generateModule (haskellModule f) imports
(publicImports f)
modifyImports
(definitions f)
(collectEnvFromDeps deps filesByName)
Expand Down
3 changes: 3 additions & 0 deletions src/Data/ProtoLens/Compiler/Combinators.hs
Original file line number Diff line number Diff line change
Expand Up @@ -295,6 +295,9 @@ exportWith q = Syntax.EThingWith ()
q
. map (Syntax.ConName ())

exportModule :: ModuleName -> ExportSpec
exportModule = Syntax.EModuleContents ()

type Name = Syntax.Name ()

type Pat = Syntax.Pat ()
Expand Down
47 changes: 41 additions & 6 deletions src/Data/ProtoLens/Compiler/Generate.hs
Original file line number Diff line number Diff line change
Expand Up @@ -60,22 +60,27 @@ data UseRuntime = UseRuntime | UseOriginal
-- input contains all defined names, incl. those in this module
generateModule :: ModuleName
-> [ModuleName] -- ^ The imported modules
-> [ModuleName] -- ^ The publically imported modules
-> ModifyImports
-> Env Name -- ^ Definitions in this file
-> Env QName -- ^ Definitions in the imported modules
-> [ServiceInfo]
-> [Module]
generateModule modName imports modifyImport definitions importedEnv services
generateModule modName imports publicImports modifyImport definitions importedEnv services
= [ Module modName
(Just $ (serviceExports ++) $ concatMap generateExports $ Map.elems definitions)
(Just $ serviceExports
++ concatMap generateExports (Map.elems definitions)
++ map exportModule publicImports)
pragmas
(mainImports ++ sharedImports)
(mainImports ++ sharedImports
++ map importSimple (imports List.\\ publicImports)
++ map importPublic publicImports)
$ (concatMap generateDecls $ Map.toList definitions)
++ map uncommented (concatMap (generateServiceDecls env) services)
, Module fieldModName
Nothing
pragmas
sharedImports
(sharedImports ++ map importSimple imports)
. map uncommented
$ concatMap generateFieldDecls allLensNames
]
Expand Down Expand Up @@ -115,7 +120,6 @@ generateModule modName imports modifyImport definitions importedEnv services
, "Data.Vector.Unboxed"
, "Text.Read"
]
++ map importSimple imports
env = Map.union (unqualifyEnv definitions) importedEnv
generateDecls (protoName, Message m)
= generateMessageDecls fieldModName env (stripDotPrefix protoName) m
Expand Down Expand Up @@ -143,6 +147,24 @@ allMessageFields env info =
map (plainRecordField env) (messageFields info)
++ map (oneofRecordField env) (messageOneofFields info)

{- We import modules as follows:
1) Modules from proto-lens-runtime: import qualified, strip the prefix:
import qualified Data.ProtoLens.Runtime.Data.Text as Data.Text
2) Modules from "import" declarations: import qualified:
import qualified Proto.Foo.Bar
3) Modules from "import public" declarations: import unqualified:
import Proto.Foo.Bar
To reexport the imported declarations from the current module via
module ... (module Proto.Foo.Bar)
the module Proto.Foo.Bar needs to be unqualified.
Alternately we could explicitly enumerate every definition being reexported, but
that would lead to less readable Haddocks and also make codegen a little more
complicated.
-}

importSimple :: ModuleName -> ImportDecl ()
importSimple m = ImportDecl
{ importAnn = ()
Expand All @@ -156,6 +178,19 @@ importSimple m = ImportDecl
, importSpecs = Nothing
}

importPublic :: ModuleName -> ImportDecl ()
importPublic m = ImportDecl
{ importAnn = ()
, importModule = m
-- Don't import qualified so that this module can reexport its definitions.
, importQualified = False
, importSrc = False
, importSafe = False
, importPkg = Nothing
, importAs = Nothing
, importSpecs = Nothing
}

type ModifyImports = ImportDecl () -> ImportDecl ()

reexported :: ModifyImports
Expand Down Expand Up @@ -967,7 +1002,7 @@ fieldAccessorExpr (PlainFieldInfo kind f) = accessorCon @@ fieldOfExp hsFieldNam
-> "Data.ProtoLens.MapField"
@@ fieldOfExp (overloadedField $ keyField entry)
@@ fieldOfExp (overloadedField $ valueField entry)
RepeatedField packed ->
RepeatedField packed ->
"Data.ProtoLens.RepeatedField"
@@ if packed == Packed
then "Data.ProtoLens.Packed"
Expand Down
26 changes: 13 additions & 13 deletions src/Data/ProtoLens/Compiler/Plugin.hs
Original file line number Diff line number Diff line change
Expand Up @@ -42,10 +42,8 @@ data ProtoFile = ProtoFile
, haskellModule :: ModuleName
, definitions :: Env Name
, services :: [ServiceInfo]
-- | The names of proto files exported (transitively, via "import public"
-- decl) by this file.
, exports :: [ProtoFileName]
, exportedEnv :: Env QName
, publicImports :: [ModuleName]
}

-- Given a list of FileDescriptorProtos, collect information about each file
Expand All @@ -59,23 +57,24 @@ analyzeProtoFiles modulePrefix files =
-- The definitions in each input proto file, indexed by filename.
definitionsByName = fmap collectDefinitions filesByName
servicesByName = fmap collectServices filesByName
-- The exports from each .proto file (including any "public import"
-- dependencies), as they appear to other modules that are importing them;
-- i.e., qualified by module name.
exportsByName = transitiveExports files
localExports = Map.intersectionWith qualifyEnv moduleNames definitionsByName
exportedEnvs = fmap (\es -> unions [localExports ! e | e <- es]) exportsByName
exportedEnvs = fmap (foldMap (definitionsByName !)) exportsByName

ingestFile f = ProtoFile
{ descriptor = f
, haskellModule = moduleNames ! n
, haskellModule = m
, definitions = definitionsByName ! n
, services = servicesByName ! n
, exports = exportsByName ! n
, exportedEnv = exportedEnvs ! n
, exportedEnv = qualifyEnv m $ exportedEnvs ! n
, publicImports = [moduleNames ! i | i <- reexported]
}
where
n = f ^. name
m = moduleNames ! n
reexported =
[ (f ^. dependency) !! fromIntegral i
| i <- f ^. publicDependency
]

collectEnvFromDeps :: [ProtoFileName] -> Map ProtoFileName ProtoFile -> Env QName
collectEnvFromDeps deps filesByName =
Expand Down Expand Up @@ -106,11 +105,13 @@ moduleNameStr prefix path = fixModuleName rawModuleName
. splitDirectories $ dropExtension
$ path


-- | Given a list of .proto files (topologically sorted), determine which
-- files' definitions are exported by which files.
--
-- Files only export their own definitions, along with the definitions exported
-- by any "import public" declarations.
-- by any "import public" declarations. (And any definitions that *those* files
-- "import public", etc.)
transitiveExports :: [FileDescriptorProto] -> Map ProtoFileName [ProtoFileName]
-- Accumulate the transitive dependencies by folding over the files in
-- topological order.
Expand All @@ -127,4 +128,3 @@ transitiveExports = foldl' setExportsFromFile Map.empty
| i <- fd ^. publicDependency
]
where n = fd ^. name

0 comments on commit 25665e0

Please sign in to comment.