[Git][ghc/ghc][wip/T17521] Update lint and allow coercions

Jaro Reinders (@Noughtmare) gitlab at gitlab.haskell.org
Fri Aug 11 13:14:05 UTC 2023



Jaro Reinders pushed to branch wip/T17521 at Glasgow Haskell Compiler / GHC


Commits:
3a068538 by Jaro Reinders at 2023-08-11T15:13:55+02:00
Update lint and allow coercions

- - - - -


4 changed files:

- compiler/GHC/Core.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/Stg/Lint.hs


Changes:

=====================================
compiler/GHC/Core.hs
=====================================
@@ -527,7 +527,10 @@ So, for the first incarnation of this feature we choose very restrictive
 conditions, which are still useful in practice. We allow top-level unlifted
 data constructor workers if they are applied to arguments that are one of:
 
-* A Literal. Literals are guaranteed to be fully evaluated.
+* A literal. Literals are guaranteed to be fully evaluated.
+
+* A coercion. These are always fully evaluated and even removed when compiling
+  to STG.
 
 * Any expressions of lifted type, but only if that argument is not
   marked strict.


=====================================
compiler/GHC/Core/Lint.hs
=====================================
@@ -590,9 +590,10 @@ lintLetBind top_lvl rec_flag binder rhs rhs_ty
        ; checkL ( isJoinId binder
                || mightBeLiftedType binder_ty
                || (isNonRec rec_flag && exprOkForSpeculation rhs)
-               || isDataConWorkId binder || isDataConWrapId binder -- until #17521 is fixed
                || exprIsTickedString rhs
-               || isTopLevel top_lvl && isBoxedType rhs_ty && isJust (do (Var v, xs) <- pure (collectArgs rhs); guard (isDataConWorkId v && all exprIsTrivial xs)))
+               || isTopLevel top_lvl
+                    && isBoxedType rhs_ty
+                    && exprIsDataConValue False rhs)
            (badBndrTyMsg binder (text "unlifted"))
 
         -- Check that if the binder is at the top level and has type Addr#,


=====================================
compiler/GHC/Core/Utils.hs
=====================================
@@ -31,7 +31,7 @@ module GHC.Core.Utils (
         exprIsWorkFree, exprIsConLike,
         isCheapApp, isExpandableApp, isSaturatedConApp,
         exprIsTickedString, exprIsTickedString_maybe,
-        exprIsTopLevelBindable,
+        exprIsTopLevelBindable, exprIsDataConValue,
         altsAreExhaustive, etaExpansionTick,
 
         -- * Equality
@@ -2017,7 +2017,7 @@ exprIsTopLevelBindable expr ty
     -- consequently we must use 'mightBeUnliftedType' rather than 'isUnliftedType',
     -- as the latter would panic.
   || exprIsTickedString expr
-  || isBoxedType ty && exprIsDataConValue expr
+  || isBoxedType ty && exprIsDataConValue True expr
 
 -- | Check if the expression is zero or more Ticks wrapped around a literal
 -- string.
@@ -2028,8 +2028,8 @@ exprIsTickedString = isJust . exprIsTickedString_maybe
 -- We use this function to determine if unlifted expressions can be floated
 -- to the top level.
 -- See Note [Core top-level unlifted data-con values] in GHC.Core
-exprIsDataConValue :: CoreExpr -> Bool
-exprIsDataConValue x = is_datacon_app x
+exprIsDataConValue :: Bool -> CoreExpr -> Bool
+exprIsDataConValue nesting_allowed x = is_datacon_app x
   where
     -- We cannot use @exprIsHNF@ because it does not handle
     -- data constructor worker strictness properly.
@@ -2045,6 +2045,7 @@ exprIsDataConValue x = is_datacon_app x
     is_datacon_app _ = False
 
     arg_ok _ _ Lit{} = True
+    arg_ok _ _ Coercion{} = True
     arg_ok (Just Lifted) False _ = True
     arg_ok (Just Unlifted) _ Var{} = True
     -- We allow nested constructor applications; we trust that they will
@@ -2063,7 +2064,7 @@ exprIsDataConValue x = is_datacon_app x
     --    foo2 = UNil
     --
     -- This does always seem to happen and is checked by the Core linter.
-    arg_ok (Just Unlifted) _ x = is_datacon_app x
+    arg_ok (Just Unlifted) _ x = nesting_allowed && is_datacon_app x
     arg_ok _ _ _ = False
 
     -- This is slightly different from 'collectArgs' as it looks through ticks


=====================================
compiler/GHC/Stg/Lint.hs
=====================================
@@ -209,8 +209,9 @@ lint_binds_help top_lvl (binder, rhs)
         -- Check binder doesn't have unlifted type or it's a join point
         checkL ( isJoinId binder
               || not (isUnliftedType (idType binder))
-              || isDataConWorkId binder || isDataConWrapId binder -- until #17521 is fixed
-              || isTopLevel top_lvl && isBoxedType (idType binder) && case rhs of StgRhsCon{} -> True; _ -> False)
+              || isTopLevel top_lvl
+                   && isBoxedType (idType binder)
+                   && case rhs of StgRhsCon{} -> True; _ -> False)
           (mkUnliftedTyMsg opts binder rhs)
 
 -- | Top-level bindings can't inherit the cost centre stack from their



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3a06853820203862c5698b8a6f91596bdff7b9ee
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/20230811/02218d95/attachment-0001.html>


More information about the ghc-commits mailing list