Bad fusion for `enumFrom*` on 32-bit targets
Consider the following example:
module Test where
import Data.Word
foo :: Word64
foo = sum [0..123456]
On x86-64 we get the following Core:
Rec {
$wgo3
= \ x_s1f6 ww_s1f9 ->
case x_s1f6 of wild_X2 {
__DEFAULT ->
$wgo3
(plusWord# wild_X2 1##)
(plusWord64# ww_s1f9 (wordToWord64# wild_X2));
123456## -> plusWord64# ww_s1f9 123456#Word64
}
end Rec }
foo
= case $wgo3 0## 0#Word64 of ww_s1fe { __DEFAULT -> W64# ww_s1fe }
But with the JS target (32-bit) we get:
lvl_r1im = IS 1#
Rec {
foo_$s$wgo3
= \ sc_s1ie ww_s1i2 ->
case ># sc_s1ie 123456# of {
__DEFAULT ->
$wgo3_r1in
(integerAdd (IS sc_s1ie) lvl_r1im)
(plusWord64# ww_s1i2 (int64ToWord64# (intToInt64# sc_s1ie)));
1# -> ww_s1i2
}
$wgo3_r1in
= \ x_s1hZ ww_s1i2 ->
join {
$j_s1hU
= case integerToWord64# x_s1hZ of ds_a1a8 { __DEFAULT ->
$wgo3_r1in
(integerAdd x_s1hZ lvl_r1im) (plusWord64# ww_s1i2 ds_a1a8)
} } in
case x_s1hZ of {
IS x1_a1eQ ->
case ># x1_a1eQ 123456# of {
__DEFAULT -> jump $j_s1hU;
1# -> ww_s1i2
};
IP x1_a1eV -> ww_s1i2;
IN x1_a1hI -> jump $j_s1hU
}
end Rec }
foo
= case foo_$s$wgo3 0# 0#Word64 of ww_s1i7 { __DEFAULT ->
W64# ww_s1i7
}
Which is worse because it uses Integer
(boxed) instead of Word64#
.
Probably related to this code:
-- in base:GHC.Word
instance Enum Word64 where
...
#if WORD_SIZE_IN_BITS < 64
...
#else
-- use Word's Enum as it has better support for fusion. We can't use
-- `boundedEnumFrom` and `boundedEnumFromThen` -- which use Int's Enum
-- instance -- because Word64 isn't compatible with Int/Int64's domain.
--
...
#endif
We have the same issue for Int64
with similar CPP in base:GHC.Int
.