[commit: haddock] ghc-head, ghc-head1, haddock-quick, ie_avails, wip/T14529, wip/new-tree-one-param, wip/revert-ttg-2017-11-20, wip/ttg-2017-10-13, wip/ttg-2017-10-31, wip/ttg-2017-11-06, wip/ttg2-2017-11-10, wip/ttg3-2017-11-12, wip/ttg4-constraints-2017-11-13, wip/ttg6-unrevert-2017-11-22: Documentation. (0671abf)

git at git.haskell.org git at git.haskell.org
Tue Nov 28 11:49:23 UTC 2017


Repository : ssh://git@git.haskell.org/haddock

On branches: ghc-head,ghc-head1,haddock-quick,ie_avails,wip/T14529,wip/new-tree-one-param,wip/revert-ttg-2017-11-20,wip/ttg-2017-10-13,wip/ttg-2017-10-31,wip/ttg-2017-11-06,wip/ttg2-2017-11-10,wip/ttg3-2017-11-12,wip/ttg4-constraints-2017-11-13,wip/ttg6-unrevert-2017-11-22
Link       : http://git.haskell.org/haddock.git/commitdiff/0671abfe7e8ceae2269467a30b77ed9d9656e2cc

>---------------------------------------------------------------

commit 0671abfe7e8ceae2269467a30b77ed9d9656e2cc
Author: Edward Z. Yang <ezyang at cs.stanford.edu>
Date:   Mon Mar 13 15:13:27 2017 -0700

    Documentation.
    
    Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>


>---------------------------------------------------------------

0671abfe7e8ceae2269467a30b77ed9d9656e2cc
 haddock-api/src/Haddock/Interface/Create.hs | 27 ++++++++++++++++++++++-----
 1 file changed, 22 insertions(+), 5 deletions(-)

diff --git a/haddock-api/src/Haddock/Interface/Create.hs b/haddock-api/src/Haddock/Interface/Create.hs
index 60843ee..78f21ac 100644
--- a/haddock-api/src/Haddock/Interface/Create.hs
+++ b/haddock-api/src/Haddock/Interface/Create.hs
@@ -11,6 +11,10 @@
 -- Maintainer  :  haddock at projects.haskell.org
 -- Stability   :  experimental
 -- Portability :  portable
+--
+-- This module provides a single function 'createInterface',
+-- which creates a Haddock 'Interface' from the typechecking
+-- results 'TypecheckedModule' from GHC.
 -----------------------------------------------------------------------------
 module Haddock.Interface.Create (createInterface) where
 
@@ -54,7 +58,11 @@ import HsDecls ( getConDetails )
 -- | Use a 'TypecheckedModule' to produce an 'Interface'.
 -- To do this, we need access to already processed modules in the topological
 -- sort. That's what's in the 'IfaceMap'.
-createInterface :: TypecheckedModule -> [Flag] -> IfaceMap -> InstIfaceMap -> ErrMsgGhc Interface
+createInterface :: TypecheckedModule
+                -> [Flag]       -- Boolean flags
+                -> IfaceMap     -- Locally processed modules
+                -> InstIfaceMap -- External, already installed interfaces
+                -> ErrMsgGhc Interface
 createInterface tm flags modMap instIfaceMap = do
 
   let ms             = pm_mod_summary . tm_parsed_module $ tm
@@ -518,7 +526,7 @@ mkExportItems
   -> WarningMap
   -> GlobalRdrEnv
   -> [Name]             -- exported names (orig)
-  -> [LHsDecl Name]
+  -> [LHsDecl Name]     -- renamed source declarations
   -> Maps
   -> FixMap
   -> [SrcSpan]          -- splice locations
@@ -716,7 +724,7 @@ moduleExports :: Module           -- ^ Module A (identity, NOT semantic)
               -> WarningMap
               -> GlobalRdrEnv     -- ^ The renaming environment used for A
               -> [Name]           -- ^ All the exports of A
-              -> [LHsDecl Name]   -- ^ All the declarations in A
+              -> [LHsDecl Name]   -- ^ All the renamed declarations in A
               -> IfaceMap         -- ^ Already created interfaces
               -> InstIfaceMap     -- ^ Interfaces in other packages
               -> Maps
@@ -765,8 +773,17 @@ moduleExports thisMod expMod dflags warnings gre _exports decls ifaceMap instIfa
 -- (For more information, see Trac #69)
 
 
-fullModuleContents :: DynFlags -> WarningMap -> GlobalRdrEnv -> Maps -> FixMap -> [SrcSpan]
-                   -> [LHsDecl Name] -> ErrMsgGhc [ExportItem Name]
+-- | Simplified variant of 'mkExportItems', where we can assume that
+-- every locally defined declaration is exported; thus, we just
+-- zip through the renamed declarations.
+fullModuleContents :: DynFlags
+                   -> WarningMap
+                   -> GlobalRdrEnv      -- ^ The renaming environment
+                   -> Maps
+                   -> FixMap
+                   -> [SrcSpan]         -- ^ Locations of all TH splices
+                   -> [LHsDecl Name]    -- ^ All the renamed declarations
+                   -> ErrMsgGhc [ExportItem Name]
 fullModuleContents dflags warnings gre (docMap, argMap, subMap, declMap, instMap) fixMap splices decls =
   liftM catMaybes $ mapM mkExportItem (expandSig decls)
   where



More information about the ghc-commits mailing list