[Git][ghc/ghc][wip/romes/rep-arity] Account for all VoidRep types on precomputedStaticConInfo

Rodrigo Mesquita (@alt-romes) gitlab at gitlab.haskell.org
Mon Mar 27 16:41:14 UTC 2023



Rodrigo Mesquita pushed to branch wip/romes/rep-arity at Glasgow Haskell Compiler / GHC


Commits:
59234911 by romes at 2023-03-27T17:41:04+01:00
Account for all VoidRep types on precomputedStaticConInfo

Previously, we were considering coercion values whose unlifted type
equality had a zerobit runtime representation (VoidRep) to be
constructor arguments when determining whether we should pre-compute a
staticConInfo for a data constructor.

This made it so that GADT constructors with type-equality constraints
that should have no runtime representation actually ended up impacting
the code generation.

Fixes #23158

- - - - -


2 changed files:

- compiler/GHC/Core/DataCon.hs
- + compiler/GHC/Types/RepType.hs-boot


Changes:

=====================================
compiler/GHC/Core/DataCon.hs
=====================================
@@ -79,6 +79,7 @@ import GHC.Core.TyCo.Subst
 import GHC.Core.TyCo.Compare( eqType )
 import GHC.Core.Multiplicity
 import {-# SOURCE #-} GHC.Types.TyThing
+import {-# SOURCE #-} GHC.Types.RepType (isZeroBitTy)
 import GHC.Types.FieldLabel
 import GHC.Types.SourceText
 import GHC.Core.Class
@@ -111,8 +112,8 @@ import Data.List( find )
 import Language.Haskell.Syntax.Module.Name
 
 {-
-Data constructor representation
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Note [Data constructor representation]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 Consider the following Haskell data type declaration
 
         data T = T !Int ![Int]
@@ -981,7 +982,7 @@ but the rep type is
         Trep :: Int# -> a -> Void# -> T a
 Actually, the unboxed part isn't implemented yet!
 
-Not that this representation is still *different* from runtime
+Note that this representation is still *different* from runtime
 representation. (Which is what STG uses after unarise).
 
 This is how T would end up being used in STG post-unarise:
@@ -1397,7 +1398,7 @@ dataConSourceArity (MkData { dcSourceArity = arity }) = arity
 
 -- | Gives the number of actual fields in the /representation/ of the
 -- data constructor. This may be more than appear in the source code;
--- the extra ones are the existentially quantified dictionaries
+-- the extra ones are the existentially quantified dictionaries.
 dataConRepArity :: DataCon -> Arity
 dataConRepArity (MkData { dcRepArity = arity }) = arity
 
@@ -1408,8 +1409,10 @@ isNullarySrcDataCon dc = dataConSourceArity dc == 0
 
 -- | Return whether there are any argument types for this 'DataCon's runtime representation type
 -- See Note [DataCon arities]
+--
+-- ROMES: The arity of the runtime representation DOES NOT match the arity of the Core representation, which is what `dataConRepArity` means
 isNullaryRepDataCon :: DataCon -> Bool
-isNullaryRepDataCon dc = dataConRepArity dc == 0
+isNullaryRepDataCon dc = length (filter (not . isZeroBitTy . scaledThing) (dataConRepArgTys dc)) == 0
 
 dataConRepStrictness :: DataCon -> [StrictnessMark]
 -- ^ Give the demands on the arguments of a
@@ -1668,6 +1671,21 @@ dataConOtherTheta dc = dcOtherTheta dc
 -- | Returns the arg types of the worker, including *all* non-dependent
 -- evidence, after any flattening has been done and without substituting for
 -- any type variables
+--
+-- In Note [Data constructor workers and wrappers], 'dataConRepArgTys' is
+-- mentioned as the arguments of the worker, in contrast with 'dcOrigArgTys'
+-- which are the arguments of the wrapper. In this context, it makes sense to
+-- consider that coercions should be in the list returned by 'dataConRepArgTys'
+--
+-- In Note [Data con representation] it is said the following
+--
+--    So whenever this module talks about the representation of a data constructor
+--    what it means is the DataCon with all Unpacking having been applied.
+--    We can think of this as the Core representation.
+--
+-- This means we should be careful NOT to use 'dataConRepArgTys' to determine
+-- the number of runtime arguments a function has.
+-- filter (not . isZeroBitTy . scaledThing)
 dataConRepArgTys :: DataCon -> [Scaled Type]
 dataConRepArgTys (MkData { dcRep        = rep
                          , dcEqSpec     = eq_spec


=====================================
compiler/GHC/Types/RepType.hs-boot
=====================================
@@ -0,0 +1,9 @@
+module GHC.Types.RepType where
+
+import Data.Bool
+import GHC.Core.TyCo.Rep (Type)
+import GHC.Utils.Misc (HasDebugCallStack)
+
+isZeroBitTy :: HasDebugCallStack => Type -> Bool
+
+



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/59234911f3a970b66b2be23324430f4d87ce8689
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/20230327/245dc300/attachment-0001.html>


More information about the ghc-commits mailing list