[Git][ghc/ghc][wip/T23942] small fixes and improvements

Matthew Craven (@clyring) gitlab at gitlab.haskell.org
Thu Mar 7 13:26:23 UTC 2024



Matthew Craven pushed to branch wip/T23942 at Glasgow Haskell Compiler / GHC


Commits:
438278dd by Matthew Craven at 2024-03-07T08:25:18-05:00
small fixes and improvements

- - - - -


5 changed files:

- compiler/GHC/CoreToStg/Prep.hs
- libraries/ghc-bignum/src/GHC/Num/Backend/FFI.hs
- libraries/ghc-bignum/src/GHC/Num/Backend/GMP.hs
- libraries/ghc-bignum/src/GHC/Num/Backend/Native.hs
- libraries/ghc-internal/src/GHC/Internal/Base.hs


Changes:

=====================================
compiler/GHC/CoreToStg/Prep.hs
=====================================
@@ -2484,7 +2484,29 @@ cpeBigNatLit env i = assert (i >= 0) $ do
   --   * A call to `newByteArray#` with the appropriate size
   --   * A call to `copyAddrToByteArray#` to initialize the `ByteArray#`
   --   * A call to `unsafeFreezeByteArray#` to make the types match
-  litAddrId <- newVar addrPrimTy
+  litAddrId <- mkSysLocalM (fsLit "bigNatGuts") ManyTy addrPrimTy
+  -- returned from newByteArray#:
+  deadNewByteArrayTupleId
+    <- fmap (`setIdOccInfo` IAmDead) . mkSysLocalM (fsLit "tup") ManyTy $
+         mkTupleTy Unboxed [ realWorldStatePrimTy
+                           , realWorldMutableByteArrayPrimTy
+                           ]
+  stateTokenFromNewByteArrayId
+    <- mkSysLocalM (fsLit "token") ManyTy realWorldStatePrimTy
+  mutableByteArrayId
+    <- mkSysLocalM (fsLit "mba") ManyTy realWorldMutableByteArrayPrimTy
+  -- returned from copyAddrToByteArray#:
+  stateTokenFromCopyId
+    <- mkSysLocalM (fsLit "token") ManyTy realWorldStatePrimTy
+  -- returned from unsafeFreezeByteArray#:
+  deadFreezeTupleId
+    <- fmap (`setIdOccInfo` IAmDead) . mkSysLocalM (fsLit "tup") ManyTy $
+         mkTupleTy Unboxed [realWorldStatePrimTy, byteArrayPrimTy]
+  stateTokenFromFreezeId
+    <- (`setIdOccInfo` IAmDead) <$>
+         mkSysLocalM (fsLit "token") ManyTy realWorldStatePrimTy
+  byteArrayId <- mkSysLocalM (fsLit "ba") ManyTy byteArrayPrimTy
+
   let
     litAddrRhs = Lit (LitString words)
       -- not "mkLitString"; that does UTF-8 encoding, which we don't want here
@@ -2498,13 +2520,6 @@ cpeBigNatLit env i = assert (i >= 0) $ do
         `App` contentsLength
         `App` Var realWorldPrimId
 
-  -- returned from newByteArray#:
-  deadNewByteArrayTupleId <- newVar $
-    mkTupleTy Unboxed [realWorldStatePrimTy, realWorldMutableByteArrayPrimTy]
-  stateTokenFromNewByteArrayId <- newVar realWorldStatePrimTy
-  mutableByteArrayId <- newVar realWorldMutableByteArrayPrimTy
-
-  let
     copyContentsCall =
       Var (primOpId CopyAddrToByteArrayOp)
         `App` Type realWorldTy
@@ -2514,23 +2529,12 @@ cpeBigNatLit env i = assert (i >= 0) $ do
         `App` contentsLength
         `App` Var stateTokenFromNewByteArrayId
 
-  -- returned from copyAddrToByteArray#:
-  stateTokenFromCopyId <- newVar realWorldStatePrimTy
-
-  let
     unsafeFreezeCall =
       Var (primOpId UnsafeFreezeByteArrayOp)
         `App` Type realWorldTy
         `App` Var mutableByteArrayId
         `App` Var stateTokenFromCopyId
 
-  -- returned from unsafeFreezeByteArray#:
-  deadFreezeTupleId <- newVar $
-    mkTupleTy Unboxed [realWorldStatePrimTy, byteArrayPrimTy]
-  stateTokenFromFreezeId <- newVar realWorldStatePrimTy
-  byteArrayId <- newVar byteArrayPrimTy
-
-  let
     unboxed2tuple_alt :: AltCon
     unboxed2tuple_alt = DataAlt (tupleDataCon Unboxed 2)
 


=====================================
libraries/ghc-bignum/src/GHC/Num/Backend/FFI.hs
=====================================
@@ -24,7 +24,8 @@ import {-# SOURCE #-} GHC.Num.Natural
 import {-# SOURCE #-} GHC.Num.Integer
 
 -- See W1 of Note [Tracking dependencies on primitives] in GHC.Internal.Base
--- (we have a string literal)
+-- (we use the empty tuple () and string literals)
+import GHC.Tuple ()
 import GHC.CString ()
 
 default ()


=====================================
libraries/ghc-bignum/src/GHC/Num/Backend/GMP.hs
=====================================
@@ -31,7 +31,8 @@ import {-# SOURCE #-} GHC.Num.BigNat
 import {-# SOURCE #-} GHC.Num.Natural
 
 -- See W1 of Note [Tracking dependencies on primitives] in GHC.Internal.Base
--- (we have a string literal)
+-- (we use the empty tuple () and string literals)
+import GHC.Tuple ()
 import GHC.CString ()
 
 default ()


=====================================
libraries/ghc-bignum/src/GHC/Num/Backend/Native.hs
=====================================
@@ -29,7 +29,8 @@ import GHC.Prim
 import GHC.Types
 
 -- See W1 of Note [Tracking dependencies on primitives] in GHC.Internal.Base
--- (we have a string literal)
+-- (we use the empty tuple () and string literals)
+import GHC.Tuple ()
 import GHC.CString ()
 
 default ()


=====================================
libraries/ghc-internal/src/GHC/Internal/Base.hs
=====================================
@@ -366,13 +366,13 @@ been built, otherwise compilation will fail with an error like this one:
     Use -v to see a list of the files searched for.
 
 To prevent such errors, we insist that if any boot library module X
-implicitly depending on primitives in module Y, then the transitive
+implicitly depends on primitives in module Y, then the transitive
 imports of X must include Y.
 
 Such implicit dependencies can be introduced in at least the following ways:
 
 W1:
-  Awkward dependencies on ghc-prim:
+  Awkward dependencies:
    * TypeRep metadata introduces references to GHC.Types in EVERY module.
    * A String literal introduces a reference to GHC.CString, for either
      unpackCString# or unpackCStringUtf8# depending on its contents.
@@ -432,7 +432,7 @@ W4:
   as long as the module which defines Eq imports GHC.Magic this cannot
   cause trouble.
 
-  Embarrasingly, we do not follow this plan for the Lift class.
+  Embarrassingly, we do not follow this plan for the Lift class.
   Derived Lift instances refer to machinery in Language.Haskell.TH.Lib,
   which is not imported by the module Language.Haskell.TH.Syntax that
   defines the Lift class.  This is still causing annoyance for boot
@@ -471,8 +471,8 @@ This presents a problem.
   GHC.Internal.Base and GHC.Internal.Num. Enum is a superclass of
   Integral. We don't use any Enum methods here, but it is relevant
   (read on).
-* Integral is defined in GHC.Real, which imports GHC.Base, GHC.Num, and
-  GHC.Enum.
+* Integral is defined in GHC.Internal.Real, which imports
+  GHC.Internal.Base, GHC.Internal.Num, and GHC.Internal.Enum.
 
 We resolve this web of dependencies with hs-boot files. The rules
 https://ghc.gitlab.haskell.org/ghc/doc/users_guide/separate_compilation.html#how-to-compile-mutually-recursive-modules



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/438278dd05e17598384b5bd74c930ad1747317a9
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/20240307/a6940319/attachment-0001.html>


More information about the ghc-commits mailing list