Skip to content
Snippets Groups Projects
Commit 226cefd0 authored by Sylvain Henry's avatar Sylvain Henry Committed by Marge Bot
Browse files

Fix fake import in GHC.Exception.Type boot module

It seems like I imported "GHC.Types ()" thinking that it would
transitively import GHC.Num.Integer when I wrote that module; but it
doesn't.

This led to build failures.
See https://mail.haskell.org/pipermail/ghc-devs/2021-March/019641.html
parent 8e054ff3
No related branches found
No related tags found
No related merge requests found
......@@ -147,35 +147,37 @@ default () -- Double isn't available yet
Note [Depend on GHC.Num.Integer]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
The Integer type is special because GHC.Iface.Tidy uses constructors in
GHC.Num.Integer to construct Integer literal values. Currently it reads the
interface file whether or not the current module *has* any Integer literals, so
it's important that GHC.Num.Integer is compiled before any other module.
(There's a hack in GHC to disable this for packages ghc-prim and ghc-bignum
which aren't allowed to contain any Integer literals.)
Likewise we implicitly need Integer when deriving things like Eq instances.
The danger is that if the build system doesn't know about the dependency
on Integer, it'll compile some base module before GHC.Num.Integer,
The Integer type is special because GHC.CoreToStg.Prep.mkConvertNumLiteral
lookups names in ghc-bignum interfaces to construct Integer literal values.
Currently it reads the interface file whether or not the current module *has*
any Integer literals, so it's important that GHC.Num.Integer is compiled before
any other module.
The danger is that if the build system doesn't know about the implicit
dependency on Integer, it'll compile some base module before GHC.Num.Integer,
resulting in:
Failed to load interface for ‘GHC.Num.Integer’
There are files missing in the ‘ghc-bignum’ package,
Bottom line: we make GHC.Base depend on GHC.Num.Integer; and everything
else either depends on GHC.Base, or does not have NoImplicitPrelude
(and hence depends on Prelude).
Note: this is only a problem with the make-based build system. Hadrian doesn't
seem to interleave compilation of modules from separate packages and respects
Note that this is only a problem with the make-based build system. Hadrian
doesn't interleave compilation of modules from separate packages and respects
the dependency between `base` and `ghc-bignum`.
To ensure that GHC.Num.Integer is there, we must ensure that there is a visible
dependency on GHC.Num.Integer from every module in base. We make GHC.Base
depend on GHC.Num.Integer; and everything else either depends on GHC.Base,
directly on GHC.Num.Integer, or does not have NoImplicitPrelude (and hence
depends on Prelude).
The lookup is only disabled for packages ghc-prim and ghc-bignum, which aren't
allowed to contain any Integer literal.
Note [Depend on GHC.Tuple]
~~~~~~~~~~~~~~~~~~~~~~~~~~
Similarly, tuple syntax (or ()) creates an implicit dependency on
GHC.Tuple, so we use the same rule as for Integer --- see Note [Depend on
GHC.Integer] --- to explain this to the build system. We make GHC.Base
GHC.Num.Integer] --- to explain this to the build system. We make GHC.Base
depend on GHC.Tuple, and everything else depends on GHC.Base or Prelude.
-}
......
......@@ -26,7 +26,6 @@ module GHC.Err( absentErr, error, errorWithoutStackTrace, undefined ) where
import GHC.Types (Char, RuntimeRep)
import GHC.Stack.Types
import GHC.Prim
import GHC.Num.Integer () -- See Note [Depend on GHC.Num.Integer] in GHC.Base
import {-# SOURCE #-} GHC.Exception
( errorCallWithCallStackException
, errorCallException )
......
......@@ -9,7 +9,7 @@ module GHC.Exception.Type
, underflowException
) where
import GHC.Types ()
import GHC.Num.Integer () -- See Note [Depend on GHC.Num.Integer] in GHC.Base
data SomeException
divZeroException, overflowException,
......
......@@ -4,7 +4,6 @@
module GHC.IO where
import GHC.Types
import GHC.Num.Integer () -- See Note [Depend on GHC.Num.Integer] in GHC.Base
import {-# SOURCE #-} GHC.Exception.Type (SomeException)
mplusIO :: IO a -> IO a -> IO a
......
......@@ -21,7 +21,6 @@ module Unsafe.Coerce
import GHC.Arr (amap) -- For amap/unsafeCoerce rule
import GHC.Base
import GHC.Num.Integer () -- See Note [Depend on GHC.Num.Integer] in GHC.Base
import GHC.Types
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment