[commit: ghc] ghc-8.0: Ensure Typeable declarations end up in boot interface files (09665a7)

git at git.haskell.org git at git.haskell.org
Wed Apr 20 11:08:54 UTC 2016


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

On branch  : ghc-8.0
Link       : http://ghc.haskell.org/trac/ghc/changeset/09665a7e678691ca03702854d0a1f76812a11c1a/ghc

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

commit 09665a7e678691ca03702854d0a1f76812a11c1a
Author: Ben Gamari <bgamari.foss at gmail.com>
Date:   Wed Apr 20 12:05:13 2016 +0200

    Ensure Typeable declarations end up in boot interface files
    
    Previously we neglected to emit Typeable TyCon and Module declarations
    when typechecking boot interface files. This resulted in #11824.
    
    Ultimately we'll likely want to do a bit of cleaning in this area but in
    the interest of getting some sort of fix in I'm merging this. Further
    clean-ups to come.
    
    Test Plan: Validate
    
    Reviewers: simonpj, austin
    
    Subscribers: thomie
    
    Differential Revision: https://phabricator.haskell.org/D2108
    
    GHC Trac Issues: #11824
    
    (cherry picked from commit 048d6187b5892502e9bc75abfb21f9bd848a29cb)


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

09665a7e678691ca03702854d0a1f76812a11c1a
 compiler/typecheck/TcRnDriver.hs       | 7 +++++--
 testsuite/tests/typecheck/T11824/all.T | 2 +-
 2 files changed, 6 insertions(+), 3 deletions(-)

diff --git a/compiler/typecheck/TcRnDriver.hs b/compiler/typecheck/TcRnDriver.hs
index 42d810f..e7328b9 100644
--- a/compiler/typecheck/TcRnDriver.hs
+++ b/compiler/typecheck/TcRnDriver.hs
@@ -653,7 +653,6 @@ tcRnHsBootDecls hsc_src decls
         -- See Note [Extra dependencies from .hs-boot files] in RnSource
         ; (gbl_env, lie) <- captureConstraints $ setGblEnv tcg_env $ do {
 
-
                 -- Check for illegal declarations
         ; case group_tail of
              Just (SpliceDecl d _, _) -> badBootDecl hsc_src "splice" d
@@ -669,6 +668,10 @@ tcRnHsBootDecls hsc_src decls
              <- tcTyClsInstDecls tycl_decls inst_decls deriv_decls val_binds
         ; setGblEnv tcg_env     $ do {
 
+                -- Emit Typeable declarations
+        ; tcg_env <- setGblEnv tcg_env mkTypeableBinds
+        ; setGblEnv tcg_env $ do {
+
                 -- Typecheck value declarations
         ; traceTc "Tc5" empty
         ; val_ids <- tcHsBootSigs val_binds val_sigs
@@ -691,7 +694,7 @@ tcRnHsBootDecls hsc_src decls
               }
 
         ; setGlobalTypeEnv gbl_env type_env2
-   }}
+   }}}
    ; traceTc "boot" (ppr lie); return gbl_env }
 
 badBootDecl :: HscSource -> String -> Located decl -> TcM ()
diff --git a/testsuite/tests/typecheck/T11824/all.T b/testsuite/tests/typecheck/T11824/all.T
index 90aaa1e..9a435ab 100644
--- a/testsuite/tests/typecheck/T11824/all.T
+++ b/testsuite/tests/typecheck/T11824/all.T
@@ -1 +1 @@
-test('T11824', expect_broken(11824), compile_and_run, [''])
\ No newline at end of file
+test('T11824', normal, compile_and_run, [''])
\ No newline at end of file



More information about the ghc-commits mailing list