Skip to content
Snippets Groups Projects
Commit ab9cd52d authored by Sylvain Henry's avatar Sylvain Henry Committed by Marge Bot
Browse files

ghc-heap: remove wrong Addr# coercion (#23181)

Conversion from Addr# to I# isn't correct with the JS backend.
parent 43ebd5dc
No related branches found
No related tags found
No related merge requests found
Pipeline #65240 canceled
......@@ -120,7 +120,7 @@ instance Word64# ~ a => HasHeapRep (a :: TYPE 'Word64Rep) where
instance Addr# ~ a => HasHeapRep (a :: TYPE 'AddrRep) where
getClosureData x = return $
AddrClosure { ptipe = PAddr, addrVal = I# (unsafeCoerce# x) }
AddrClosure { ptipe = PAddr, addrVal = Ptr x }
instance Float# ~ a => HasHeapRep (a :: TYPE 'FloatRep) where
getClosureData x = return $
......
......@@ -329,7 +329,7 @@ data GenClosure b
-- | Primitive Addr
| AddrClosure
{ ptipe :: PrimType
, addrVal :: !Int }
, addrVal :: !(Ptr ()) }
-- | Primitive Float
| FloatClosure
......
......@@ -12,6 +12,7 @@ import GHC.Int
import GHC.IO
import GHC.IORef
import GHC.MVar
import GHC.Ptr
import GHC.Stack
import GHC.STRef
import GHC.Weak
......@@ -176,7 +177,7 @@ exWord64Closure = Word64Closure
exAddrClosure :: Closure
exAddrClosure = AddrClosure
{ ptipe = PAddr, addrVal = 42 }
{ ptipe = PAddr, addrVal = nullPtr `plusPtr` 42 }
exFloatClosure :: Closure
exFloatClosure = FloatClosure
......@@ -328,7 +329,7 @@ main = do
-- assertClosuresEq exWord64Closure
-- Primitive Addr
let v = unsafeCoerce# 42# :: Addr#
let (Ptr v) = nullPtr `plusPtr` 42
getClosureData v >>=
assertClosuresEq exAddrClosure
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment