GHC is reluctant to unbox Int with -O when returned in a sum field
Summary
Example 1
I have some code like
{-# LANGUAGE BangPatterns #-}
module M where
foo :: [Int] -> Maybe Int
foo = go 1 0
where
go :: Int -> Int -> [Int] -> Maybe Int
go !i !n [] = Just n
go i n (x:xs)
| i < 10 = go (i+1) (n+x) xs
| otherwise = Nothing
If I compile it with -O on GHC 9.4.8 or 9.6.3, n
is not unboxed even with the bang.
Core:
-- RHS size: {terms: 31, types: 16, coercions: 0, joins: 0/0}
M.$wgo [InlPrag=[2], Occ=LoopBreaker]
:: GHC.Prim.Int# -> Int -> [Int] -> Maybe Int
[GblId[StrictWorker([~, !, !])],
Arity=3,
Str=<L><1L><1L>,
Unf=OtherCon []]
M.$wgo
= \ (ww_sNC :: GHC.Prim.Int#) (n_sNE :: Int) (ds_sNF :: [Int]) ->
case n_sNE of n1_X1 { GHC.Types.I# ipv_sN7 ->
case ds_sNF of {
[] -> GHC.Maybe.Just @Int n1_X1;
: ipv1_sN9 ipv2_sNa ->
case GHC.Prim.<# ww_sNC 10# of {
__DEFAULT -> GHC.Maybe.Nothing @Int;
1# ->
case ipv1_sN9 of { GHC.Types.I# y_aNl ->
M.$wgo
(GHC.Prim.+# ww_sNC 1#)
(GHC.Types.I# (GHC.Prim.+# ipv_sN7 y_aNl))
ipv2_sNa
}
}
}
}
Example 2
module M where
foo :: [Int] -> Maybe Int
foo [] = Nothing
foo xs = Just $! sum xs
The accumulator in sum
remains boxed.
This is not the case with GHC 9.2.8. Using -O2 with 9.4.8 and 9.6.3 also unboxes it.
Is this intended behavior?
Steps to reproduce
Compile the snippet above.
Expected behavior
n
is unboxed.
Environment
- GHC version used: 9.4.8, 9.6.3
Edited by meooow