[Git][ghc/ghc][wip/clc216] base: Deprecate GHC.Desugar

Rodrigo Mesquita (@alt-romes) gitlab at gitlab.haskell.org
Thu Aug 8 12:54:58 UTC 2024



Rodrigo Mesquita pushed to branch wip/clc216 at Glasgow Haskell Compiler / GHC


Commits:
5428c7b7 by Ben Gamari at 2024-08-08T13:54:45+01:00
base: Deprecate GHC.Desugar

See https://github.com/haskell/core-libraries-committee/issues/216.

This will be removed in GHC 9.14.

- - - - -


5 changed files:

- compiler/GHC/Tc/Gen/Splice.hs
- libraries/base/changelog.md
- libraries/base/src/GHC/Desugar.hs
- libraries/ghci/GHCi/TH.hs
- libraries/ghci/ghci.cabal.in


Changes:

=====================================
compiler/GHC/Tc/Gen/Splice.hs
=====================================
@@ -12,6 +12,14 @@
 {-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
 {-# LANGUAGE NamedFieldPuns #-}
 
+#if __GLASGOW_HASKELL__ < 914
+-- In GHC 9.14, GHC.Desugar will be removed from base in favour of
+-- ghc-internal's GHC.Internal.Desugar. However, because of bootstrapping
+-- concerns, we will only depend on ghc-internal when the boot compiler is
+-- certain to have it.
+{-# OPTIONS_GHC -Wno-warnings-deprecations #-}
+#endif
+
 {-
 (c) The University of Glasgow 2006
 (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
@@ -136,9 +144,8 @@ import qualified GHC.Internal.TH.Syntax as TH
 import qualified GHC.Internal.TH.Ppr    as TH
 
 #if defined(HAVE_INTERNAL_INTERPRETER)
--- Because GHC.Desugar might not be in the base library of the bootstrapping compiler
-import GHC.Desugar      ( AnnotationWrapper(..) )
 import Unsafe.Coerce    ( unsafeCoerce )
+import GHC.Desugar ( AnnotationWrapper(..) )
 #endif
 
 import Control.Monad


=====================================
libraries/base/changelog.md
=====================================
@@ -1,6 +1,7 @@
 # Changelog for [`base` package](http://hackage.haskell.org/package/base)
 
 ## 4.21.0.0 *TBA*
+  * `GHC.Desugar` has been deprecated and should be removed in GHC 9.14. ([CLC proposal #216](https://github.com/haskell/core-libraries-committee/issues/216))
   * Add a `readTixFile` field to the `HpcFlags` record in `GHC.RTS.Flags` ([CLC proposal #276](https://github.com/haskell/core-libraries-committee/issues/276))
   * Add `compareLength` to `Data.List` and `Data.List.NonEmpty` ([CLC proposal #257](https://github.com/haskell/core-libraries-committee/issues/257))
   * Add `INLINE[1]` to `compareInt` / `compareWord` ([CLC proposal #179](https://github.com/haskell/core-libraries-committee/issues/179))


=====================================
libraries/base/src/GHC/Desugar.hs
=====================================
@@ -1,6 +1,8 @@
+{-# LANGUAGE CPP #-}
 {-# LANGUAGE Safe #-}
 {-# OPTIONS_HADDOCK not-home #-}
 
+-----------------------------------------------------------------------------
 -- |
 --
 -- Module      :  GHC.Desugar
@@ -8,7 +10,7 @@
 -- License     :  see libraries/base/LICENSE
 --
 -- Maintainer  :  ghc-devs at haskell.org
--- Stability   :  internal
+-- Stability   :  deprecated (<https://github.com/haskell/core-libraries-committee/issues/216>)
 -- Portability :  non-portable (GHC extensions)
 --
 -- Support code for desugaring in GHC
@@ -18,11 +20,14 @@
 -- bound, e.g., @base < 4.X@ rather than @base < 5@, because the interface can
 -- change rapidly without much warning.
 --
+-----------------------------------------------------------------------------
+
+#if __GLASGOW_HASKELL >= 914
+#error "GHC.Desugar should be removed in GHC 9.14"
+#endif
 
 module GHC.Desugar
-    ((>>>),
-     AnnotationWrapper(..),
-     toAnnotationWrapper
-     ) where
+  {-# DEPRECATED ["GHC.Desugar is deprecated and will be removed in GHC 9.14.", "(>>>) should be imported from Control.Arrow.", "AnnotationWrapper is internal to GHC and should not be used externally."] #-}
+  ((>>>), AnnotationWrapper(..), toAnnotationWrapper) where
 
 import GHC.Internal.Desugar


=====================================
libraries/ghci/GHCi/TH.hs
=====================================
@@ -1,6 +1,9 @@
 {-# LANGUAGE ScopedTypeVariables, StandaloneDeriving, DeriveGeneric,
     TupleSections, RecordWildCards, InstanceSigs, CPP #-}
 {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
+{-# OPTIONS_GHC -Wno-warnings-deprecations #-}
+-- TODO We want to import GHC.Internal.Desugar instead of GHC.Desugar when we
+-- can require of the bootstrap compiler to have ghc-internal.
 
 -- |
 -- Running TH splices
@@ -109,7 +112,7 @@ import Data.IORef
 import Data.Map (Map)
 import qualified Data.Map as M
 import Data.Maybe
-import GHC.Desugar
+import GHC.Desugar (AnnotationWrapper(..))
 import qualified GHC.Internal.TH.Syntax as TH
 import Unsafe.Coerce
 


=====================================
libraries/ghci/ghci.cabal.in
=====================================
@@ -85,6 +85,10 @@ library
         rts,
         array            == 0.5.*,
         base             >= 4.8 && < 4.21,
+        -- ghc-internal     == @ProjectVersionMunged at 01.*
+        -- TODO: Use GHC.Internal.Desugar from ghc-internal instead of ignoring
+        -- the deprecation warning of GHC.Desugar when we require ghc-internal
+        -- of the bootstrap compiler
         ghc-prim         >= 0.5.0 && < 0.12,
         binary           == 0.8.*,
         bytestring       >= 0.10 && < 0.13,



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5428c7b7c8fc345618e6859a4c25ec3bee54feaa

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5428c7b7c8fc345618e6859a4c25ec3bee54feaa
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20240808/5726c754/attachment-0001.html>


More information about the ghc-commits mailing list