SpecConstr passes unused parameters
Consider
f x y = case x of
a : as -> f as y
[] -> True
boo p ps = f (p:ps) 'v'
Notice that y
is unused, and so is a
in the pattern match.
Compile with -O2, and we get (as the output of SpecConstr):
Rec {
-- RHS size: {terms: 5, types: 7, coercions: 0, joins: 0/0}
Foo.f_$s$wf [Occ=LoopBreaker] :: forall a. a -> [a] -> Bool
[GblId, Arity=2, Caf=NoCafRefs, Str=<L,A><S,1*U>, Unf=OtherCon []]
Foo.f_$s$wf
= \ (@ a_aud) _ [Occ=Dead] (sc1_sv3 :: [a_aud]) ->
Foo.$wf @ a_aud @ Char sc1_sv3
-- RHS size: {terms: 10, types: 13, coercions: 0, joins: 0/0}
Foo.$wf [InlPrag=NOUSERINLINE[2], Occ=LoopBreaker]
:: forall a t. [a] -> Bool
[GblId, Arity=1, Caf=NoCafRefs, Str=<S,1*U>, Unf=OtherCon []]
Foo.$wf
= \ (@ a_suO) (@ t_suP) (w_suQ :: [a_suO]) ->
case w_suQ of {
[] -> GHC.Types.True;
: a1_agf as_agg -> Foo.$wf @ a_suO @ t_suP as_agg
}
end Rec }
-- RHS size: {terms: 6, types: 9, coercions: 0, joins: 0/0}
f [InlPrag=NOUSERINLINE[2]] :: forall a t. [a] -> t -> Bool
[GblId,
Arity=2,
Caf=NoCafRefs,
Str=<S,1*U><L,A>,
Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True,
Guidance=ALWAYS_IF(arity=2,unsat_ok=True,boring_ok=True)
Tmpl= \ (@ a_suO)
(@ t_suP)
(w_suQ [Occ=Once] :: [a_suO])
_ [Occ=Dead] ->
Foo.$wf @ a_suO @ t_suP w_suQ}]
f = \ (@ a_suO) (@ t_suP) (w_suQ :: [a_suO]) _ [Occ=Dead] ->
Foo.$wf @ a_suO @ t_suP w_suQ
-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
Foo.boo1 :: Char
[GblId,
Caf=NoCafRefs,
Str=m,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
Foo.boo1 = GHC.Types.C# 'v'#
-- RHS size: {terms: 6, types: 6, coercions: 0, joins: 0/0}
boo :: forall a. a -> [a] -> Bool
[GblId,
Arity=2,
Caf=NoCafRefs,
Str=<L,A><S,1*U>,
Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True,
Guidance=ALWAYS_IF(arity=2,unsat_ok=True,boring_ok=False)
Tmpl= \ (@ a_aud)
(p_atA [Occ=Once] :: a_aud)
(ps_atB [Occ=Once] :: [a_aud]) ->
f @ a_aud @ Char (GHC.Types.: @ a_aud p_atA ps_atB) Foo.boo1}]
boo
= \ (@ a_aud) (p_atA :: a_aud) (ps_atB :: [a_aud]) ->
Foo.f_$s$wf @ a_aud p_atA ps_atB
------ Local rules for imported ids --------
"SC:$wf0" [2]
forall (@ a_aud) (sc_sv2 :: a_aud) (sc1_sv3 :: [a_aud]).
Foo.$wf @ a_aud @ Char (GHC.Types.: @ a_aud sc_sv2 sc1_sv3)
= Foo.f_$s$wf @ a_aud sc_sv2 sc1_sv3
The worker $wf
drops y
, as it should, as a result of demand analysis. But a
is unused too, and lo! sc_sv2
is passed by the RULE to f_$s$wf
, which indeed does not use it.
This is fixed by -flate-dmd-anal
, but there is a missed opportunity. SpecConstr actually gathers NoOcc
info, and could exploit it to pass fewer arguments to the specialised function.