[commit: ghc] master: Fix a build problem with integer-simple (fdd552e)
Ian Lynagh
igloo at earth.li
Sun May 19 19:32:59 CEST 2013
Repository : http://darcs.haskell.org/ghc.git/
On branch : master
https://github.com/ghc/ghc/commit/fdd552e0ecaa17300670a48562995040e1d6687e
>---------------------------------------------------------------
commit fdd552e0ecaa17300670a48562995040e1d6687e
Author: Ian Lynagh <ian at well-typed.com>
Date: Sun May 19 16:19:47 2013 +0100
Fix a build problem with integer-simple
We were trying to look up the mkInteger Id before we'd compiled
the Integer modules. I'm not sure why this never showed up with
integer-gmp; possibly we just always got lucky with the build
order.
>---------------------------------------------------------------
compiler/coreSyn/CorePrep.lhs | 14 +++++++++++---
compiler/main/TidyPgm.lhs | 4 +---
2 files changed, 12 insertions(+), 6 deletions(-)
diff --git a/compiler/coreSyn/CorePrep.lhs b/compiler/coreSyn/CorePrep.lhs
index 084c853..e55f595 100644
--- a/compiler/coreSyn/CorePrep.lhs
+++ b/compiler/coreSyn/CorePrep.lhs
@@ -8,7 +8,8 @@ Core pass to saturate constructors and PrimOps
{-# LANGUAGE BangPatterns #-}
module CorePrep (
- corePrepPgm, corePrepExpr, cvtLitInteger
+ corePrepPgm, corePrepExpr, cvtLitInteger,
+ lookupMkIntegerName,
) where
#include "HsVersions.h"
@@ -40,6 +41,7 @@ import TysWiredIn
import DataCon
import PrimOp
import BasicTypes
+import Module
import UniqSupply
import Maybes
import OrdList
@@ -1107,10 +1109,16 @@ data CorePrepEnv = CPE {
cpe_mkIntegerId :: Id
}
+lookupMkIntegerName :: DynFlags -> HscEnv -> IO Id
+lookupMkIntegerName dflags hsc_env
+ = if thisPackage dflags == primPackageId
+ then return $ panic "Can't use Integer in ghc-prim"
+ else liftM tyThingId
+ $ initTcForLookup hsc_env (tcLookupGlobal mkIntegerName)
+
mkInitialCorePrepEnv :: DynFlags -> HscEnv -> IO CorePrepEnv
mkInitialCorePrepEnv dflags hsc_env
- = do mkIntegerId <- liftM tyThingId
- $ initTcForLookup hsc_env (tcLookupGlobal mkIntegerName)
+ = do mkIntegerId <- lookupMkIntegerName dflags hsc_env
return $ CPE {
cpe_dynFlags = dflags,
cpe_env = emptyVarEnv,
diff --git a/compiler/main/TidyPgm.lhs b/compiler/main/TidyPgm.lhs
index 6bb2861..1c6bb39 100644
--- a/compiler/main/TidyPgm.lhs
+++ b/compiler/main/TidyPgm.lhs
@@ -36,7 +36,6 @@ import Name hiding (varName)
import NameSet
import NameEnv
import Avail
-import PrelNames
import IfaceEnv
import TcEnv
import TcRnMonad
@@ -986,8 +985,7 @@ tidyTopBinds :: HscEnv
-> IO (TidyEnv, CoreProgram)
tidyTopBinds hsc_env this_mod unfold_env init_occ_env binds
- = do mkIntegerId <- liftM tyThingId
- $ initTcForLookup hsc_env (tcLookupGlobal mkIntegerName)
+ = do mkIntegerId <- lookupMkIntegerName dflags hsc_env
return $ tidy mkIntegerId init_env binds
where
dflags = hsc_dflags hsc_env
More information about the ghc-commits
mailing list