[Git][ghc/ghc][master] Export singleton function from Data.List

Marge Bot gitlab at gitlab.haskell.org
Sat Sep 19 19:48:48 UTC 2020



 Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
e195dae6 by Wander Hillen at 2020-09-19T15:48:41-04:00
Export singleton function from Data.List

Data.OldList exports a monomorphized singleton function but
it is not re-exported by Data.List. Adding the export to
Data.List causes a conflict with a 14-year old function of the
same name and type by SPJ in GHC.Utils.Misc. We can't just remove
this function because that leads to a problems when building
GHC with a stage0 compiler that does not have singleton in
Data.List yet. We also can't hide the function in GHC.Utils.Misc
since it is not possible to hide a function from a module if the
module does not export the function. To work around this, all
places where the Utils.Misc singleton was used now use a qualified
version like Utils.singleton and in GHC.Utils.Misc we are very
specific about which version we export.

- - - - -


8 changed files:

- compiler/GHC/Builtin/Utils.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Iface/Recomp.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Tc/Gen/Sig.hs
- compiler/GHC/Types/Name/Reader.hs
- compiler/GHC/Utils/Misc.hs
- libraries/base/Data/List.hs


Changes:

=====================================
compiler/GHC/Builtin/Utils.hs
=====================================
@@ -71,7 +71,7 @@ import GHC.Driver.Types
 import GHC.Core.Class
 import GHC.Core.TyCon
 import GHC.Types.Unique.FM
-import GHC.Utils.Misc
+import GHC.Utils.Misc as Utils
 import GHC.Utils.Panic
 import GHC.Builtin.Types.Literals ( typeNatTyCons )
 import GHC.Hs.Doc
@@ -180,7 +180,7 @@ knownKeyNamesOkay all_names
   | otherwise
   = Just badNamesStr
   where
-    namesEnv      = foldl' (\m n -> extendNameEnv_Acc (:) singleton m n n)
+    namesEnv      = foldl' (\m n -> extendNameEnv_Acc (:) Utils.singleton m n n)
                            emptyUFM all_names
     badNamesEnv   = filterNameEnv (\ns -> ns `lengthExceeds` 1) namesEnv
     badNamesPairs = nonDetUFMToList badNamesEnv


=====================================
compiler/GHC/Core/Rules.hs
=====================================
@@ -67,7 +67,7 @@ import GHC.Utils.Panic
 import GHC.Data.FastString
 import GHC.Data.Maybe
 import GHC.Data.Bag
-import GHC.Utils.Misc
+import GHC.Utils.Misc as Utils
 import Data.List
 import Data.Function    ( on )
 import Control.Monad    ( guard )
@@ -358,7 +358,7 @@ unionRuleBase rb1 rb2 = plusNameEnv_C (++) rb1 rb2
 
 extendRuleBase :: RuleBase -> CoreRule -> RuleBase
 extendRuleBase rule_base rule
-  = extendNameEnv_Acc (:) singleton rule_base (ruleIdName rule) rule
+  = extendNameEnv_Acc (:) Utils.singleton rule_base (ruleIdName rule) rule
 
 pprRuleBase :: RuleBase -> SDoc
 pprRuleBase rules = pprUFM rules $ \rss ->


=====================================
compiler/GHC/Iface/Recomp.hs
=====================================
@@ -37,7 +37,7 @@ import GHC.Data.Graph.Directed
 import GHC.Types.SrcLoc
 import GHC.Utils.Outputable as Outputable
 import GHC.Types.Unique
-import GHC.Utils.Misc hiding ( eqListBy )
+import GHC.Utils.Misc as Utils hiding ( eqListBy )
 import GHC.Data.Maybe
 import GHC.Data.FastString
 import GHC.Utils.Binary
@@ -1339,7 +1339,7 @@ mkOrphMap get_key decls
   where
     go (non_orphs, orphs) d
         | NotOrphan occ <- get_key d
-        = (extendOccEnv_Acc (:) singleton non_orphs occ d, orphs)
+        = (extendOccEnv_Acc (:) Utils.singleton non_orphs occ d, orphs)
         | otherwise = (non_orphs, d:orphs)
 
 -- -----------------------------------------------------------------------------


=====================================
compiler/GHC/Rename/Names.hs
=====================================
@@ -58,7 +58,7 @@ import GHC.Utils.Outputable as Outputable
 import GHC.Data.Maybe
 import GHC.Types.SrcLoc as SrcLoc
 import GHC.Types.Basic  ( TopLevelFlag(..), StringLiteral(..) )
-import GHC.Utils.Misc
+import GHC.Utils.Misc as Utils
 import GHC.Utils.Panic
 import GHC.Data.FastString
 import GHC.Data.FastString.Env
@@ -1186,8 +1186,8 @@ mkChildEnv :: [GlobalRdrElt] -> NameEnv [GlobalRdrElt]
 mkChildEnv gres = foldr add emptyNameEnv gres
   where
     add gre env = case gre_par gre of
-        FldParent p _  -> extendNameEnv_Acc (:) singleton env p gre
-        ParentIs  p    -> extendNameEnv_Acc (:) singleton env p gre
+        FldParent p _  -> extendNameEnv_Acc (:) Utils.singleton env p gre
+        ParentIs  p    -> extendNameEnv_Acc (:) Utils.singleton env p gre
         NoParent       -> env
 
 findChildren :: NameEnv [a] -> Name -> [a]


=====================================
compiler/GHC/Tc/Gen/Sig.hs
=====================================
@@ -55,7 +55,7 @@ import GHC.Types.Name.Env
 import GHC.Utils.Outputable
 import GHC.Utils.Panic
 import GHC.Types.SrcLoc
-import GHC.Utils.Misc( singleton )
+import GHC.Utils.Misc as Utils ( singleton )
 import GHC.Data.Maybe( orElse )
 import Data.Maybe( mapMaybe )
 import Control.Monad( unless )
@@ -554,7 +554,7 @@ lookupPragEnv :: TcPragEnv -> Name -> [LSig GhcRn]
 lookupPragEnv prag_fn n = lookupNameEnv prag_fn n `orElse` []
 
 extendPragEnv :: TcPragEnv -> (Name, LSig GhcRn) -> TcPragEnv
-extendPragEnv prag_fn (n, sig) = extendNameEnv_Acc (:) singleton prag_fn n sig
+extendPragEnv prag_fn (n, sig) = extendNameEnv_Acc (:) Utils.singleton prag_fn n sig
 
 ---------------
 mkPragEnv :: [LSig GhcRn] -> LHsBinds GhcRn -> TcPragEnv


=====================================
compiler/GHC/Types/Name/Reader.hs
=====================================
@@ -84,7 +84,7 @@ import GHC.Utils.Outputable
 import GHC.Types.Unique
 import GHC.Types.Unique.FM
 import GHC.Types.Unique.Set
-import GHC.Utils.Misc
+import GHC.Utils.Misc as Utils
 import GHC.Utils.Panic
 import GHC.Types.Name.Env
 
@@ -970,7 +970,7 @@ mkGlobalRdrEnv :: [GlobalRdrElt] -> GlobalRdrEnv
 mkGlobalRdrEnv gres
   = foldr add emptyGlobalRdrEnv gres
   where
-    add gre env = extendOccEnv_Acc insertGRE singleton env
+    add gre env = extendOccEnv_Acc insertGRE Utils.singleton env
                                    (greOccName gre)
                                    gre
 
@@ -1004,7 +1004,7 @@ transformGREs trans_gre occs rdr_env
 
 extendGlobalRdrEnv :: GlobalRdrEnv -> GlobalRdrElt -> GlobalRdrEnv
 extendGlobalRdrEnv env gre
-  = extendOccEnv_Acc insertGRE singleton env
+  = extendOccEnv_Acc insertGRE Utils.singleton env
                      (greOccName gre) gre
 
 shadowNames :: GlobalRdrEnv -> [Name] -> GlobalRdrEnv


=====================================
compiler/GHC/Utils/Misc.hs
=====================================
@@ -43,7 +43,7 @@ module GHC.Utils.Misc (
         listLengthCmp, atLength,
         equalLength, compareLength, leLength, ltLength,
 
-        isSingleton, only, singleton,
+        isSingleton, only, GHC.Utils.Misc.singleton,
         notNull, snocView,
 
         isIn, isn'tIn,


=====================================
libraries/base/Data/List.hs
=====================================
@@ -25,6 +25,7 @@ module Data.List
    , tail
    , init
    , uncons
+   , singleton
    , null
    , length
 



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e195dae6d959e2a9b1a22a2ca78db5955e1d7dea
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/20200919/66e23dcb/attachment-0001.html>


More information about the ghc-commits mailing list