Avoid evaluating unsafe coercions before the safety checks
Only inline unsafeCoerce in CorePrep, to avoid floating unsafeCoerce calls out and evaluating a cast before the check for its safety.
Here's an example of how this happens (from the regression test T16893 -- not included in this patch):
$wcloseComplex d ww
= case sameTypeRep ww t1 of
True -> case ww |> (UnsafeCo ...) of { OpenComplex .. -> ... }
False -> case sameTypeRep ww t2 of
True -> case ww |> (UnsafeCo ...) of { CloseComplex .. -> ... }
False -> ...
The two cases on ww are both evaluating something we know is evaluated so we
float the cases on ww
out:
$wcloseComplex d ww
= case ww |> (UnsafeCo ...) of { OpenComplex .. ->
case ww |> (UnsafeCo ...) of { CloseComplex .. ->
case sameTypeRep ww t1 of
True -> ...
False -> case sameTypeRep ww t2 of
True -> ...
False -> ...
Which is bogus as ww can't be both OpenComplex
and CloseComplex
.
With this patch we avoid floating unsafe coercions by removing the "compulsory
unfolding" of unsafeCoerce#
(making it opaque to the simplifier) and then
eliminating it in CorePrep. (this is similar to how we handle GHC.Magic.lazy
or GHC.Magic.noinline
)
Fixes #16893 (closed)
Merge request reports
Activity
mentioned in issue #16893 (closed)
added 44 commits
-
f03cf43d...52f755aa - 43 commits from branch
ghc:master
- ceb0cec2 - Late inline unsafeCoerce
-
f03cf43d...52f755aa - 43 commits from branch
I'm making progress. I made two changes:
- I made
unsafeCoerceId
non-inlinable by removing it's unfolding. - I manually inlined
unsafeCoerce
in CorePrep:
However this causes an assertion error when building the ghc-heap library. The STG that causes the problem:
GHC.Exts.Heap.$fHasHeapRepInt64Repa1 :: forall (a :: TYPE 'GHC.Types.Int64Rep). (GHC.Prim.Int64# GHC.Types.~ a) => a -> GHC.Prim.State# GHC.Prim.RealWorld -> (# GHC.Prim.State# GHC.Prim.RealWorld, GHC.Exts.Heap.Closures.GenClosure GHC.Exts.Heap.Closures.Box #) [GblId, Arity=3, Caf=NoCafRefs, Str=<L,A><L,U><L,U>, Unf=OtherCon []] = \r [$d~_s7Yk x_s7Yl s_s7Ym] let { sat_s7Yo [Occ=Once] :: GHC.Exts.Heap.Closures.GenClosure GHC.Exts.Heap.Closures.Box [LclId] = \u [] case x_s7Yl of wild_s7Yn [Occ=Once] { __DEFAULT -> GHC.Exts.Heap.Closures.Int64Closure [GHC.Exts.Heap.Closures.PInt64 wild_s7Yn]; }; } in (#,#) [s_s7Ym sat_s7Yo];
This is part of this Haskell definition:
instance Int64# ~ a => HasHeapRep (a :: TYPE 'Int64Rep) where getClosureData x = return $ Int64Closure { ptipe = PInt64, int64Val = I64# (unsafeCoerce# x) }
The STG causes a panic in
cgCase
becuase "prim rep slots" ofx_s7Yl
(scrutinee, prim repInt64Rep
) andwild_s7Yn
(case binder, prim repIntRep
) do not match.I guess the first argument (
GHC.Prim.Int64# GHC.Types.~ a
) should fix the type error, but that should somehow happen before the STG phase? I'll investigate further.- I made
I think in the panic shown above it may actually be the assertion that is wrong, see #16952 (closed).
Minimal reproducer:
{-# LANGUAGE MagicHash, FlexibleInstances, TypeInType, GADTs #-} module Lib where import Data.Int import GHC.Exts import GHC.Int data PrimType = PInt64 class HasHeapRep (a :: TYPE rep) where getClosureData :: a -> IO Closure data Closure = Int64Closure !Int64 instance Int64# ~ a => HasHeapRep (a :: TYPE 'Int64Rep) where getClosureData x = return (Int64Closure (I64# (unsafeCoerce# x)))
Error:
ghc-stage1: panic! (the 'impossible' happened) (GHC version 8.9.0.20190716: cgCase: reps do not match, perhaps a dodgy unsafeCoerce? x_s1vV :: a_a1gi (Int64Rep) wild_s1vW :: Int# (IntRep) Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler/utils/Outputable.hs:1179:37 in ghc:Outputable pprPanic, called at compiler/codeGen/StgCmmExpr.hs:435:12 in ghc:StgCmmExpr Please report this as a GHC bug: https://www.haskell.org/ghc/reportabug
STG:
$cgetClosureData_r1so :: forall (a :: TYPE 'GHC.Types.Int64Rep). (GHC.Prim.Int64# GHC.Types.~ a) => a -> GHC.Types.IO Lib.Closure [GblId, Arity=2, Unf=OtherCon []] = \r [$d~_s1vU x_s1vV] let { sat_s1vY [Occ=Once] :: Lib.Closure [LclId] = \u [] case x_s1vV of wild_s1vW [Occ=Once] { __DEFAULT -> let { sat_s1vX [Occ=Once] :: GHC.Int.Int64 [LclId] = CCCS GHC.Int.I64#! [wild_s1vW]; } in Lib.Int64Closure [sat_s1vX]; }; } in GHC.Base.return GHC.Base.$fMonadIO sat_s1vY;
The program passes Core Lint.
mentioned in merge request !1455 (closed)
I think @bgamari is picking this up.
I'm back this week so I can finish this work if @bgamari has other things to do.
assigned to @osa1
In #16964 (closed) we discuss removing
IntRep
(it'd beInt32Rep
on 32-bit,Int64Rep
on 64-bit). Doing that would unblock this as well.mentioned in issue #17026
mentioned in merge request !1552 (closed)
In #16964 (closed) we discuss removing
IntRep
(it'd beInt32Rep
on 32-bit,Int64Rep
on 64-bit). Doing that would unblock this as well.But what exactly is the problem with this patch? What is really going wrong?
Looking at it, I think !1552 (closed) will fix this, because actually
IntRep
is indeed compatible withInt64Rep
on 64-bit architectures.mentioned in commit 50115378
mentioned in merge request !1667 (closed)
added 140 commits
-
ceb0cec2...b55ee979 - 138 commits from branch
ghc:master
- 50115378 - Refactor bad coercion checking in a few places
- 80768ace - Late inline unsafeCoerce
-
ceb0cec2...b55ee979 - 138 commits from branch