[Git][ghc/ghc][wip/angerman/ghci-ghc-9.8-compat] Conditionalize the ghc-internal dependency on the ghc version.

Moritz Angermann pushed to branch wip/angerman/ghci-ghc-9.8-compat at Glasgow Haskell Compiler / GHC Commits: 7f389f1d by Moritz Angermann at 2025-09-06T06:04:33+09:00 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! - - - - - 3 changed files: - libraries/ghci/GHCi/CreateBCO.hs - libraries/ghci/GHCi/TH.hs - libraries/ghci/ghci.cabal.in Changes: ===================================== libraries/ghci/GHCi/CreateBCO.hs ===================================== @@ -6,6 +6,10 @@ {-# LANGUAGE UnboxedTuples #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE CPP #-} +-- Only needed when we don't have ghc-internal (and must import deprecated names) +#ifndef HAVE_GHC_INTERNAL +{-# OPTIONS_GHC -Wno-warnings-deprecations #-} +#endif -- -- (c) The University of Glasgow 2002-2006 @@ -26,8 +30,13 @@ import Data.Array.Base import Foreign hiding (newArray) import Unsafe.Coerce (unsafeCoerce) import GHC.Arr ( Array(..) ) -import GHC.Exts hiding ( BCO, mkApUpd0#, newBCO# ) +-- When ghc-internal is available prefer the non-deprecated exports. +#ifdef HAVE_GHC_INTERNAL +import GHC.Exts hiding ( BCO, mkApUpd0#, newBCO# ) import GHC.Internal.Base ( BCO, mkApUpd0#, newBCO# ) +#else +import GHC.Exts +#endif import GHC.IO import Control.Exception ( ErrorCall(..) ) ===================================== libraries/ghci/GHCi/TH.hs ===================================== @@ -1,6 +1,11 @@ {-# LANGUAGE ScopedTypeVariables, StandaloneDeriving, DeriveGeneric, TupleSections, RecordWildCards, InstanceSigs, CPP #-} {-# OPTIONS_GHC -fno-warn-name-shadowing #-} +-- Suppress deprecation warnings only when we must import deprecated symbols +-- (i.e. when ghc-internal isn't available yet). +#ifndef HAVE_GHC_INTERNAL +{-# OPTIONS_GHC -Wno-warnings-deprecations #-} +#endif -- | -- Running TH splices @@ -109,7 +114,12 @@ import Data.IORef import Data.Map (Map) import qualified Data.Map as M import Data.Maybe +-- Prefer the non-deprecated internal path when available. +#ifdef HAVE_GHC_INTERNAL import GHC.Internal.Desugar (AnnotationWrapper(..)) +#else +import GHC.Desugar (AnnotationWrapper(..)) +#endif import qualified GHC.Boot.TH.Syntax as TH import qualified GHC.Boot.TH.Monad as TH import Unsafe.Coerce ===================================== libraries/ghci/ghci.cabal.in ===================================== @@ -86,7 +86,6 @@ library rts, array == 0.5.*, base >= 4.8 && < 4.23, - ghc-internal >= 9.1001.0 && <=@ProjectVersionForLib@.0, ghc-prim >= 0.5.0 && < 0.14, binary == 0.8.*, bytestring >= 0.10 && < 0.13, @@ -97,6 +96,20 @@ library ghc-heap >= 9.10.1 && <=@ProjectVersionMunged@, transformers >= 0.5 && < 0.7 + if impl(ghc > 9.10) + -- ghc-internal is only available (and required) when building + -- with a compiler that itself provides the ghc-internal + -- library. Older bootstrap compilers (<= 9.10) don't ship it, + -- so we must not depend on it in that case. + -- + -- When available we depend on the in-tree version (matching + -- @ProjectVersionForLib@) and define HAVE_GHC_INTERNAL so that + -- sources can import the non-deprecated modules from + -- GHC.Internal.* instead of the legacy (deprecated) locations. + Build-Depends: + ghc-internal >= 9.1001.0 && <=@ProjectVersionForLib@.0 + CPP-Options: -DHAVE_GHC_INTERNAL + if flag(bootstrap) build-depends: ghc-boot-th-next == @ProjectVersionMunged@ View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7f389f1d67f7cc9b0c634290dea8570f... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7f389f1d67f7cc9b0c634290dea8570f... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Moritz Angermann (@angerman)