[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
Thu Jan 19 14:39:24 UTC 2023



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


Commits:
fc0c2463 by Andreas Klebinger at 2023-01-19T15:38:27+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

- - - - -


4 changed files:

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


Changes:

=====================================
compiler/GHC/Core/Opt/SpecConstr.hs
=====================================
@@ -1534,6 +1534,9 @@ scExpr' env (Case scrut b ty alts)
                                   | not (single_alt && all deadArgOcc arg_occs)
                                   -> -- pprTrace "sc_alt1" (ppr b' $$ ppr con $$ ppr bs $$ ppr arg_occs) $
                                      ScrutOcc (unitUFM dc arg_occs)
+                               LitAlt _
+                                  | not (single_alt)
+                                  -> ScrutOcc (emptyUFM)
                                _  -> -- pprTrace "sc_alt1" (ppr b' $$ ppr con $$ ppr bs $$ ppr arg_occs) $
                                      UnkOcc
           ; return (usg', b_occ `combineOcc` scrut_occ, Alt con bs2 rhs') }
@@ -2633,6 +2636,11 @@ argToPat in_scope val_env arg arg_occ
   -- Check for a constructor application
   -- NB: this *precedes* the Var case, so that we catch nullary constrs
 argToPat1 env in_scope val_env arg arg_occ _arg_str
+  | Just (ConVal (LitAlt lit) _args) <- isValue val_env arg
+  , mb_scrut_lit
+  = do {
+       ; return (True, Lit lit , []) }
+
   | Just (ConVal (DataAlt dc) args) <- isValue val_env arg
   , not (ignoreDataCon env dc)        -- See Note [NoSpecConstr]
   , Just arg_occs <- mb_scrut dc
@@ -2662,6 +2670,13 @@ argToPat1 env in_scope val_env arg arg_occ _arg_str
                             -> Just (repeat UnkOcc)
                             | otherwise
                             -> Nothing
+    mb_scrut_lit = case arg_occ of
+                ScrutOcc _  -> True
+                _other      | sc_force env || sc_keen (sc_opts env)
+                            -> True
+                            | otherwise
+                            -> False
+
     match_vals bangs (arg:args)
       | isTypeArg arg
       = NotMarkedStrict : match_vals bangs args


=====================================
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,34 @@ primRepSizeB platform = \case
    VoidRep          -> 0
    (VecRep len rep) -> len * primElemRepSizeB platform rep
 
+-- | Like primRepSizeB but assume pointers/words are 8 words wide.
+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.
+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,22 @@ 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
+        nv_prim_reps = filter (not . isVoidRep) . concatMap (typePrimRep . scaledThing . fst) $ rep_tys
+
+    -- 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.
+    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 +1438,12 @@ 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, even when compiling
+for 32bit platforms.
+
 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/fc0c24630f5836d87dfc5103331383e35e2e5fc0

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fc0c24630f5836d87dfc5103331383e35e2e5fc0
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/20230119/cf9cdafb/attachment-0001.html>


More information about the ghc-commits mailing list