Missing constant folding in STG
Summary
This is a followup of #25166 (closed): we don't generate static closures in some cases. This was found while investigating #25649
Steps to reproduce
Compile the following code with -O2 -ddump-cmm
:
module M where
import Data.Word
data Alice = Alice1 {-# UNPACK #-} !Word32 | Alice2 {-# UNPACK #-} !Bob
data Bob = Bob1 | Bob2
foo = Alice1 10
bar = Alice2 Bob2
data Carlos = Carlos {-# UNPACK #-} !Alice
baz_foo = Carlos foo
baz_bar = Carlos bar
In the Cmm output, we see that baz_bar
and baz_foo
are dynamically allocated:
[M.baz_bar_entry() { // [R1]
...
cLw: // global
I64[Sp - 16] = stg_bh_upd_frame_info;
I64[Sp - 8] = _cLv::I64;
I64[Hp - 16] = M.Carlos_con_info;
I64[Hp - 8] = 2;
I64[Hp] = 2;
R1 = Hp - 15;
Sp = Sp - 16;
call (P64[Sp])(R1) args: 24, res: 0, upd: 24;
}
},
section ""data" . M.baz_bar_closure" {
M.baz_bar_closure:
const M.baz_bar_info;
const 0;
const 0;
const 0;
}]
Expected behavior
I would expect them to be statically allocated. I.e. for baz_bar
above:
section ""data" . M.baz_bar_closure" {
M.baz_bar_closure:
const M.Carlos_con_info;
const 2;
const 2;
}]
Analysis
If we -ddump-stg-final
, we can see that these closures are dynamically allocated because constant folding isn't performed in STG:
M.baz_foo :: M.Carlos
[GblId, Unf=OtherCon []] =
{} \u []
case word32ToWord# [10#Word32] of cst_sum_gJU {
__DEFAULT -> M.Carlos [1# cst_sum_gJU];
};
M.baz_bar :: M.Carlos
[GblId, Unf=OtherCon []] =
{} \u []
case int2Word# [2#] of cst_sum_gJZ {
__DEFAULT -> M.Carlos [2# cst_sum_gJZ];
};
We should improve the STG optimizer to perform them.
Environment
- GHC version used:
Optional:
- Operating System:
- System Architecture: