[GHC] #8572: Building an empty module with profiling requires profiling libraries for integer-gmp

#8572: Building an empty module with profiling requires profiling libraries for integer-gmp -------------------------------------------+------------------------------- Reporter: parcs | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type checker) | Version: 7.7 Keywords: | Operating System: Architecture: Unknown/Multiple | Unknown/Multiple Difficulty: Unknown | Type of failure: Blocked By: | None/Unknown Related Tickets: | Test Case: | Blocking: -------------------------------------------+------------------------------- {{{ #!haskell {-# 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 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 2ef5cd26db27543ac8664a3d18f45550d0109a8b and fdd552e0ecaa17300670a48562995040e1d6687e -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8572 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8572: Building an empty module with profiling requires profiling libraries for integer-gmp -------------------------------------+------------------------------------- Reporter: parcs | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 7.7 (Type checker) | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => patch -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8572#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8572: Building an empty module with profiling requires profiling libraries for integer-gmp -------------------------------------+------------------------------------- Reporter: parcs | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: | Architecture: Unknown/Multiple Unknown/Multiple | Difficulty: Unknown Type of failure: | Blocked By: None/Unknown | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by thoughtpolice): * cc: hvr (added) * status: patch => infoneeded * component: Compiler (Type checker) => Compiler * milestone: => 7.12.1 Comment: I don't really know if I like this patch. It seems very fragile and most of the code has been refactored now. I think Herbert should take a look, but I hope he'd agree. :) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8572#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8572: Building an empty module with profiling requires profiling libraries for integer-gmp -------------------------------------+------------------------------------- Reporter: parcs | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: | Architecture: Unknown/Multiple Unknown/Multiple | Difficulty: Unknown Type of failure: | Blocked By: None/Unknown | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by hvr): * cc: simonpj (added) Comment: tbh, I've got a bad gut feeling too... this should be fixed properly, but I'm not sure how yet... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8572#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8572: Building an empty module with profiling requires profiling libraries for integer-gmp -------------------------------------+------------------------------------- Reporter: parcs | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.7 Resolution: | Keywords: integer-gmp Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * keywords: => integer-gmp -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8572#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8572: Building an empty module with profiling requires profiling libraries for integer-gmp -------------------------------------+------------------------------------- Reporter: parcs | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.1 Component: Profiling | Version: 7.7 Resolution: | Keywords: integer-gmp Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * component: Compiler => Profiling -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8572#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC