[Git][ghc/ghc][wip/andreask/interpreter_primops] Flatten and expand subword instructions.

Andreas Klebinger (@AndreasK) gitlab at gitlab.haskell.org
Mon Mar 3 17:26:14 UTC 2025


Andreas Klebinger pushed to branch wip/andreask/interpreter_primops at Glasgow Haskell Compiler / GHC


Commits:
6ed53c04 by Andreas Klebinger at 2025-03-03T18:03:08+01:00
Flatten and expand subword instructions.

- - - - -


6 changed files:

- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/ByteCode/Instr.hs
- compiler/GHC/StgToByteCode.hs
- rts/Disassembler.c
- rts/Interpreter.c
- rts/include/rts/Bytecodes.h


Changes:

=====================================
compiler/GHC/ByteCode/Asm.hs
=====================================
@@ -540,30 +540,113 @@ assembleI platform i = case i of
                                  emit bci_CCALL [wOp off, Op np, SmallOp i]
   PRIMCALL                 -> emit bci_PRIMCALL []
 
-  OP_ADD                   -> emit bci_OP_ADD []
-  OP_SUB                   -> emit bci_OP_SUB []
-  OP_AND                   -> emit bci_OP_AND []
-  OP_XOR                   -> emit bci_OP_XOR []
-  OP_NOT                   -> emit bci_OP_NOT []
-  OP_NEG                   -> emit bci_OP_NEG []
-  OP_MUL                   -> emit bci_OP_MUL []
-  OP_SHL                   -> emit bci_OP_SHL []
-  OP_ASR                   -> emit bci_OP_ASR []
-  OP_LSR                   -> emit bci_OP_LSR []
-
-  OP_NEQ                   -> emit bci_OP_NEQ []
-  OP_EQ                    -> emit bci_OP_EQ []
-
-  OP_U_LT                  -> emit bci_OP_U_LT []
-  OP_S_LT                  -> emit bci_OP_S_LT []
-  OP_U_GE                  -> emit bci_OP_U_GE []
-  OP_S_GE                  -> emit bci_OP_S_GE []
-  OP_U_GT                  -> emit bci_OP_U_GT []
-  OP_S_GT                  -> emit bci_OP_S_GT []
-  OP_U_LE                  -> emit bci_OP_U_LE []
-  OP_S_LE                  -> emit bci_OP_S_LE []
-
-  OP_SIZED_SUB rep         -> emit (sizedInstr platform bci_OP_SIZED_SUB rep) []
+  OP_ADD w -> case w of
+    W64                   -> emit bci_OP_ADD_64 []
+    W32                   -> emit bci_OP_ADD_32 []
+    W16                   -> emit bci_OP_ADD_16 []
+    W8                   -> emit bci_OP_ADD_08 []
+  OP_SUB w -> case w of
+    W64                   -> emit bci_OP_SUB_64 []
+    W32                   -> emit bci_OP_SUB_32 []
+    W16                   -> emit bci_OP_SUB_16 []
+    W8                   -> emit bci_OP_SUB_08 []
+  OP_AND w -> case w of
+    W64                   -> emit bci_OP_AND_64 []
+    W32                   -> emit bci_OP_AND_32 []
+    W16                   -> emit bci_OP_AND_16 []
+    W8                   -> emit bci_OP_AND_08 []
+  OP_XOR w -> case w of
+    W64                   -> emit bci_OP_XOR_64 []
+    W32                   -> emit bci_OP_XOR_32 []
+    W16                   -> emit bci_OP_XOR_16 []
+    W8                   -> emit bci_OP_XOR_08 []
+  OP_OR w -> case w of
+    W64                    -> emit bci_OP_OR_64 []
+    W32                    -> emit bci_OP_OR_32 []
+    W16                    -> emit bci_OP_OR_16 []
+    W8                    -> emit bci_OP_OR_08 []
+  OP_NOT w -> case w of
+    W64                   -> emit bci_OP_NOT_64 []
+    W32                   -> emit bci_OP_NOT_32 []
+    W16                   -> emit bci_OP_NOT_16 []
+    W8                   -> emit bci_OP_NOT_08 []
+  OP_NEG w -> case w of
+    W64                   -> emit bci_OP_NEG_64 []
+    W32                   -> emit bci_OP_NEG_32 []
+    W16                   -> emit bci_OP_NEG_16 []
+    W8                   -> emit bci_OP_NEG_08 []
+  OP_MUL w -> case w of
+    W64                   -> emit bci_OP_MUL_64 []
+    W32                   -> emit bci_OP_MUL_32 []
+    W16                   -> emit bci_OP_MUL_16 []
+    W8                   -> emit bci_OP_MUL_08 []
+  OP_SHL w -> case w of
+    W64                   -> emit bci_OP_SHL_64 []
+    W32                   -> emit bci_OP_SHL_32 []
+    W16                   -> emit bci_OP_SHL_16 []
+    W8                   -> emit bci_OP_SHL_08 []
+  OP_ASR w -> case w of
+    W64                   -> emit bci_OP_ASR_64 []
+    W32                   -> emit bci_OP_ASR_32 []
+    W16                   -> emit bci_OP_ASR_16 []
+    W8                   -> emit bci_OP_ASR_08 []
+  OP_LSR w -> case w of
+    W64                   -> emit bci_OP_LSR_64 []
+    W32                   -> emit bci_OP_LSR_32 []
+    W16                   -> emit bci_OP_LSR_16 []
+    W8                   -> emit bci_OP_LSR_08 []
+
+  OP_NEQ w -> case w of
+    W64                   -> emit bci_OP_NEQ_64 []
+    W32                   -> emit bci_OP_NEQ_32 []
+    W16                   -> emit bci_OP_NEQ_16 []
+    W8                   -> emit bci_OP_NEQ_08 []
+  OP_EQ w -> case w of
+    W64                    -> emit bci_OP_EQ_64 []
+    W32                    -> emit bci_OP_EQ_32 []
+    W16                    -> emit bci_OP_EQ_16 []
+    W8                    -> emit bci_OP_EQ_08 []
+
+  OP_U_LT w -> case w of
+    W64                  -> emit bci_OP_U_LT_64 []
+    W32                  -> emit bci_OP_U_LT_32 []
+    W16                  -> emit bci_OP_U_LT_16 []
+    W8                  -> emit bci_OP_U_LT_08 []
+  OP_S_LT w -> case w of
+    W64                  -> emit bci_OP_S_LT_64 []
+    W32                  -> emit bci_OP_S_LT_32 []
+    W16                  -> emit bci_OP_S_LT_16 []
+    W8                  -> emit bci_OP_S_LT_08 []
+  OP_U_GE w -> case w of
+    W64                  -> emit bci_OP_U_GE_64 []
+    W32                  -> emit bci_OP_U_GE_32 []
+    W16                  -> emit bci_OP_U_GE_16 []
+    W8                  -> emit bci_OP_U_GE_08 []
+  OP_S_GE w -> case w of
+    W64                  -> emit bci_OP_S_GE_64 []
+    W32                  -> emit bci_OP_S_GE_32 []
+    W16                  -> emit bci_OP_S_GE_16 []
+    W8                  -> emit bci_OP_S_GE_08 []
+  OP_U_GT w -> case w of
+    W64                  -> emit bci_OP_U_GT_64 []
+    W32                  -> emit bci_OP_U_GT_32 []
+    W16                  -> emit bci_OP_U_GT_16 []
+    W8                  -> emit bci_OP_U_GT_08 []
+  OP_S_GT w -> case w of
+    W64                  -> emit bci_OP_S_GT_64 []
+    W32                  -> emit bci_OP_S_GT_32 []
+    W16                  -> emit bci_OP_S_GT_16 []
+    W8                  -> emit bci_OP_S_GT_08 []
+  OP_U_LE w -> case w of
+    W64                  -> emit bci_OP_U_LE_64 []
+    W32                  -> emit bci_OP_U_LE_32 []
+    W16                  -> emit bci_OP_U_LE_16 []
+    W8                  -> emit bci_OP_U_LE_08 []
+  OP_S_LE w -> case w of
+    W64                  -> emit bci_OP_S_LE_64 []
+    W32                  -> emit bci_OP_S_LE_32 []
+    W16                  -> emit bci_OP_S_LE_16 []
+    W8                  -> emit bci_OP_S_LE_08 []
 
   BRK_FUN arr tick_mod tickx info_mod infox cc ->
                               do p1 <- ptr (BCOPtrBreakArray arr)


=====================================
compiler/GHC/ByteCode/Instr.hs
=====================================
@@ -37,6 +37,7 @@ import GHC.Stg.Syntax
 import GHCi.BreakArray (BreakArray)
 import Language.Haskell.Syntax.Module.Name (ModuleName)
 import GHC.Types.RepType (PrimRep)
+import GHC.Cmm.Type (Width)
 
 -- ----------------------------------------------------------------------------
 -- Bytecode instructions
@@ -215,34 +216,34 @@ data BCInstr
 
    | PRIMCALL
 
-   -- Primops
-   | OP_ADD
-   | OP_SUB
-   | OP_AND
-   | OP_XOR
-   | OP_MUL
-   | OP_SHL
-   | OP_ASR
-   | OP_LSR
-
-   | OP_NOT
-   | OP_NEG
-
-   | OP_NEQ
-   | OP_EQ
-
-   | OP_U_LT
-   | OP_U_GE
-   | OP_U_GT
-   | OP_U_LE
-
-   | OP_S_LT
-   | OP_S_GE
-   | OP_S_GT
-   | OP_S_LE
-
-   | OP_SIZED_SUB PrimRep
-
+   -- Primops - The actual interpreter instructions are flattened into 64/32/16/8 wide
+   -- instructions. But for generating code it's handy to have the width as argument
+   -- to avoid duplication.
+   | OP_ADD !Width
+   | OP_SUB !Width
+   | OP_AND !Width
+   | OP_XOR !Width
+   | OP_MUL !Width
+   | OP_SHL !Width
+   | OP_ASR !Width
+   | OP_LSR !Width
+   | OP_OR  !Width
+
+   | OP_NOT !Width
+   | OP_NEG !Width
+
+   | OP_NEQ !Width
+   | OP_EQ !Width
+
+   | OP_U_LT !Width
+   | OP_U_GE !Width
+   | OP_U_GT !Width
+   | OP_U_LE !Width
+
+   | OP_S_LT !Width
+   | OP_S_GE !Width
+   | OP_S_GT !Width
+   | OP_S_LE !Width
 
    -- For doing magic ByteArray passing to foreign calls
    | SWIZZLE          !WordOff -- to the ptr N words down the stack,
@@ -424,30 +425,28 @@ instance Outputable BCInstr where
                                                       _   -> empty)
    ppr PRIMCALL              = text "PRIMCALL"
 
-   ppr OP_ADD                = text "OP_ADD"
-   ppr OP_SUB                = text "OP_SUB"
-   ppr OP_AND                = text "OP_AND"
-   ppr OP_XOR                = text "OP_XOR"
-   ppr OP_NOT                = text "OP_NOT"
-   ppr OP_NEG                = text "OP_NEG"
-   ppr OP_MUL                = text "OP_MUL"
-   ppr OP_SHL                = text "OP_SHL"
-   ppr OP_ASR                = text "OP_ASR"
-   ppr OP_LSR                = text "OP_LSR"
-
-   ppr OP_EQ                = text "OP_EQ"
-   ppr OP_NEQ               = text "OP_NEQ"
-   ppr OP_S_LT                = text "OP_S_LT"
-   ppr OP_S_GE                = text "OP_S_GE"
-   ppr OP_S_GT                = text "OP_S_GT"
-   ppr OP_S_LE                = text "OP_S_LE"
-   ppr OP_U_LT                = text "OP_U_LT"
-   ppr OP_U_GE                = text "OP_U_GE"
-   ppr OP_U_GT                = text "OP_U_GT"
-   ppr OP_U_LE                = text "OP_U_LE"
-
-   ppr (OP_SIZED_SUB rep)   = text "OP_SIZED_SUB" <+> (ppr rep)
-
+   ppr (OP_ADD w)            = text "OP_ADD_" <> ppr w
+   ppr (OP_SUB w)            = text "OP_SUB_" <> ppr w
+   ppr (OP_AND w)            = text "OP_AND_" <> ppr w
+   ppr (OP_XOR w)            = text "OP_XOR_" <> ppr w
+   ppr (OP_OR w)             = text "OP_OR_" <> ppr w
+   ppr (OP_NOT w)            = text "OP_NOT_" <> ppr w
+   ppr (OP_NEG w)            = text "OP_NEG_" <> ppr w
+   ppr (OP_MUL w)            = text "OP_MUL_" <> ppr w
+   ppr (OP_SHL w)            = text "OP_SHL_" <> ppr w
+   ppr (OP_ASR w)            = text "OP_ASR_" <> ppr w
+   ppr (OP_LSR w)            = text "OP_LSR_" <> ppr w
+
+   ppr (OP_EQ w)             = text "OP_EQ_" <> ppr w
+   ppr (OP_NEQ w)            = text "OP_NEQ_" <> ppr w
+   ppr (OP_S_LT w)           = text "OP_S_LT_" <> ppr w
+   ppr (OP_S_GE w)           = text "OP_S_GE_" <> ppr w
+   ppr (OP_S_GT w)           = text "OP_S_GT_" <> ppr w
+   ppr (OP_S_LE w)           = text "OP_S_LE_" <> ppr w
+   ppr (OP_U_LT w)           = text "OP_U_LT_" <> ppr w
+   ppr (OP_U_GE w)           = text "OP_U_GE_" <> ppr w
+   ppr (OP_U_GT w)           = text "OP_U_GT_" <> ppr w
+   ppr (OP_U_LE w)           = text "OP_U_LE_" <> ppr w
 
    ppr (SWIZZLE stkoff n)    = text "SWIZZLE " <+> text "stkoff" <+> ppr stkoff
                                                <+> text "by" <+> ppr n
@@ -561,6 +560,7 @@ bciStackUse OP_ADD{}              = 0 -- We overestimate, it's -1 actually ...
 bciStackUse OP_SUB{}              = 0
 bciStackUse OP_AND{}              = 0
 bciStackUse OP_XOR{}              = 0
+bciStackUse OP_OR{}               = 0
 bciStackUse OP_NOT{}              = 0
 bciStackUse OP_NEG{}              = 0
 bciStackUse OP_MUL{}              = 0
@@ -579,8 +579,6 @@ bciStackUse OP_U_GT{}               = 0
 bciStackUse OP_U_LE{}               = 0
 bciStackUse OP_U_GE{}               = 0
 
-bciStackUse OP_SIZED_SUB{}        = 0
-
 bciStackUse SWIZZLE{}             = 0
 bciStackUse BRK_FUN{}             = 0
 


=====================================
compiler/GHC/StgToByteCode.hs
=====================================
@@ -60,6 +60,7 @@ import GHC.Utils.Exception (evaluate)
 import GHC.StgToCmm.Closure ( NonVoid(..), fromNonVoid, idPrimRepU,
                               addIdReps, addArgReps,
                               assertNonVoidIds, assertNonVoidStgArgs )
+import GHC.CmmToAsm.Config (platformWordWidth)
 import GHC.StgToCmm.Layout
 import GHC.Runtime.Heap.Layout hiding (WordOff, ByteOff, wordsToBytes)
 import GHC.Data.Bitmap
@@ -850,12 +851,12 @@ doPrimOp op init_d s p args =
     Int64SubOp -> primOp OP_SUB
     Word64SubOp -> primOp OP_SUB
 
-    Int8SubOp   -> primOp (OP_SIZED_SUB primArg1Width)
-    Word8SubOp  -> primOp (OP_SIZED_SUB primArg1Width)
-    Int16SubOp  -> primOp (OP_SIZED_SUB primArg1Width)
-    Word16SubOp -> primOp (OP_SIZED_SUB primArg1Width)
-    Int32SubOp  -> primOp (OP_SIZED_SUB primArg1Width)
-    Word32SubOp -> primOp (OP_SIZED_SUB primArg1Width)
+    Int8SubOp   -> primOp OP_SUB
+    Word8SubOp  -> primOp OP_SUB
+    Int16SubOp  -> primOp OP_SUB
+    Word16SubOp -> primOp OP_SUB
+    Int32SubOp  -> primOp OP_SUB
+    Word32SubOp -> primOp OP_SUB
 
     IntAndOp -> primOp OP_AND
     WordAndOp -> primOp OP_AND
@@ -869,6 +870,19 @@ doPrimOp op init_d s p args =
     WordXorOp -> primOp OP_XOR
     Word64XorOp -> primOp OP_XOR
 
+    IntOrOp -> primOp OP_OR
+    WordOrOp -> primOp OP_OR
+    Word64OrOp -> primOp OP_OR
+
+    WordSllOp   -> primOp OP_SHL
+    Word64SllOp -> primOp OP_SHL
+    IntSllOp    -> primOp OP_SHL
+    Int64SllOp  -> primOp OP_SHL
+    Word64SrlOp -> primOp OP_LSR
+    WordSrlOp   -> primOp OP_LSR
+    IntSrlOp    -> primOp OP_ASR
+    Int64SrlOp  -> primOp OP_ASR
+
     IntNeOp -> primOp OP_NEQ
     WordNeOp -> primOp OP_NEQ
     Word64NeOp -> primOp OP_NEQ
@@ -912,20 +926,47 @@ doPrimOp op init_d s p args =
     OrdOp           -> no_op
 
     _ -> Nothing
-    where
-      primArg1Width = (stgArgRepU $ head args) :: PrimRep
-      -- Push args, execute primop, slide, return_N
-      primOp op_inst = Just $ do
-        platform <- profilePlatform <$> getProfile
-        prim_code <- mkPrimOpCode init_d s p op_inst args
-        let slide = mkSlideW 1 (bytesToWords platform $ init_d - s) `snocOL` RETURN N
-        return $ prim_code `appOL` slide
+  where
+    primArg1Width platform (arg:_)
+      | rep <- (stgArgRepU arg)
+      = case rep of
+        AddrRep -> platformWordWidth platform
+        IntRep -> platformWordWidth platform
+        WordRep -> platformWordWidth platform
 
-      no_op = Just $ do
-        platform <- profilePlatform <$> getProfile
-        prim_code <- terribleNoOp init_d s p undefined args
-        let slide = mkSlideW 1 (bytesToWords platform $ init_d - s) `snocOL` RETURN N
-        return $ prim_code `appOL` slide
+        Int64Rep -> W64
+        Word64Rep -> W64
+
+        Int32Rep -> W32
+        Word32Rep -> W32
+
+        Int16Rep -> W16
+        Word16Rep -> W16
+
+        Int8Rep -> W8
+        Word8Rep -> W8
+
+        FloatRep -> unexpectedRep
+        DoubleRep -> unexpectedRep
+
+        BoxedRep{} -> unexpectedRep
+        VecRep{} -> unexpectedRep
+      where
+        unexpectedRep = panic "doPrimOp: Unexpected argument rep"
+    primArg1Width _ _  = panic "doPrimOp: Unexpected argument count"
+
+    -- Push args, execute primop, slide, return_N
+    primOp op_inst = Just $ do
+      platform <- profilePlatform <$> getProfile
+      prim_code <- mkPrimOpCode init_d s p (op_inst $ primArg1Width platform args) $ args
+      let slide = mkSlideW 1 (bytesToWords platform $ init_d - s) `snocOL` RETURN N
+      return $ prim_code `appOL` slide
+
+    no_op = Just $ do
+      platform <- profilePlatform <$> getProfile
+      prim_code <- terribleNoOp init_d s p undefined args
+      let slide = mkSlideW 1 (bytesToWords platform $ init_d - s) `snocOL` RETURN N
+      return $ prim_code `appOL` slide
 
 -- It's horrible, but still better than calling intToWord ...
 terribleNoOp


=====================================
rts/Disassembler.c
=====================================
@@ -63,6 +63,26 @@ disInstr ( StgBCO *bco, int pc )
 #endif
 #define BCO_GET_LARGE_ARG ((instr & bci_FLAG_LARGE_ARGS) ? BCO_READ_NEXT_WORD : BCO_NEXT)
 #define BCO_GET_BCI_WIDTH(bci) ((bci & bci_FLAG_WIDTH) >> 13)
+// For brevity
+#define BELCH_INSTR_NAME(OP_NAME) \
+   case bci_ ## OP_NAME: \
+      debugBelch("OP_NAME\n"); \
+      break
+
+#define BELCH_INSTR_NAME_ALL_SIZES(OP_NAME) \
+   case bci_ ## OP_NAME ## _64: \
+      debugBelch("#OP_NAME" "_64\n"); \
+      break; \
+   case bci_ ## OP_NAME ## _32: \
+      debugBelch("#OP_NAME" "_32\n"); \
+      break; \
+   case bci_ ## OP_NAME ## _16: \
+      debugBelch("#OP_NAME" "_16\n"); \
+      break; \
+   case bci_ ## OP_NAME ## _08: \
+      debugBelch("#OP_NAME" "_08\n"); \
+      break;
+
 
    switch (instr & 0xff) {
       case bci_BRK_FUN:
@@ -420,38 +440,20 @@ disInstr ( StgBCO *bco, int pc )
          debugBelch("TESTEQ_P  %d, fail to %d\n", instrs[pc],
                                                       instrs[pc+1]);
          pc += 2; break;
-      case bci_CASEFAIL:
-         debugBelch("CASEFAIL\n" );
-         break;
+      BELCH_INSTR_NAME(CASEFAIL);
       case bci_JMP:
          debugBelch("JMP to    %d\n", instrs[pc]);
          pc += 1; break;
 
-      case bci_ENTER:
-         debugBelch("ENTER\n");
-         break;
+      BELCH_INSTR_NAME(ENTER);
+      BELCH_INSTR_NAME(RETURN_P);
+      BELCH_INSTR_NAME(RETURN_N);
+      BELCH_INSTR_NAME(RETURN_F);
+      BELCH_INSTR_NAME(RETURN_D);
+      BELCH_INSTR_NAME(RETURN_L);
+      BELCH_INSTR_NAME(RETURN_V);
+      BELCH_INSTR_NAME(RETURN_T);
 
-      case bci_RETURN_P:
-         debugBelch("RETURN_P\n" );
-         break;
-      case bci_RETURN_N:
-         debugBelch("RETURN_N\n" );
-         break;
-      case bci_RETURN_F:
-         debugBelch("RETURN_F\n" );
-         break;
-      case bci_RETURN_D:
-         debugBelch("RETURN_D\n" );
-         break;
-      case bci_RETURN_L:
-         debugBelch("RETURN_L\n" );
-         break;
-      case bci_RETURN_V:
-         debugBelch("RETURN_V\n" );
-         break;
-      case bci_RETURN_T:
-         debugBelch("RETURN_T\n ");
-         break;
 
       case bci_BCO_NAME: {
          const char *name = (const char*) literals[instrs[pc]];
@@ -460,74 +462,30 @@ disInstr ( StgBCO *bco, int pc )
          break;
       }
 
-      case bci_OP_ADD:
-         debugBelch("OP_ADD\n");
-         break;
-      case bci_OP_SUB:
-         debugBelch("OP_SUB\n");
-         break;
-      case bci_OP_AND:
-         debugBelch("OP_AND\n");
-         break;
-      case bci_OP_XOR:
-         debugBelch("OP_XOR\n");
-         break;
-      case bci_OP_NOT:
-         debugBelch("OP_NOT\n");
-         break;
-      case bci_OP_NEG:
-         debugBelch("OP_NEG\n");
-         break;
-      case bci_OP_MUL:
-         debugBelch("OP_MUL\n");
-         break;
-      case bci_OP_SHL:
-         debugBelch("OP_SHL\n");
-         break;
-      case bci_OP_ASR:
-         debugBelch("OP_ASR\n");
-         break;
-      case bci_OP_LSR:
-         debugBelch("OP_LSR\n");
-         break;
-
-      case bci_OP_NEQ:
-         debugBelch("OP_NEQ\n");
-         break;
-      case bci_OP_EQ:
-         debugBelch("OP_EQ\n");
-         break;
-
-      case bci_OP_U_GT:
-         debugBelch("OP_U_GT\n");
-         break;
-      case bci_OP_U_LE:
-         debugBelch("OP_U_LE\n");
-         break;
-      case bci_OP_U_GE:
-         debugBelch("OP_U_GE\n");
-         break;
-      case bci_OP_U_LT:
-         debugBelch("OP_U_LT\n");
-         break;
-
-      case bci_OP_S_GT:
-         debugBelch("OP_S_GT\n");
-         break;
-      case bci_OP_S_LE:
-         debugBelch("OP_S_LE\n");
-         break;
-      case bci_OP_S_GE:
-         debugBelch("OP_S_GE\n");
-         break;
-      case bci_OP_S_LT:
-         debugBelch("OP_S_LT\n");
-         break;
-
-      case bci_OP_SIZED_SUB:
-         debugBelch("OP_SIZED_SUB_%d\n",BCO_GET_BCI_WIDTH(instr));
-         break;
-
+      BELCH_INSTR_NAME_ALL_SIZES(OP_ADD);
+      BELCH_INSTR_NAME_ALL_SIZES(OP_SUB);
+      BELCH_INSTR_NAME_ALL_SIZES(OP_AND);
+      BELCH_INSTR_NAME_ALL_SIZES(OP_XOR);
+      BELCH_INSTR_NAME_ALL_SIZES(OP_OR);
+      BELCH_INSTR_NAME_ALL_SIZES(OP_NOT);
+      BELCH_INSTR_NAME_ALL_SIZES(OP_NEG);
+      BELCH_INSTR_NAME_ALL_SIZES(OP_MUL);
+      BELCH_INSTR_NAME_ALL_SIZES(OP_SHL);
+      BELCH_INSTR_NAME_ALL_SIZES(OP_ASR);
+      BELCH_INSTR_NAME_ALL_SIZES(OP_LSR);
+
+      BELCH_INSTR_NAME_ALL_SIZES(OP_NEQ);
+      BELCH_INSTR_NAME_ALL_SIZES(OP_EQ);
+
+      BELCH_INSTR_NAME_ALL_SIZES(OP_U_GT);
+      BELCH_INSTR_NAME_ALL_SIZES(OP_U_LE);
+      BELCH_INSTR_NAME_ALL_SIZES(OP_U_GE);
+      BELCH_INSTR_NAME_ALL_SIZES(OP_U_LT);
+
+      BELCH_INSTR_NAME_ALL_SIZES(OP_S_GT);
+      BELCH_INSTR_NAME_ALL_SIZES(OP_S_LE);
+      BELCH_INSTR_NAME_ALL_SIZES(OP_S_GE);
+      BELCH_INSTR_NAME_ALL_SIZES(OP_S_LT);
 
       default:
          barf("disInstr: unknown opcode %u", (unsigned int) instr);


=====================================
rts/Interpreter.c
=====================================
@@ -1144,9 +1144,9 @@ run_BCO:
 #endif
 
         bci = BCO_NEXT;
-    /* We use the high 8 bits for flags. The highest three of which are
-     * currently allocated to LARGE_ARGS and WIDTH */
-    ASSERT((bci & 0xFF00) == (bci & ( bci_FLAG_LARGE_ARGS | bci_FLAG_WIDTH )));
+    /* We use the high 8 bits for flags. The highest of which is
+     * currently allocated to LARGE_ARGS */
+    ASSERT((bci & 0xFF00) == (bci & ( bci_FLAG_LARGE_ARGS )));
 
     switch (bci & 0xFF) {
 
@@ -2171,45 +2171,108 @@ run_BCO:
             goto nextInsn;                                                      \
         }
 
-#define UN_INT64_OP(op) UN_SIZED_OP(op,StgInt64)
-#define BIN_INT64_OP(op) SIZED_BIN_OP(op,StgInt64)
-#define BIN_WORD64_OP(op) SIZED_BIN_OP(op,StgWord64)
-
-        case bci_OP_ADD: BIN_INT64_OP(+)
-        case bci_OP_SUB: BIN_INT64_OP(-)
-        case bci_OP_AND: BIN_INT64_OP(&)
-        case bci_OP_XOR: BIN_INT64_OP(^)
-        case bci_OP_MUL: BIN_INT64_OP(*)
-        case bci_OP_SHL: BIN_WORD64_OP(<<)
-        case bci_OP_LSR: BIN_WORD64_OP(>>)
-        case bci_OP_ASR: BIN_INT64_OP(>>)
-
-        case bci_OP_NEQ:  BIN_INT64_OP(!=)
-        case bci_OP_EQ:   BIN_INT64_OP(==)
-        case bci_OP_U_GT: BIN_WORD64_OP(>)
-        case bci_OP_U_GE: BIN_WORD64_OP(>=)
-        case bci_OP_U_LT: BIN_WORD64_OP(<)
-        case bci_OP_U_LE: BIN_WORD64_OP(<=)
-
-        case bci_OP_S_GT: BIN_INT64_OP(>)
-        case bci_OP_S_GE: BIN_INT64_OP(>=)
-        case bci_OP_S_LT: BIN_INT64_OP(<)
-        case bci_OP_S_LE: BIN_INT64_OP(<=)
-
-
-        case bci_OP_NOT: UN_INT64_OP(~)
-        case bci_OP_NEG: UN_INT64_OP(-)
-
-        case bci_OP_SIZED_SUB:
-        {
-            StgWord width = BCO_GET_BCI_WIDTH(bci);
-            switch (width) {
-                case 0: SIZED_BIN_OP(-,StgInt8 )
-                case 1: SIZED_BIN_OP(-,StgInt16)
-                case 2: SIZED_BIN_OP(-,StgInt32)
-                default: barf("Unexpected bci width.");
-            };
-        }
+        case bci_OP_ADD_64: SIZED_BIN_OP(+, StgInt64)
+        case bci_OP_SUB_64: SIZED_BIN_OP(-, StgInt64)
+        case bci_OP_AND_64: SIZED_BIN_OP(&, StgInt64)
+        case bci_OP_XOR_64: SIZED_BIN_OP(^, StgInt64)
+        case bci_OP_OR_64:  SIZED_BIN_OP(|, StgInt64)
+        case bci_OP_MUL_64: SIZED_BIN_OP(*, StgInt64)
+        case bci_OP_SHL_64: SIZED_BIN_OP(<<, StgWord64)
+        case bci_OP_LSR_64: SIZED_BIN_OP(>>, StgWord64)
+        case bci_OP_ASR_64: SIZED_BIN_OP(>>, StgInt64)
+
+        case bci_OP_NEQ_64:  SIZED_BIN_OP(!=, StgWord64)
+        case bci_OP_EQ_64:   SIZED_BIN_OP(==, StgWord64)
+        case bci_OP_U_GT_64: SIZED_BIN_OP(>, StgWord64)
+        case bci_OP_U_GE_64: SIZED_BIN_OP(>=, StgWord64)
+        case bci_OP_U_LT_64: SIZED_BIN_OP(<, StgWord64)
+        case bci_OP_U_LE_64: SIZED_BIN_OP(<=, StgWord64)
+
+        case bci_OP_S_GT_64: SIZED_BIN_OP(>, StgInt64)
+        case bci_OP_S_GE_64: SIZED_BIN_OP(>=, StgInt64)
+        case bci_OP_S_LT_64: SIZED_BIN_OP(<, StgInt64)
+        case bci_OP_S_LE_64: SIZED_BIN_OP(<=, StgInt64)
+
+        case bci_OP_NOT_64: UN_SIZED_OP(~, StgWord64)
+        case bci_OP_NEG_64: UN_SIZED_OP(-, StgInt64)
+
+
+        case bci_OP_ADD_32: SIZED_BIN_OP(+, StgInt32)
+        case bci_OP_SUB_32: SIZED_BIN_OP(-, StgInt32)
+        case bci_OP_AND_32: SIZED_BIN_OP(&, StgInt32)
+        case bci_OP_XOR_32: SIZED_BIN_OP(^, StgInt32)
+        case bci_OP_OR_32:  SIZED_BIN_OP(|, StgInt32)
+        case bci_OP_MUL_32: SIZED_BIN_OP(*, StgInt32)
+        case bci_OP_SHL_32: SIZED_BIN_OP(<<, StgWord32)
+        case bci_OP_LSR_32: SIZED_BIN_OP(>>, StgWord32)
+        case bci_OP_ASR_32: SIZED_BIN_OP(>>, StgInt32)
+
+        case bci_OP_NEQ_32:  SIZED_BIN_OP(!=, StgWord32)
+        case bci_OP_EQ_32:   SIZED_BIN_OP(==, StgWord32)
+        case bci_OP_U_GT_32: SIZED_BIN_OP(>, StgWord32)
+        case bci_OP_U_GE_32: SIZED_BIN_OP(>=, StgWord32)
+        case bci_OP_U_LT_32: SIZED_BIN_OP(<, StgWord32)
+        case bci_OP_U_LE_32: SIZED_BIN_OP(<=, StgWord32)
+
+        case bci_OP_S_GT_32: SIZED_BIN_OP(>, StgInt32)
+        case bci_OP_S_GE_32: SIZED_BIN_OP(>=, StgInt32)
+        case bci_OP_S_LT_32: SIZED_BIN_OP(<, StgInt32)
+        case bci_OP_S_LE_32: SIZED_BIN_OP(<=, StgInt32)
+
+        case bci_OP_NOT_32: UN_SIZED_OP(~, StgWord32)
+        case bci_OP_NEG_32: UN_SIZED_OP(-, StgInt32)
+
+
+        case bci_OP_ADD_16: SIZED_BIN_OP(+, StgInt16)
+        case bci_OP_SUB_16: SIZED_BIN_OP(-, StgInt16)
+        case bci_OP_AND_16: SIZED_BIN_OP(&, StgInt16)
+        case bci_OP_XOR_16: SIZED_BIN_OP(^, StgInt16)
+        case bci_OP_OR_16:  SIZED_BIN_OP(|, StgInt16)
+        case bci_OP_MUL_16: SIZED_BIN_OP(*, StgInt16)
+        case bci_OP_SHL_16: SIZED_BIN_OP(<<, StgWord16)
+        case bci_OP_LSR_16: SIZED_BIN_OP(>>, StgWord16)
+        case bci_OP_ASR_16: SIZED_BIN_OP(>>, StgInt16)
+
+        case bci_OP_NEQ_16:  SIZED_BIN_OP(!=, StgWord16)
+        case bci_OP_EQ_16:   SIZED_BIN_OP(==, StgWord16)
+        case bci_OP_U_GT_16: SIZED_BIN_OP(>, StgWord16)
+        case bci_OP_U_GE_16: SIZED_BIN_OP(>=, StgWord16)
+        case bci_OP_U_LT_16: SIZED_BIN_OP(<, StgWord16)
+        case bci_OP_U_LE_16: SIZED_BIN_OP(<=, StgWord16)
+
+        case bci_OP_S_GT_16: SIZED_BIN_OP(>, StgInt16)
+        case bci_OP_S_GE_16: SIZED_BIN_OP(>=, StgInt16)
+        case bci_OP_S_LT_16: SIZED_BIN_OP(<, StgInt16)
+        case bci_OP_S_LE_16: SIZED_BIN_OP(<=, StgInt16)
+
+        case bci_OP_NOT_16: UN_SIZED_OP(~, StgWord16)
+        case bci_OP_NEG_16: UN_SIZED_OP(-, StgInt16)
+
+
+        case bci_OP_ADD_08: SIZED_BIN_OP(+, StgInt8)
+        case bci_OP_SUB_08: SIZED_BIN_OP(-, StgInt8)
+        case bci_OP_AND_08: SIZED_BIN_OP(&, StgInt8)
+        case bci_OP_XOR_08: SIZED_BIN_OP(^, StgInt8)
+        case bci_OP_OR_08:  SIZED_BIN_OP(|, StgInt8)
+        case bci_OP_MUL_08: SIZED_BIN_OP(*, StgInt8)
+        case bci_OP_SHL_08: SIZED_BIN_OP(<<, StgWord8)
+        case bci_OP_LSR_08: SIZED_BIN_OP(>>, StgWord8)
+        case bci_OP_ASR_08: SIZED_BIN_OP(>>, StgInt8)
+
+        case bci_OP_NEQ_08:  SIZED_BIN_OP(!=, StgWord8)
+        case bci_OP_EQ_08:   SIZED_BIN_OP(==, StgWord8)
+        case bci_OP_U_GT_08: SIZED_BIN_OP(>, StgWord8)
+        case bci_OP_U_GE_08: SIZED_BIN_OP(>=, StgWord8)
+        case bci_OP_U_LT_08: SIZED_BIN_OP(<, StgWord8)
+        case bci_OP_U_LE_08: SIZED_BIN_OP(<=, StgWord8)
+
+        case bci_OP_S_GT_08: SIZED_BIN_OP(>, StgInt8)
+        case bci_OP_S_GE_08: SIZED_BIN_OP(>=, StgInt8)
+        case bci_OP_S_LT_08: SIZED_BIN_OP(<, StgInt8)
+        case bci_OP_S_LE_08: SIZED_BIN_OP(<=, StgInt8)
+
+        case bci_OP_NOT_08: UN_SIZED_OP(~, StgWord8)
+        case bci_OP_NEG_08: UN_SIZED_OP(-, StgInt8)
 
         case bci_CCALL: {
             void *tok;


=====================================
rts/include/rts/Bytecodes.h
=====================================
@@ -114,29 +114,100 @@
 
 #define bci_BCO_NAME                    88
 
-#define bci_OP_ADD                      89
-#define bci_OP_SUB                      90
-#define bci_OP_AND                      91
-#define bci_OP_XOR                      92
-#define bci_OP_NOT                      93
-#define bci_OP_NEG                      94
-#define bci_OP_MUL                      95
-#define bci_OP_SHL                      96
-#define bci_OP_ASR                      97
-#define bci_OP_LSR                      98
-
-#define bci_OP_NEQ                     110
-#define bci_OP_EQ                      111
-#define bci_OP_U_GE                    112
-#define bci_OP_U_GT                    113
-#define bci_OP_U_LT                    114
-#define bci_OP_U_LE                    115
-#define bci_OP_S_GE                    116
-#define bci_OP_S_GT                    117
-#define bci_OP_S_LT                    118
-#define bci_OP_S_LE                    119
-
-#define bci_OP_SIZED_SUB               130
+#define bci_OP_ADD_64                   90
+#define bci_OP_SUB_64                   91
+#define bci_OP_AND_64                   92
+#define bci_OP_XOR_64                   93
+#define bci_OP_NOT_64                   94
+#define bci_OP_NEG_64                   95
+#define bci_OP_MUL_64                   96
+#define bci_OP_SHL_64                   97
+#define bci_OP_ASR_64                   98
+#define bci_OP_LSR_64                   99
+#define bci_OP_OR_64                   100
+
+#define bci_OP_NEQ_64                  110
+#define bci_OP_EQ_64                   111
+#define bci_OP_U_GE_64                 112
+#define bci_OP_U_GT_64                 113
+#define bci_OP_U_LT_64                 114
+#define bci_OP_U_LE_64                 115
+#define bci_OP_S_GE_64                 116
+#define bci_OP_S_GT_64                 117
+#define bci_OP_S_LT_64                 118
+#define bci_OP_S_LE_64                 119
+
+
+#define bci_OP_ADD_32                  130
+#define bci_OP_SUB_32                  131
+#define bci_OP_AND_32                  132
+#define bci_OP_XOR_32                  133
+#define bci_OP_NOT_32                  134
+#define bci_OP_NEG_32                  135
+#define bci_OP_MUL_32                  136
+#define bci_OP_SHL_32                  137
+#define bci_OP_ASR_32                  138
+#define bci_OP_LSR_32                  139
+#define bci_OP_OR_32                   140
+
+#define bci_OP_NEQ_32                  150
+#define bci_OP_EQ_32                   151
+#define bci_OP_U_GE_32                 152
+#define bci_OP_U_GT_32                 153
+#define bci_OP_U_LT_32                 154
+#define bci_OP_U_LE_32                 155
+#define bci_OP_S_GE_32                 156
+#define bci_OP_S_GT_32                 157
+#define bci_OP_S_LT_32                 158
+#define bci_OP_S_LE_32                 159
+
+
+#define bci_OP_ADD_16                  170
+#define bci_OP_SUB_16                  171
+#define bci_OP_AND_16                  172
+#define bci_OP_XOR_16                  173
+#define bci_OP_NOT_16                  174
+#define bci_OP_NEG_16                  175
+#define bci_OP_MUL_16                  176
+#define bci_OP_SHL_16                  177
+#define bci_OP_ASR_16                  178
+#define bci_OP_LSR_16                  179
+#define bci_OP_OR_16                   180
+
+#define bci_OP_NEQ_16                  190
+#define bci_OP_EQ_16                   191
+#define bci_OP_U_GE_16                 192
+#define bci_OP_U_GT_16                 193
+#define bci_OP_U_LT_16                 194
+#define bci_OP_U_LE_16                 195
+#define bci_OP_S_GE_16                 196
+#define bci_OP_S_GT_16                 197
+#define bci_OP_S_LT_16                 198
+#define bci_OP_S_LE_16                 199
+
+
+#define bci_OP_ADD_08                  200
+#define bci_OP_SUB_08                  201
+#define bci_OP_AND_08                  202
+#define bci_OP_XOR_08                  203
+#define bci_OP_NOT_08                  204
+#define bci_OP_NEG_08                  205
+#define bci_OP_MUL_08                  206
+#define bci_OP_SHL_08                  207
+#define bci_OP_ASR_08                  208
+#define bci_OP_LSR_08                  209
+#define bci_OP_OR_08                   210
+
+#define bci_OP_NEQ_08                  220
+#define bci_OP_EQ_08                   221
+#define bci_OP_U_GE_08                 222
+#define bci_OP_U_GT_08                 223
+#define bci_OP_U_LT_08                 224
+#define bci_OP_U_LE_08                 225
+#define bci_OP_S_GE_08                 226
+#define bci_OP_S_GT_08                 227
+#define bci_OP_S_LT_08                 228
+#define bci_OP_S_LE_08                 229
 
 
 /* If you need to go past 255 then you will run into the flags */
@@ -144,12 +215,6 @@
 /* If you need to go below 0x0100 then you will run into the instructions */
 #define bci_FLAG_LARGE_ARGS 0x8000
 
-/* Width of primitiv operations if width-polymorphic. We use two bits to store
- * the width.
- * 0->Word8;1->Word16;2->Word32
- * Word64 operations always should take the OP with fixed width instead. */
-#define bci_FLAG_WIDTH      0x6000
-
 /* If a BCO definitely requires less than this many words of stack,
    don't include an explicit STKCHECK insn in it.  The interpreter
    will check for this many words of stack before running each BCO,



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6ed53c04bf881c20645fbd539bc130e3fcd9e6ff

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6ed53c04bf881c20645fbd539bc130e3fcd9e6ff
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/20250303/afa72219/attachment-0001.html>


More information about the ghc-commits mailing list