Skip to content
Snippets Groups Projects
Commit 1e695750 authored by Cheng Shao's avatar Cheng Shao Committed by Zubin
Browse files

rts: enable wasm32 register mapping

The wasm backend didn't properly make use of all Cmm global registers
due to #24347. Now that it is fixed, this patch re-enables full
register mapping for wasm32, and we can now generate smaller & faster
wasm modules that doesn't always spill arguments onto the stack. Fixes #22460 #24152.

(cherry picked from commit 0cda2b8b)
(cherry picked from commit f1f5068b398b1effb837add38ecc5303dc9a381f)
parent 87790f48
No related branches found
No related tags found
No related merge requests found
......@@ -4,7 +4,6 @@ module GHC.Platform.Wasm32 where
import GHC.Prelude
-- TODO
#define MACHREGS_NO_REGS 1
-- #define MACHREGS_wasm32 1
#define MACHREGS_NO_REGS 0
#define MACHREGS_wasm32 1
#include "CodeGen.Platform.h"
......@@ -43,6 +43,8 @@ import CLOSURE stg_AP_STACK_info;
import CLOSURE stg_PAP_info;
import CLOSURE stg_WHITEHOLE_info;
import CLOSURE stg_ap_0_ret_str;
import CLOSURE stg_ap_stack_entries;
import CLOSURE stg_apply_interp_info;
import CLOSURE stg_restore_cccs_eval_info;
#endif
......
......@@ -26,6 +26,8 @@ import CLOSURE large_alloc_lim;
import CLOSURE stg_MSG_THROWTO_info;
import CLOSURE stg_MVAR_DIRTY_info;
import CLOSURE stg_WHITEHOLE_info;
import CLOSURE stg_ap_stack_entries;
import CLOSURE stg_apply_interp_info;
import CLOSURE stg_arg_bitmaps;
import CLOSURE stg_block_putmvar_info;
import CLOSURE stg_block_readmvar_info;
......@@ -40,6 +42,7 @@ import CLOSURE stg_ret_f_info;
import CLOSURE stg_ret_l_info;
import CLOSURE stg_ret_n_info;
import CLOSURE stg_ret_p_info;
import CLOSURE stg_stack_save_entries;
#endif
/* Stack/Heap Check Failure
......
......@@ -599,6 +599,8 @@ the stack. See Note [Overlapping global registers] for implications.
#elif defined(MACHREGS_wasm32)
#define REG_Base 0
#define REG_R1 1
#define REG_R2 2
#define REG_R3 3
......@@ -630,7 +632,6 @@ the stack. See Note [Overlapping global registers] for implications.
#define REG_SpLim 25
#define REG_Hp 26
#define REG_HpLim 27
#define REG_CCCS 28
/* -----------------------------------------------------------------------------
The loongarch64 register mapping
......
......@@ -75,8 +75,7 @@
#endif
#if defined(wasm32_HOST_ARCH)
#undef MACHREGS_NO_REGS
#define MACHREGS_NO_REGS 1
#define MACHREGS_wasm32 1
#endif
#if defined(loongarch64_HOST_ARCH)
......
......@@ -4,7 +4,6 @@ setTestOpts(
test('selfloop', [cmm_src], compile, ['-no-hs-main'])
test('cmm_sink_sp', [ only_ways(['optasm']),
when(arch('wasm32'), fragile(24152)),
grep_errmsg(r'(\[Sp.*\]).*(=).*(\[.*R1.*\]).*;',[1,2,3]),
cmm_src], compile, ['-no-hs-main -ddump-cmm -dsuppress-uniques -O'])
......
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