[commit: ghc] ghc-7.8: fix inconsistency in exported functions from TcSplice.lhs/lhs-boot files when GHCI is not defined (c845391)

git at git.haskell.org git at git.haskell.org
Mon Dec 15 14:55:11 UTC 2014


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

On branch  : ghc-7.8
Link       : http://ghc.haskell.org/trac/ghc/changeset/c84539177e048c159a0de3be25eba27078d87a20/ghc

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

commit c84539177e048c159a0de3be25eba27078d87a20
Author: Karel Gardas <karel.gardas at centrum.cz>
Date:   Fri Jul 18 23:54:52 2014 -0500

    fix inconsistency in exported functions from TcSplice.lhs/lhs-boot files when GHCI is not defined
    
    Summary:
    This patch fixes inconsistency in exported functions from TcSplice.lhs and TcSplice.lhs-boot
    files. It looks like only GHC HEAD is sensitive to it and complains about it while bootstraping
    another HEAD. At least this is what happening on Solaris/AMD64 builder machine where GHC 7.9.20140620
    is used as a boostrap compiler. The failure does not happen on another builders.
    
    Test Plan: validate
    
    Reviewers: austin
    
    Reviewed By: austin
    
    Subscribers: phaskell, simonmar, relrod, carter
    
    Differential Revision: https://phabricator.haskell.org/D74
    
    (cherry picked from commit d996a1bb4db84727fbf1a8e9461a032e04e544e7)


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

c84539177e048c159a0de3be25eba27078d87a20
 compiler/typecheck/TcSplice.lhs-boot | 8 ++++----
 1 file changed, 4 insertions(+), 4 deletions(-)

diff --git a/compiler/typecheck/TcSplice.lhs-boot b/compiler/typecheck/TcSplice.lhs-boot
index c496aed..dccc669 100644
--- a/compiler/typecheck/TcSplice.lhs-boot
+++ b/compiler/typecheck/TcSplice.lhs-boot
@@ -3,7 +3,6 @@ module TcSplice where
 import HsSyn    ( HsSplice, HsBracket, HsQuasiQuote,
                   HsExpr, LHsType, LHsExpr, LPat, LHsDecl )
 import HsExpr   ( PendingRnSplice )
-import Id       ( Id )
 import Name     ( Name )
 import RdrName  ( RdrName )
 import TcRnTypes( TcM, TcId )
@@ -11,6 +10,7 @@ import TcType   ( TcRhoType )
 import Annotations ( Annotation, CoreAnnTarget )
 
 #ifdef GHCI
+import Id       ( Id )
 import qualified Language.Haskell.TH as TH
 #endif
 
@@ -26,20 +26,20 @@ tcTypedBracket :: HsBracket Name
                -> TcRhoType
                -> TcM (HsExpr TcId)
 
-tcTopSpliceExpr :: Bool -> TcM (LHsExpr Id) -> TcM (LHsExpr Id)
-
 runQuasiQuoteDecl :: HsQuasiQuote RdrName -> TcM [LHsDecl RdrName]
 runQuasiQuoteExpr :: HsQuasiQuote RdrName -> TcM (LHsExpr RdrName)
 runQuasiQuoteType :: HsQuasiQuote RdrName -> TcM (LHsType RdrName)
 runQuasiQuotePat  :: HsQuasiQuote RdrName -> TcM (LPat RdrName)
 runAnnotation     :: CoreAnnTarget -> LHsExpr Name -> TcM Annotation
 
+#ifdef GHCI
+tcTopSpliceExpr :: Bool -> TcM (LHsExpr Id) -> TcM (LHsExpr Id)
+
 runMetaE :: LHsExpr Id -> TcM (LHsExpr RdrName)
 runMetaP :: LHsExpr Id -> TcM (LPat RdrName)
 runMetaT :: LHsExpr Id  -> TcM (LHsType RdrName)
 runMetaD :: LHsExpr Id -> TcM [LHsDecl RdrName]
 
-#ifdef GHCI
 lookupThName_maybe :: TH.Name -> TcM (Maybe Name)
 runQuasi :: TH.Q a -> TcM a
 #endif



More information about the ghc-commits mailing list