File tree Expand file tree Collapse file tree 3 files changed +31
-10
lines changed
Expand file tree Collapse file tree 3 files changed +31
-10
lines changed Original file line number Diff line number Diff line change 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
911{-# OPTIONS_GHC -Wno-warnings-deprecations #-}
10- -- TODO We want to import GHC.Internal.Base (BCO, mkApUpd0#, newBCO#) instead
11- -- of from GHC.Exts when we can require of the bootstrap compiler to have
12- -- ghc-internal.
12+ #endif
1313
1414--
1515-- (c) The University of Glasgow 2002-2006
@@ -30,7 +30,13 @@ import Data.Array.Base
3030import Foreign hiding (newArray )
3131import Unsafe.Coerce (unsafeCoerce )
3232import GHC.Arr ( Array (.. ) )
33+ -- When ghc-internal is available prefer the non-deprecated exports.
34+ #ifdef HAVE_GHC_INTERNAL
35+ import GHC.Exts hiding ( BCO , mkApUpd0 #, newBCO # )
36+ import GHC.Internal.Base ( BCO , mkApUpd0 #, newBCO # )
37+ #else
3338import GHC.Exts
39+ #endif
3440import GHC.IO
3541import Control.Exception ( ErrorCall (.. ) )
3642
Original file line number Diff line number Diff line change 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
47{-# OPTIONS_GHC -Wno-warnings-deprecations #-}
5- -- TODO We want to import GHC.Internal.Desugar instead of GHC.Desugar when we
6- -- can require of the bootstrap compiler to have ghc-internal.
8+ #endif
79
810-- |
911-- Running TH splices
@@ -112,7 +114,12 @@ import Data.IORef
112114import Data.Map (Map )
113115import qualified Data.Map as M
114116import Data.Maybe
117+ -- Prefer the non-deprecated internal path when available.
118+ #ifdef HAVE_GHC_INTERNAL
119+ import GHC.Internal.Desugar (AnnotationWrapper (.. ))
120+ #else
115121import GHC.Desugar (AnnotationWrapper (.. ))
122+ #endif
116123import qualified GHC.Boot.TH.Syntax as TH
117124import Unsafe.Coerce
118125
Original file line number Diff line number Diff line change @@ -86,11 +86,6 @@ library
8686 rts,
8787 array == 0.5.*,
8888 base >= 4.8 && < 4.23,
89- -- ghc-internal == @ProjectVersionForLib@.*
90- -- TODO: Use GHC.Internal.Desugar and GHC.Internal.Base from
91- -- ghc-internal instead of ignoring the deprecation warning in GHCi.TH
92- -- and GHCi.CreateBCO when we require ghc-internal of the bootstrap
93- -- compiler
9489 ghc-prim >= 0.5.0 && < 0.14,
9590 binary == 0.8.*,
9691 bytestring >= 0.10 && < 0.13,
@@ -101,6 +96,19 @@ library
10196 ghc-heap == @ProjectVersionMunged@,
10297 transformers >= 0.5 && < 0.7
10398
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: ghc-internal == @ProjectVersionForLib@.*
110+ CPP-Options: -DHAVE_GHC_INTERNAL
111+
104112 if flag(bootstrap)
105113 build-depends:
106114 ghc-boot-th-next == @ProjectVersionMunged@
You can’t perform that action at this time.
0 commit comments