From 47e924695bdf941098f9d8b0deb712b7c6817fb4 Mon Sep 17 00:00:00 2001
From: Cheng Shao <terrorjack@type.dance>
Date: Sat, 22 Feb 2025 08:38:45 +0000
Subject: [PATCH] ghc-heap: fix HalfWord incompatible Binary instances for
 cross GHC

ghc-heap defines HalfWord as Word32/Word16 depending on host word
size. For cross GHC with different host/target word sizes, the Binary
instances are incompatible and breaks iserv serialization of any
message type that involves HalfWord, breaking the ghci debugger. This
patch fixes the issue and has been tested to fix ghci debugger
functionality of the wasm backend. Fixes #25420 #25781.

(cherry picked from commit b228fcb5313e82895493a6ef7f0a2e803695de02)
(cherry picked from commit 25e75c1fd56b7b88403f640d2b791f2ad59d6bf2)
---
 libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc | 12 +++++++++---
 libraries/ghci/GHCi/Message.hs                       |  4 ++++
 2 files changed, 13 insertions(+), 3 deletions(-)

diff --git a/libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc b/libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc
index 1610027b380..80a29bb1601 100644
--- a/libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc
+++ b/libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc
@@ -1,8 +1,11 @@
 {-# LANGUAGE DeriveGeneric #-}
+{-# LANGUAGE DerivingStrategies #-}
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
+
 module GHC.Exts.Heap.InfoTable.Types
     ( StgInfoTable(..)
     , EntryFunPtr
-    , HalfWord
+    , HalfWord(..)
     , ItblCodes
     ) where
 
@@ -18,13 +21,16 @@ type ItblCodes = Either [Word8] [Word32]
 #include "ghcautoconf.h"
 -- Ultra-minimalist version specially for constructors
 #if SIZEOF_VOID_P == 8
-type HalfWord = Word32
+type HalfWord' = Word32
 #elif SIZEOF_VOID_P == 4
-type HalfWord = Word16
+type HalfWord' = Word16
 #else
 #error Unknown SIZEOF_VOID_P
 #endif
 
+newtype HalfWord = HalfWord HalfWord'
+    deriving newtype (Enum, Eq, Integral, Num, Ord, Real, Show, Storable)
+
 type EntryFunPtr = FunPtr (Ptr () -> IO (Ptr ()))
 
 -- | This is a somewhat faithful representation of an info table. See
diff --git a/libraries/ghci/GHCi/Message.hs b/libraries/ghci/GHCi/Message.hs
index 2660285660f..63b9894afe7 100644
--- a/libraries/ghci/GHCi/Message.hs
+++ b/libraries/ghci/GHCi/Message.hs
@@ -488,6 +488,10 @@ instance Binary (FunPtr a) where
   put = put . castFunPtrToPtr
   get = castPtrToFunPtr <$> get
 
+instance Binary Heap.HalfWord where
+  put x = put (fromIntegral x :: Word32)
+  get = fromIntegral <$> (get :: Get Word32)
+
 -- Binary instances to support the GetClosure message
 #if MIN_VERSION_ghc_heap(8,11,0)
 instance Binary Heap.StgTSOProfInfo
-- 
GitLab