Linear types: restrict transformations around empty case
This program
{-# LANGUAGE LinearTypes, EmptyCase #-}
module M where
{-# NOINLINE f #-}
f :: a %1-> ()
f x = case () of {}
fails Linear Lint with -dlinear-core-lint -O
. There are three problems.
-
castBottomExpr
converts(case x :: T of {}) :: T
tox
. Commenting this line:
--- a/compiler/GHC/Core/Make.hs
+++ b/compiler/GHC/Core/Make.hs
@@ -239,7 +239,7 @@ castBottomExpr :: CoreExpr -> Type -> CoreExpr
-- return an expression of type 'ty'
-- See Note [Empty case alternatives] in GHC.Core
castBottomExpr e res_ty
- | e_ty `eqType` res_ty = e
+ -- | e_ty `eqType` res_ty = e
| otherwise = Case e (mkWildValBinder One e_ty) res_ty []
where
e_ty = exprType e
works around the problem, but the correct fix is to do this transformation only if the usage environment of the case is completely unrestricted. This needs #18768.
- Worker/wrapper moves the empty case to a separate binding:
f = \ (@a_sCY) (w_sCZ [Dmd=B] :: a_sCY) -> $wf_sD1 @a_sCY void#
where $wf_sD1
contains the empty case. This fails Lint, can be worked around with -fno-worker-wrapper
.
- CorePrep eliminates empty case, just like point 1.
-- Eliminate empty case
-- See Note [Unsafe coercions]
cpeRhsE env (Case scrut _ ty [])
= ...
This ticket is blocked on #18768.