[commit: ghc] master: Generate real (but empty) object files for signatures. (46b278f)

git at git.haskell.org git at git.haskell.org
Wed Dec 3 02:06:04 UTC 2014


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/46b278fb75c708256e0a8cfefb8a2bce10fddef4/ghc

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

commit 46b278fb75c708256e0a8cfefb8a2bce10fddef4
Author: Edward Z. Yang <ezyang at cs.stanford.edu>
Date:   Mon Dec 1 21:07:33 2014 -0800

    Generate real (but empty) object files for signatures.
    
    Summary:
    It's not great, but it preserves a nice invariant that every Haskell
    source file has an object file (we already have a hack in place ensure
    this is the case for hs-boot files) and further ensures every package
    has a library associated with it (which would not be the case if
    the package had all signatures and we didn't make object files.)
    
    Contains Cabal submodule update.
    
    Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>
    
    Test Plan: validate
    
    Reviewers: simonpj, austin
    
    Subscribers: carter, thomie
    
    Differential Revision: https://phabricator.haskell.org/D548


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

46b278fb75c708256e0a8cfefb8a2bce10fddef4
 compiler/main/DriverPipeline.hs           | 49 ++++++++++++++++++++++++++-----
 compiler/main/HscMain.hs                  |  5 +++-
 compiler/main/HscTypes.lhs                |  1 +
 docs/users_guide/separate_compilation.xml |  6 ++--
 libraries/Cabal                           |  2 +-
 5 files changed, 50 insertions(+), 13 deletions(-)

diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs
index eefa0a6..fdec73e 100644
--- a/compiler/main/DriverPipeline.hs
+++ b/compiler/main/DriverPipeline.hs
@@ -240,7 +240,7 @@ compileOne' m_tc_result mHscMessage
 
                _ ->
                    case ms_hsc_src summary of
-                   t | isHsBootOrSig t ->
+                   HsBootFile ->
                        do (iface, changed, details) <- hscSimpleIface hsc_env tc_result mb_old_hash
                           hscWriteIface dflags iface changed summary
                           touchObjectFile dflags object_filename
@@ -248,7 +248,23 @@ compileOne' m_tc_result mHscMessage
                                                hm_iface    = iface,
                                                hm_linkable = maybe_old_linkable })
 
-                   _ -> do guts0 <- hscDesugar hsc_env summary tc_result
+                   HsigFile ->
+                       do (iface, changed, details) <-
+                                    hscSimpleIface hsc_env tc_result mb_old_hash
+                          hscWriteIface dflags iface changed summary
+                          compileEmptyStub dflags hsc_env basename location
+
+                          -- Same as Hs
+                          o_time <- getModificationUTCTime object_filename
+                          let linkable =
+                                  LM o_time this_mod [DotO object_filename]
+
+                          return (HomeModInfo{ hm_details  = details,
+                                               hm_iface    = iface,
+                                               hm_linkable = Just linkable })
+
+                   HsSrcFile ->
+                        do guts0 <- hscDesugar hsc_env summary tc_result
                            guts <- hscSimplify hsc_env guts0
                            (iface, changed, details, cgguts) <- hscNormalIface hsc_env guts mb_old_hash
                            hscWriteIface dflags iface changed summary
@@ -287,6 +303,21 @@ compileStub hsc_env stub_c = do
 
         return stub_o
 
+compileEmptyStub :: DynFlags -> HscEnv -> FilePath -> ModLocation -> IO ()
+compileEmptyStub dflags hsc_env basename location = do
+  -- To maintain the invariant that every Haskell file
+  -- compiles to object code, we make an empty (but
+  -- valid) stub object file for signatures
+  empty_stub <- newTempName dflags "c"
+  writeFile empty_stub ""
+  _ <- runPipeline StopLn hsc_env
+                  (empty_stub, Nothing)
+                  (Just basename)
+                  Persistent
+                  (Just location)
+                  Nothing
+  return ()
+
 -- ---------------------------------------------------------------------------
 -- Link
 
@@ -341,11 +372,7 @@ link' dflags batch_attempt_linking hpt
                           LinkStaticLib -> True
                           _ -> platformBinariesAreStaticLibs (targetPlatform dflags)
 
-            -- Don't attempt to link hsigs; they don't actually produce objects.
-            -- This is in contrast to hs-boot files, which will /eventually/
-            -- get objects.
-            home_mod_infos =
-                filter ((==Nothing).mi_sig_of.hm_iface) (eltsUFM hpt)
+            home_mod_infos = eltsUFM hpt
 
             -- the packages we depend on
             pkg_deps  = concatMap (map fst . dep_pkgs . mi_deps . hm_iface) home_mod_infos
@@ -981,6 +1008,14 @@ runPhase (HscOut src_flavour mod_name result) _ dflags = do
                    -- stamp file for the benefit of Make
                    liftIO $ touchObjectFile dflags o_file
                    return (RealPhase next_phase, o_file)
+            HscUpdateSig ->
+                do -- We need to create a REAL but empty .o file
+                   -- because we are going to attempt to put it in a library
+                   PipeState{hsc_env=hsc_env'} <- getPipeState
+                   let input_fn = expectJust "runPhase" (ml_hs_file location)
+                       basename = dropExtension input_fn
+                   liftIO $ compileEmptyStub dflags hsc_env' basename location
+                   return (RealPhase next_phase, o_file)
             HscRecomp cgguts mod_summary
               -> do output_fn <- phaseOutputFilename next_phase
 
diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs
index fcf0c48..8f8da02 100644
--- a/compiler/main/HscMain.hs
+++ b/compiler/main/HscMain.hs
@@ -647,7 +647,10 @@ hscCompileOneShot' hsc_env mod_summary src_changed
                     t | isHsBootOrSig t ->
                         do (iface, changed, _) <- hscSimpleIface' tc_result mb_old_hash
                            liftIO $ hscWriteIface dflags iface changed mod_summary
-                           return HscUpdateBoot
+                           return (case t of
+                                    HsBootFile -> HscUpdateBoot
+                                    HsigFile -> HscUpdateSig
+                                    HsSrcFile -> panic "hscCompileOneShot Src")
                     _ ->
                         do guts <- hscSimplify' guts0
                            (iface, changed, _details, cgguts) <- hscNormalIface' guts mb_old_hash
diff --git a/compiler/main/HscTypes.lhs b/compiler/main/HscTypes.lhs
index cf3db52..b6e3a98 100644
--- a/compiler/main/HscTypes.lhs
+++ b/compiler/main/HscTypes.lhs
@@ -195,6 +195,7 @@ data HscStatus
     = HscNotGeneratingCode
     | HscUpToDate
     | HscUpdateBoot
+    | HscUpdateSig
     | HscRecomp CgGuts ModSummary
 
 -- -----------------------------------------------------------------------------
diff --git a/docs/users_guide/separate_compilation.xml b/docs/users_guide/separate_compilation.xml
index 43ab182..b30eff8 100644
--- a/docs/users_guide/separate_compilation.xml
+++ b/docs/users_guide/separate_compilation.xml
@@ -966,10 +966,8 @@ ghc -c A.hs
 
       <para>Just like <literal>hs-boot</literal> files, when an
       <literal>hsig</literal> file is compiled it is checked for type
-      consistency against the backing implementation; furthermore, it also
-      produces a pseudo-object file <literal>A.o</literal> which you should
-      not link with.  Signature files are also written in a subset
-      of Haskell similar to essentially identical to that of
+      consistency against the backing implementation.  Signature files are also
+      written in a subset of Haskell essentially identical to that of
       <literal>hs-boot</literal> files.</para>
 
       <para>There is one important gotcha with the current implementation:
diff --git a/libraries/Cabal b/libraries/Cabal
index 6c395bb..ea062bf 160000
--- a/libraries/Cabal
+++ b/libraries/Cabal
@@ -1 +1 @@
-Subproject commit 6c395bb8f22961ce5267df64e6d9351c310fcbb3
+Subproject commit ea062bf522e015f6e643bcc833487098edba8398



More information about the ghc-commits mailing list