Skip to content
Draft
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
11 changes: 10 additions & 1 deletion libraries/ghci/GHCi/CreateBCO.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand All @@ -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(..) )

Expand Down
10 changes: 10 additions & 0 deletions libraries/ghci/GHCi/TH.hs
Original file line number Diff line number Diff line change
@@ -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
Expand Down Expand Up @@ -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
Expand Down
15 changes: 14 additions & 1 deletion libraries/ghci/ghci.cabal.in
Original file line number Diff line number Diff line change
Expand Up @@ -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,
Expand All @@ -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@
Expand Down