[Git][ghc/ghc][wip/T22010] Remove GHC.Utils.Containers.Internal.Prelude
Jaro Reinders (@Noughtmare)
gitlab at gitlab.haskell.org
Thu Jun 29 07:49:48 UTC 2023
Jaro Reinders pushed to branch wip/T22010 at Glasgow Haskell Compiler / GHC
Commits:
bfdc2dd2 by Jaro Reinders at 2023-06-29T09:49:40+02:00
Remove GHC.Utils.Containers.Internal.Prelude
- - - - -
9 changed files:
- compiler/GHC/Builtin/Uniques.hs
- compiler/GHC/Data/Word64Map/Internal.hs
- compiler/GHC/Data/Word64Map/Strict/Internal.hs
- compiler/GHC/Data/Word64Set/Internal.hs
- compiler/GHC/Utils/Containers/Internal/BitUtil.hs
- − compiler/GHC/Utils/Containers/Internal/Prelude.hs
- compiler/ghc.cabal.in
- testsuite/tests/count-deps/CountDepsAst.stdout
- testsuite/tests/count-deps/CountDepsParser.stdout
Changes:
=====================================
compiler/GHC/Builtin/Uniques.hs
=====================================
@@ -69,7 +69,7 @@ import GHC.Utils.Panic
import GHC.Utils.Panic.Plain (assert)
import Data.Maybe
-import GHC.Utils.Word64 (word64ToInt, intToWord64)
+import GHC.Utils.Word64 (word64ToInt)
-- | Get the 'Name' associated with a known-key 'Unique'.
knownUniqueName :: Unique -> Maybe Name
@@ -283,9 +283,7 @@ isTupleTyConUnique u =
where
(tag, n) = unpkUnique u
(arity', i) = quotRem n 2
- arity =
- assert (arity' <= intToWord64 (maxBound :: Int))
- (word64ToInt arity')
+ arity = word64ToInt arity'
getTupleTyConName :: Boxity -> Int -> Name
getTupleTyConName boxity n =
=====================================
compiler/GHC/Data/Word64Map/Internal.hs
=====================================
@@ -298,21 +298,16 @@ module GHC.Data.Word64Map.Internal (
, mapGentlyWhenMatched
) where
+import GHC.Prelude.Basic hiding
+ (lookup, filter, foldr, foldl, foldl', null, map)
+
import Data.Functor.Identity (Identity (..))
-import Data.Semigroup (Semigroup(stimes))
-#if !(MIN_VERSION_base(4,11,0))
-import Data.Semigroup (Semigroup((<>)))
-#endif
-import Data.Semigroup (stimesIdempotentMonoid)
+import Data.Semigroup (Semigroup(stimes,(<>)),stimesIdempotentMonoid)
import Data.Functor.Classes
import Control.DeepSeq (NFData(rnf))
-import Data.Bits
import qualified Data.Foldable as Foldable
import Data.Maybe (fromMaybe)
-import GHC.Utils.Containers.Internal.Prelude hiding
- (lookup, map, filter, foldr, foldl, null)
-import Prelude ()
import GHC.Data.Word64Set.Internal (Key)
import qualified GHC.Data.Word64Set.Internal as Word64Set
=====================================
compiler/GHC/Data/Word64Map/Strict/Internal.hs
=====================================
@@ -253,11 +253,9 @@ module GHC.Data.Word64Map.Strict.Internal (
, maxViewWithKey
) where
-import GHC.Utils.Containers.Internal.Prelude hiding
- (lookup,map,filter,foldr,foldl,null)
-import Prelude ()
+import GHC.Prelude.Basic hiding
+ (lookup, filter, foldr, foldl, foldl', null, map)
-import Data.Bits
import qualified GHC.Data.Word64Map.Internal as L
import GHC.Data.Word64Map.Internal
( Word64Map (..)
=====================================
compiler/GHC/Data/Word64Set/Internal.hs
=====================================
@@ -198,14 +198,9 @@ import Control.DeepSeq (NFData(rnf))
import Data.Bits
import qualified Data.List as List
import Data.Maybe (fromMaybe)
-import Data.Semigroup (Semigroup(stimes))
-#if !(MIN_VERSION_base(4,11,0))
-import Data.Semigroup (Semigroup((<>)))
-#endif
-import Data.Semigroup (stimesIdempotentMonoid)
-import GHC.Utils.Containers.Internal.Prelude hiding
- (filter, foldr, foldl, null, map)
-import Prelude ()
+import Data.Semigroup (Semigroup(stimes, (<>)), stimesIdempotentMonoid)
+import GHC.Prelude.Basic hiding
+ (filter, foldr, foldl, foldl', null, map)
import Data.Word ( Word64 )
import GHC.Utils.Containers.Internal.BitUtil
=====================================
compiler/GHC/Utils/Containers/Internal/BitUtil.hs
=====================================
@@ -37,10 +37,7 @@ module GHC.Utils.Containers.Internal.BitUtil
, shiftRL
) where
-import Data.Bits (popCount, unsafeShiftL, unsafeShiftR
- , countLeadingZeros
- )
-import Prelude
+import GHC.Prelude.Basic
import Data.Word
{----------------------------------------------------------------------
=====================================
compiler/GHC/Utils/Containers/Internal/Prelude.hs deleted
=====================================
@@ -1,18 +0,0 @@
-{-# LANGUAGE CPP #-}
--- | This hideous module lets us avoid dealing with the fact that
--- @liftA2@ wasn't previously exported from the standard prelude.
-module GHC.Utils.Containers.Internal.Prelude
- ( module Prelude
- , Applicative (..)
-#if !MIN_VERSION_base(4,10,0)
- , liftA2
-#endif
- )
- where
-
-import Prelude hiding (Applicative(..))
-import Control.Applicative(Applicative(..))
-
-#if !MIN_VERSION_base(4,10,0)
-import Control.Applicative(liftA2)
-#endif
=====================================
compiler/ghc.cabal.in
=====================================
@@ -877,7 +877,6 @@ Library
GHC.Utils.BufHandle
GHC.Utils.CliOption
GHC.Utils.Constants
- GHC.Utils.Containers.Internal.Prelude
GHC.Utils.Containers.Internal.BitUtil
GHC.Utils.Containers.Internal.StrictPair
GHC.Utils.Error
=====================================
testsuite/tests/count-deps/CountDepsAst.stdout
=====================================
@@ -294,7 +294,6 @@ GHC.Utils.BufHandle
GHC.Utils.CliOption
GHC.Utils.Constants
GHC.Utils.Containers.Internal.BitUtil
-GHC.Utils.Containers.Internal.Prelude
GHC.Utils.Containers.Internal.StrictPair
GHC.Utils.Error
GHC.Utils.Exception
=====================================
testsuite/tests/count-deps/CountDepsParser.stdout
=====================================
@@ -301,7 +301,6 @@ GHC.Utils.BufHandle
GHC.Utils.CliOption
GHC.Utils.Constants
GHC.Utils.Containers.Internal.BitUtil
-GHC.Utils.Containers.Internal.Prelude
GHC.Utils.Containers.Internal.StrictPair
GHC.Utils.Error
GHC.Utils.Exception
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bfdc2dd2ea957df3bc034fe23446c911fcb32841
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bfdc2dd2ea957df3bc034fe23446c911fcb32841
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/20230629/a2023c66/attachment-0001.html>
More information about the ghc-commits
mailing list