Skip to content

Commit 9cc2922

Browse files
committed
Conditionalize the ghc-internal dependency on the ghc version.
This change reverts part of !14544, which forces the bootstrap compiler to have ghc-internal. As such it breaks booting with ghc 9.8.4. A better solution would be to make this conditional on the ghc version in the cabal file!
1 parent 9d626be commit 9cc2922

File tree

3 files changed

+33
-2
lines changed

3 files changed

+33
-2
lines changed

libraries/ghci/GHCi/CreateBCO.hs

Lines changed: 10 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,10 @@
66
{-# LANGUAGE UnboxedTuples #-}
77
{-# LANGUAGE RecordWildCards #-}
88
{-# LANGUAGE CPP #-}
9+
-- Only needed when we don't have ghc-internal (and must import deprecated names)
10+
#ifndef HAVE_GHC_INTERNAL
11+
{-# OPTIONS_GHC -Wno-warnings-deprecations #-}
12+
#endif
913

1014
--
1115
-- (c) The University of Glasgow 2002-2006
@@ -26,8 +30,13 @@ import Data.Array.Base
2630
import Foreign hiding (newArray)
2731
import Unsafe.Coerce (unsafeCoerce)
2832
import GHC.Arr ( Array(..) )
29-
import GHC.Exts hiding ( BCO, mkApUpd0#, newBCO# )
33+
-- When ghc-internal is available prefer the non-deprecated exports.
34+
#ifdef HAVE_GHC_INTERNAL
35+
import GHC.Exts hiding ( BCO, mkApUpd0#, newBCO# )
3036
import GHC.Internal.Base ( BCO, mkApUpd0#, newBCO# )
37+
#else
38+
import GHC.Exts
39+
#endif
3140
import GHC.IO
3241
import Control.Exception ( ErrorCall(..) )
3342

libraries/ghci/GHCi/TH.hs

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,11 @@
11
{-# LANGUAGE ScopedTypeVariables, StandaloneDeriving, DeriveGeneric,
22
TupleSections, RecordWildCards, InstanceSigs, CPP #-}
33
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
4+
-- Suppress deprecation warnings only when we must import deprecated symbols
5+
-- (i.e. when ghc-internal isn't available yet).
6+
#ifndef HAVE_GHC_INTERNAL
7+
{-# OPTIONS_GHC -Wno-warnings-deprecations #-}
8+
#endif
49

510
-- |
611
-- Running TH splices
@@ -109,7 +114,12 @@ import Data.IORef
109114
import Data.Map (Map)
110115
import qualified Data.Map as M
111116
import Data.Maybe
117+
-- Prefer the non-deprecated internal path when available.
118+
#ifdef HAVE_GHC_INTERNAL
112119
import GHC.Internal.Desugar (AnnotationWrapper(..))
120+
#else
121+
import GHC.Desugar (AnnotationWrapper(..))
122+
#endif
113123
import qualified GHC.Boot.TH.Syntax as TH
114124
import qualified GHC.Boot.TH.Monad as TH
115125
import Unsafe.Coerce

libraries/ghci/ghci.cabal.in

Lines changed: 13 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -86,7 +86,6 @@ library
8686
rts,
8787
array == 0.5.*,
8888
base >= 4.8 && < 4.23,
89-
ghc-internal >= 9.1001.0 && <=@ProjectVersionForLib@.0,
9089
ghc-prim >= 0.5.0 && < 0.14,
9190
binary == 0.8.*,
9291
bytestring >= 0.10 && < 0.13,
@@ -97,6 +96,19 @@ library
9796
ghc-heap >= 9.10.1 && <=@ProjectVersionMunged@,
9897
transformers >= 0.5 && < 0.7
9998

99+
if impl(ghc > 9.10)
100+
-- ghc-internal is only available (and required) when building
101+
-- with a compiler that itself provides the ghc-internal
102+
-- library. Older bootstrap compilers (<= 9.10) don't ship it,
103+
-- so we must not depend on it in that case.
104+
--
105+
-- When available we depend on the in-tree version (matching
106+
-- @ProjectVersionForLib@) and define HAVE_GHC_INTERNAL so that
107+
-- sources can import the non-deprecated modules from
108+
-- GHC.Internal.* instead of the legacy (deprecated) locations.
109+
Build-Depends: >= 9.1001.0 && <=@ProjectVersionForLib@.0,
110+
CPP-Options: -DHAVE_GHC_INTERNAL
111+
100112
if flag(bootstrap)
101113
build-depends:
102114
ghc-boot-th-next == @ProjectVersionMunged@

0 commit comments

Comments
 (0)