[commit: ghc] wip/ci-i386, wip/linters, wip/ww-noinline: HIE: Save module name and module exports (69ebf5c)

git at git.haskell.org git at git.haskell.org
Tue Feb 19 14:13:07 UTC 2019


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

On branches: wip/ci-i386,wip/linters,wip/ww-noinline
Link       : http://ghc.haskell.org/trac/ghc/changeset/69ebf5cb4592b4c89e268937ef7eb96f7c9d4532/ghc

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

commit 69ebf5cb4592b4c89e268937ef7eb96f7c9d4532
Author: Matthew Pickering <matthewtpickering at gmail.com>
Date:   Fri Feb 15 10:14:29 2019 +0000

    HIE: Save module name and module exports


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

69ebf5cb4592b4c89e268937ef7eb96f7c9d4532
 compiler/hieFile/HieAst.hs   | 12 ++++++++++--
 compiler/hieFile/HieTypes.hs | 13 ++++++++++++-
 compiler/main/HscMain.hs     |  5 +++--
 3 files changed, 25 insertions(+), 5 deletions(-)

diff --git a/compiler/hieFile/HieAst.hs b/compiler/hieFile/HieAst.hs
index 0040b30..7fd217c 100644
--- a/compiler/hieFile/HieAst.hs
+++ b/compiler/hieFile/HieAst.hs
@@ -34,6 +34,8 @@ import TcHsSyn                    ( hsLitType, hsPatType )
 import Type                       ( mkFunTys, Type )
 import TysWiredIn                 ( mkListTy, mkSumTy )
 import Var                        ( Id, Var, setVarName, varName, varType )
+import TcRnTypes
+import MkIface                    ( mkIfaceExports )
 
 import HieTypes
 import HieUtils
@@ -87,17 +89,23 @@ modifyState = foldr go id
 type HieM = ReaderT HieState Hsc
 
 -- | Construct an 'HieFile' from the outputs of the typechecker.
-mkHieFile :: ModSummary -> TypecheckedSource -> RenamedSource -> Hsc HieFile
+mkHieFile :: ModSummary
+          -> TcGblEnv
+          -> RenamedSource -> Hsc HieFile
 mkHieFile ms ts rs = do
-  (asts', arr) <- getCompressedAsts ts rs
+  let tc_binds = tcg_binds ts
+  (asts', arr) <- getCompressedAsts tc_binds rs
   let Just src_file = ml_hs_file $ ms_location ms
   src <- liftIO $ BS.readFile src_file
   return $ HieFile
       { hie_version = curHieVersion
       , hie_ghc_version = BSC.pack cProjectVersion
       , hie_hs_file = src_file
+      , hie_module = ms_mod ms
       , hie_types = arr
       , hie_asts = asts'
+      -- mkIfaceExports sorts the AvailInfos for stability
+      , hie_exports = mkIfaceExports (tcg_exports ts)
       , hie_hs_src = src
       }
 
diff --git a/compiler/hieFile/HieTypes.hs b/compiler/hieFile/HieTypes.hs
index c20887f..1b1d8c5 100644
--- a/compiler/hieFile/HieTypes.hs
+++ b/compiler/hieFile/HieTypes.hs
@@ -10,10 +10,11 @@ import GhcPrelude
 import Binary
 import FastString                 ( FastString )
 import IfaceType
-import Module                     ( ModuleName )
+import Module                     ( ModuleName, Module )
 import Name                       ( Name )
 import Outputable hiding ( (<>) )
 import SrcLoc                     ( RealSrcSpan )
+import Avail
 
 import qualified Data.Array as A
 import qualified Data.Map as M
@@ -56,6 +57,9 @@ data HieFile = HieFile
     , hie_hs_file :: FilePath
     -- ^ Initial Haskell source file path
 
+    , hie_module :: Module
+    -- ^ The module this HIE file is for
+
     , hie_types :: A.Array TypeIndex HieTypeFlat
     -- ^ Types referenced in the 'hie_asts'.
     --
@@ -64,6 +68,9 @@ data HieFile = HieFile
     , hie_asts :: HieASTs TypeIndex
     -- ^ Type-annotated abstract syntax trees
 
+    , hie_exports :: [AvailInfo]
+    -- ^ The names that this module exports
+
     , hie_hs_src :: ByteString
     -- ^ Raw bytes of the initial Haskell source
     }
@@ -73,8 +80,10 @@ instance Binary HieFile where
     put_ bh $ hie_version hf
     put_ bh $ hie_ghc_version hf
     put_ bh $ hie_hs_file hf
+    put_ bh $ hie_module hf
     put_ bh $ hie_types hf
     put_ bh $ hie_asts hf
+    put_ bh $ hie_exports hf
     put_ bh $ hie_hs_src hf
 
   get bh = HieFile
@@ -84,6 +93,8 @@ instance Binary HieFile where
     <*> get bh
     <*> get bh
     <*> get bh
+    <*> get bh
+    <*> get bh
 
 
 {-
diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs
index 9a4dd4a..674afc9 100644
--- a/compiler/main/HscMain.hs
+++ b/compiler/main/HscMain.hs
@@ -408,8 +408,9 @@ extract_renamed_stuff mod_summary tc_result = do
 
     -- Create HIE files
     when (gopt Opt_WriteHie dflags) $ do
-        hieFile <- mkHieFile mod_summary (tcg_binds tc_result)
-                                         (fromJust rn_info)
+        -- I assume this fromJust is safe because `-fwrite-hie-file`
+        -- enables the option which keeps the renamed source.
+        hieFile <- mkHieFile mod_summary tc_result (fromJust rn_info)
         let out_file = ml_hie_file $ ms_location mod_summary
         liftIO $ writeHieFile out_file hieFile
 



More information about the ghc-commits mailing list