Building an empty module with profiling requires profiling libraries for integer-gmp
{-# LANGUAGE NoImplicitPrelude #-}
module A where
$ ghc-stage2 -prof -c A.hs
Top level:
Failed to load interface for ‛GHC.Integer.Type’
Perhaps you haven't installed the profiling libraries for package ‛integer-gmp’?
Use -v to see a list of the files searched for.
I can't built module A
without profiling libraries for integer-gmp
, even though I don't use integer-gmp
anywhere in the module.
This happens because the Tidy Core
pass attempts to look up the mkInteger
name (in order to desugar integer literals) even when there are no integer literals in the module.
The obvious fix is to lazily look up mkInteger
in Coreprep.lookupMkIntegerName
:
diff --git a/compiler/coreSyn/CorePrep.lhs b/compiler/coreSyn/CorePrep.lhs
index 5e0cd65..9836982 100644
--- a/compiler/coreSyn/CorePrep.lhs
+++ b/compiler/coreSyn/CorePrep.lhs
@@ -56,6 +56,7 @@ import Config
import Data.Bits
import Data.List ( mapAccumL )
import Control.Monad
+import System.IO.Unsafe ( unsafeInterleaveIO )
\end{code}
-- ---------------------------------------------------------------------------
@@ -1119,6 +1120,7 @@ lookupMkIntegerName dflags hsc_env
else if thisPackage dflags == integerPackageId
then return $ panic "Can't use Integer in integer"
else liftM tyThingId
+ $ unsafeInterleaveIO
$ initTcForLookup hsc_env (tcLookupGlobal mkIntegerName)
mkInitialCorePrepEnv :: DynFlags -> HscEnv -> IO CorePrepEnv
This way, we don't attempt to look up mkInteger
until we actually need it, i.e. if there are integer literals that we must desugar.
Relevant commits are 2ef5cd26 and fdd552e0
Trac metadata
Trac field | Value |
---|---|
Version | 7.7 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler (Type checker) |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |