[Git][ghc/ghc][wip/T23146] 2 commits: Revert "Account for all VoidRep types on precomputedStaticConInfo"

Rodrigo Mesquita (@alt-romes) gitlab at gitlab.haskell.org
Tue Mar 28 23:09:07 UTC 2023



Rodrigo Mesquita pushed to branch wip/T23146 at Glasgow Haskell Compiler / GHC


Commits:
5b37b9c6 by Rodrigo Mesquita at 2023-03-29T00:02:59+01:00
Revert "Account for all VoidRep types on precomputedStaticConInfo"

This reverts commit 5551ba681e704afccb7d896618b660172ef4c368.

- - - - -
8c2a8ae0 by Rodrigo Mesquita at 2023-03-29T00:08:07+01:00
Attempt patch just on mkLFImported, audit isNullaryRepDataCon later.

- - - - -


3 changed files:

- compiler/GHC/Core/DataCon.hs
- compiler/GHC/StgToCmm/Closure.hs
- compiler/GHC/StgToCmm/DataCon.hs


Changes:

=====================================
compiler/GHC/Core/DataCon.hs
=====================================
@@ -1397,7 +1397,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. ROMES:TODO:
+-- the extra ones are the existentially quantified dictionaries
 dataConRepArity :: DataCon -> Arity
 dataConRepArity (MkData { dcRepArity = arity }) = arity
 


=====================================
compiler/GHC/StgToCmm/Closure.hs
=====================================
@@ -24,8 +24,6 @@ module GHC.StgToCmm.Closure (
         NonVoid(..), fromNonVoid, nonVoidIds, nonVoidStgArgs,
         assertNonVoidIds, assertNonVoidStgArgs,
 
-        isStgNullaryDataCon,
-
         -- * LambdaFormInfo
         LambdaFormInfo,         -- Abstract
         StandardFormInfo,        -- ...ditto...
@@ -203,18 +201,6 @@ addArgReps = map (\arg -> let arg' = fromNonVoid arg
 argPrimRep :: StgArg -> PrimRep
 argPrimRep arg = typePrimRep1 (stgArgType arg)
 
--- | Morally equivalent to @isNullaryRepDataCon con@ at the Stg level, where
--- we do not consider types with no runtime representation to be constructor
--- arguments.
---
--- 'isNullaryRepDataCon' is not fit for checking whether the constructor is
--- nullary at the Stg level because the function 'dataConRepArgTys' it
--- depends on includes unlifted type equalities, whose runtime
--- representation is 'VoidRep', in the returned list.
-isStgNullaryDataCon :: DataCon -> Bool
-isStgNullaryDataCon =
-    null . filter (not . isZeroBitTy . scaledThing) . dataConRepArgTys
-
 ------------------------------------------------------
 --                Building LambdaFormInfo
 ------------------------------------------------------
@@ -285,7 +271,7 @@ mkLFImported id =
         -- Interface doesn't have a LambdaFormInfo, make a conservative one from
         -- the type.
         | Just con <- isDataConId_maybe id
-        , isStgNullaryDataCon con
+        , length (filter (not . isZeroBitTy . scaledThing) (dataConRepArgTys con)) == 0
             -- See Note [Imported nullary datacon wrappers must have correct LFInfo]
             -- in GHC.StgToCmm.Types
         -> LFCon con   -- An imported nullary constructor


=====================================
compiler/GHC/StgToCmm/DataCon.hs
=====================================
@@ -327,10 +327,9 @@ because they don't support cross package data references well.
 precomputedStaticConInfo_maybe :: StgToCmmConfig -> Id -> DataCon -> [NonVoid StgArg] -> Maybe CgIdInfo
 precomputedStaticConInfo_maybe cfg binder con []
 -- Nullary constructors
-  | isStgNullaryDataCon con
+  | isNullaryRepDataCon con
   = Just $ litIdInfo (stgToCmmPlatform cfg) binder (mkConLFInfo con)
                 (CmmLabel (mkClosureLabel (dataConName con) NoCafRefs))
-
 precomputedStaticConInfo_maybe cfg binder con [arg]
   -- Int/Char values with existing closures in the RTS
   | intClosure || charClosure



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/aae05e9da8e13e3827c5f1b35dd40ce0bc6745ae...8c2a8ae062abc6a5bb66b8b23881a0a10b568813

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/aae05e9da8e13e3827c5f1b35dd40ce0bc6745ae...8c2a8ae062abc6a5bb66b8b23881a0a10b568813
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/20230328/3d4fd0bd/attachment-0001.html>


More information about the ghc-commits mailing list