Moritz Angermann pushed to branch wip/angerman/ghci-ghc-9.8-compat at Glasgow Haskell Compiler / GHC

Commits:

3 changed files:

Changes:

  • libraries/ghci/GHCi/CreateBCO.hs
    ... ... @@ -6,6 +6,10 @@
    6 6
     {-# LANGUAGE UnboxedTuples #-}
    
    7 7
     {-# LANGUAGE RecordWildCards #-}
    
    8 8
     {-# 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
    
    9 13
     
    
    10 14
     --
    
    11 15
     --  (c) The University of Glasgow 2002-2006
    
    ... ... @@ -26,8 +30,13 @@ import Data.Array.Base
    26 30
     import Foreign hiding (newArray)
    
    27 31
     import Unsafe.Coerce (unsafeCoerce)
    
    28 32
     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# )
    
    30 36
     import GHC.Internal.Base ( BCO, mkApUpd0#, newBCO# )
    
    37
    +#else
    
    38
    +import GHC.Exts
    
    39
    +#endif
    
    31 40
     import GHC.IO
    
    32 41
     import Control.Exception ( ErrorCall(..) )
    
    33 42
     
    

  • libraries/ghci/GHCi/TH.hs
    1 1
     {-# LANGUAGE ScopedTypeVariables, StandaloneDeriving, DeriveGeneric,
    
    2 2
         TupleSections, RecordWildCards, InstanceSigs, CPP #-}
    
    3 3
     {-# 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
    
    4 9
     
    
    5 10
     -- |
    
    6 11
     -- Running TH splices
    
    ... ... @@ -109,7 +114,12 @@ import Data.IORef
    109 114
     import Data.Map (Map)
    
    110 115
     import qualified Data.Map as M
    
    111 116
     import Data.Maybe
    
    117
    +-- Prefer the non-deprecated internal path when available.
    
    118
    +#ifdef HAVE_GHC_INTERNAL
    
    112 119
     import GHC.Internal.Desugar (AnnotationWrapper(..))
    
    120
    +#else
    
    121
    +import GHC.Desugar (AnnotationWrapper(..))
    
    122
    +#endif
    
    113 123
     import qualified GHC.Boot.TH.Syntax as TH
    
    114 124
     import qualified GHC.Boot.TH.Monad as TH
    
    115 125
     import Unsafe.Coerce
    

  • libraries/ghci/ghci.cabal.in
    ... ... @@ -86,7 +86,6 @@ library
    86 86
             rts,
    
    87 87
             array            == 0.5.*,
    
    88 88
             base             >= 4.8 && < 4.23,
    
    89
    -        ghc-internal     >= 9.1001.0 && <=@ProjectVersionForLib@.0,
    
    90 89
             ghc-prim         >= 0.5.0 && < 0.14,
    
    91 90
             binary           == 0.8.*,
    
    92 91
             bytestring       >= 0.10 && < 0.13,
    
    ... ... @@ -97,6 +96,20 @@ library
    97 96
             ghc-heap         >= 9.10.1 && <=@ProjectVersionMunged@,
    
    98 97
             transformers     >= 0.5 && < 0.7
    
    99 98
     
    
    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:
    
    110
    +            ghc-internal      >= 9.1001.0 && <=@ProjectVersionForLib@.0
    
    111
    +        CPP-Options:          -DHAVE_GHC_INTERNAL
    
    112
    +
    
    100 113
         if flag(bootstrap)
    
    101 114
           build-depends:
    
    102 115
                 ghc-boot-th-next  == @ProjectVersionMunged@