[Git][ghc/ghc][wip/andreask/unpack_unboxed_tuples] Properly compute unpacked sizes for -funpack-small-strict-fields.

Andreas Klebinger (@AndreasK) gitlab at gitlab.haskell.org
Fri Jan 20 14:54:15 UTC 2023



Andreas Klebinger pushed to branch wip/andreask/unpack_unboxed_tuples at Glasgow Haskell Compiler / GHC


Commits:
e9d0629b by Andreas Klebinger at 2023-01-20T15:53:12+01:00
Properly compute unpacked sizes for -funpack-small-strict-fields.

Base unpacking under -funpack-small-strict-fields on the rep size
of the unpacked constructor instead of the number of reps it's
represented by.

Fixes #22309

- - - - -


3 changed files:

- compiler/GHC/Core/TyCon.hs
- compiler/GHC/Types/Id/Make.hs
- docs/users_guide/using-optimisation.rst


Changes:

=====================================
compiler/GHC/Core/TyCon.hs
=====================================
@@ -126,8 +126,8 @@ module GHC.Core.TyCon(
         PrimRep(..), PrimElemRep(..),
         primElemRepToPrimRep,
         isVoidRep, isGcPtrRep,
-        primRepSizeB,
-        primElemRepSizeB,
+        primRepSizeB, primRepSizeW64_B,
+        primElemRepSizeB, primElemRepSizeW64_B,
         primRepIsFloat,
         primRepsCompatible,
         primRepCompatible,
@@ -1659,9 +1659,40 @@ primRepSizeB platform = \case
    VoidRep          -> 0
    (VecRep len rep) -> len * primElemRepSizeB platform rep
 
+-- | Like primRepSizeB but assumes pointers/words are 8 words wide.
+--
+-- This can be useful to compute the size of a rep as if we were compiling
+-- for a 64bit platform.
+primRepSizeW64_B :: PrimRep -> Int
+primRepSizeW64_B = \case
+   IntRep           -> 8
+   WordRep          -> 8
+   Int8Rep          -> 1
+   Int16Rep         -> 2
+   Int32Rep         -> 4
+   Int64Rep         -> 8
+   Word8Rep         -> 1
+   Word16Rep        -> 2
+   Word32Rep        -> 4
+   Word64Rep        -> 8
+   FloatRep         -> fLOAT_SIZE
+   DoubleRep        -> dOUBLE_SIZE
+   AddrRep          -> 8
+   LiftedRep        -> 8
+   UnliftedRep      -> 8
+   VoidRep          -> 0
+   (VecRep len rep) -> len * primElemRepSizeW64_B rep
+
 primElemRepSizeB :: Platform -> PrimElemRep -> Int
 primElemRepSizeB platform = primRepSizeB platform . primElemRepToPrimRep
 
+-- | Like primElemRepSizeB but assumes pointers/words are 8 words wide.
+--
+-- This can be useful to compute the size of a rep as if we were compiling
+-- for a 64bit platform.
+primElemRepSizeW64_B :: PrimElemRep -> Int
+primElemRepSizeW64_B = primRepSizeW64_B . primElemRepToPrimRep
+
 primElemRepToPrimRep :: PrimElemRep -> PrimRep
 primElemRepToPrimRep Int8ElemRep   = Int8Rep
 primElemRepToPrimRep Int16ElemRep  = Int16Rep


=====================================
compiler/GHC/Types/Id/Make.hs
=====================================
@@ -67,6 +67,7 @@ import GHC.Types.Literal
 import GHC.Types.SourceText
 import GHC.Types.Name.Set
 import GHC.Types.Name
+import GHC.Types.RepType
 import GHC.Types.ForeignCall
 import GHC.Types.Id
 import GHC.Types.Id.Info
@@ -1362,9 +1363,21 @@ shouldUnpackTy bang_opts prag fam_envs ty
           | otherwise
           -> bang_opt_unbox_strict bang_opts
              || (bang_opt_unbox_small bang_opts
-                 && rep_tys `lengthAtMost` 1)  -- See Note [Unpack one-wide fields]
-      where (rep_tys, _) = dataConArgUnpack ty
+                 && is_small_rep rep_tys)  -- See Note [Unpack one-wide fields]
+      where
+        (rep_tys, _) = dataConArgUnpack ty
+
+    -- Takes in the list of reps used to represent the dataCon after it's unpacked
+    -- and tells us if they can fit into 8 bytes. See Note [Unpack one-wide fields]
+    is_small_rep rep_tys =
 
+      let -- Neccesary to look through unboxed tuples.
+          prim_reps = concatMap (typePrimRep . scaledThing . fst) $ rep_tys
+          -- Void types are erased when unpacked so we
+          nv_prim_reps = filter (not . isVoidRep) prim_reps
+          -- And then get the actual size of the unpacked constructor.
+          rep_size = sum $ map primRepSizeW64_B nv_prim_reps
+      in rep_size <= 8
 
 -- Given a type already assumed to have been normalized by topNormaliseType,
 -- unpackable_type_datacons ty = Just datacons
@@ -1424,6 +1437,14 @@ However
 
 Here we can represent T with an Int#.
 
+Special care has to be taken to make sure we don't mistake fields with unboxed
+tuple/sum rep or very large reps. See #22309
+
+For consistency we unpack anything that fits into 8 bytes on a 64-bit platform,
+even when compiling for 32bit platforms. This way unpacking decisions will be the
+same for 32bit and 64bit systems. To do so we use primRepSizeW64_B instead of
+primRepSizeB.
+
 Note [Recursive unboxing]
 ~~~~~~~~~~~~~~~~~~~~~~~~~
 Consider


=====================================
docs/users_guide/using-optimisation.rst
=====================================
@@ -1468,9 +1468,9 @@ by saying ``-fno-wombat``.
     default you can disable it for certain constructor fields using the
     ``NOUNPACK`` pragma (see :ref:`nounpack-pragma`).
 
-    Note that for consistency ``Double``, ``Word64``, and ``Int64``
-    constructor fields are unpacked on 32-bit platforms, even though
-    they are technically larger than a pointer on those platforms.
+    Note that for consistency constructor fields are unpacked on 32-bit platforms
+    as if it we were compiling for a 64-bit target even if fields are larger
+    than a pointer on those platforms.
 
 .. ghc-flag:: -funbox-strict-fields
     :shortdesc: Flatten strict constructor fields



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e9d0629b9bf332a2a2812af5e1c1c0be7254e31f
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/20230120/0d4b4868/attachment-0001.html>


More information about the ghc-commits mailing list