Generate static closure for datacon with unpacked sums
Summary
GHC doesn't generate static closures when some field is an unpacked sum.
Steps to reproduce
Consider the following example:
module Test where
data A = A | B | C
data D = D !Bool !A
foo = D True B
Compile it with ghc-9.10 -O2 Test2.hs -fforce-recomp -ddump-cmm -dno-typeable-binds
and get:
...
[section ""data" . Test.foo_closure" {
Test.foo_closure:
const Test.D_con_info;
const GHC.Types.True_closure+2;
const Test.B_closure+2;
const 3; // STATIC_LINK field
}]
...
foo
is a statically allocated closure.
Now change the code to UNPACK A
:
module Test where
data A = A | B | C
data D = D !Bool {-# UNPACK #-} !A
foo = D True B
Now foo
isn't a statically allocated closure but:
[Test.foo_entry() { // [R1]
{ info_tbls: [(cBv,
label: Test.foo_info
rep: HeapRep static { Thunk }
srt: Nothing)]
stack_info: arg_space: 8
}
{offset
cBv: // global
_r1::P64 = R1;
if ((Sp + -16) < SpLim) (likely: False) goto cBw; else goto cBx;
cBx: // global
Hp = Hp + 24;
if (Hp > HpLim) (likely: False) goto cBz; else goto cBy;
cBz: // global
HpAlloc = 24;
goto cBw;
cBw: // global
R1 = _r1::P64;
call (stg_gc_enter_1)(R1) args: 8, res: 0, upd: 8;
cBy: // global
(_cBr::I64) = call "ccall" arg hints: [PtrHint,
PtrHint] result hints: [PtrHint] newCAF(BaseReg, _r1::P64);
if (_cBr::I64 == 0) goto cBt; else goto cBs;
cBt: // global
call (I64![_r1::P64])() args: 8, res: 0, upd: 8;
cBs: // global
I64[Sp - 16] = stg_bh_upd_frame_info;
I64[Sp - 8] = _cBr::I64;
I64[Hp - 16] = Test.D_con_info;
P64[Hp - 8] = GHC.Types.True_closure+2;
I64[Hp] = 2;
R1 = Hp - 15;
Sp = Sp - 16;
call (P64[Sp])(R1) args: 24, res: 0, upd: 24;
}
},
section ""data" . Test.foo_closure" {
Test.foo_closure:
const Test.foo_info;
const 0;
const 0;
const 0;
}]
Expected behavior
I would expect a static closure like this:
[section ""data" . Test.foo_closure" {
Test.foo_closure:
const Test.D_con_info;
const GHC.Types.True_closure+2;
const 2; // Tag of B
const 3; // STATIC_LINK field
}]