Skip to content

Commit 1883839

Browse files
authored
Always inline function declared with an [@inline] annotation (#422)
1 parent 8d02e85 commit 1883839

File tree

8 files changed

+83
-58
lines changed

8 files changed

+83
-58
lines changed

middle_end/flambda/inlining/inlining_decision.ml

Lines changed: 29 additions & 39 deletions
Original file line numberDiff line numberDiff line change
@@ -49,14 +49,19 @@ module Function_declaration_decision = struct
4949
large_function_size: Code_size.t;
5050
}
5151

52-
let can_inline t =
52+
type inlining_behaviour =
53+
| Cannot_be_inlined
54+
| Must_be_inlined
55+
| Could_possibly_be_inlined
56+
57+
let behaviour t =
5358
match t with
5459
| Never_inline_attribute
55-
| Function_body_too_large _ -> false
60+
| Function_body_too_large _ -> Cannot_be_inlined
5661
| Stub
5762
| Attribute_inline
58-
| Small_function _
59-
| Speculatively_inlinable _-> true
63+
| Small_function _ -> Must_be_inlined
64+
| Speculatively_inlinable _-> Could_possibly_be_inlined
6065

6166
let print fmt = function
6267
| Never_inline_attribute ->
@@ -125,7 +130,11 @@ module Function_declaration_decision = struct
125130
let report fmt t =
126131
Format.fprintf fmt "@[<v>The function %s be inlined at its use-sites@ \
127132
because @[<hov>%a@]@]"
128-
(if can_inline t then "can" else "cannot") report_reason t
133+
(match behaviour t with
134+
| Cannot_be_inlined -> "cannot"
135+
| Could_possibly_be_inlined -> "could"
136+
| Must_be_inlined -> "must")
137+
report_reason t
129138

130139
end
131140

@@ -189,15 +198,12 @@ module Call_site_decision = struct
189198
}
190199
| Attribute_always
191200
| Attribute_unroll of int
201+
| Definition_says_inline
192202
| Speculatively_inline of {
193203
cost_metrics: Cost_metrics.t;
194204
evaluated_to: float;
195205
threshold: float;
196206
}
197-
| Small_function of {
198-
size: Code_size.t;
199-
small_function_size: Code_size.t;
200-
}
201207

202208
let print ppf t =
203209
match t with
@@ -213,6 +219,8 @@ module Call_site_decision = struct
213219
Format.fprintf ppf "Never_inline_attribute"
214220
| Attribute_always ->
215221
Format.fprintf ppf "Attribute_unroll"
222+
| Definition_says_inline ->
223+
Format.fprintf ppf "Definition_says_inline"
216224
| Attribute_unroll unroll_to ->
217225
Format.fprintf ppf
218226
"@[<hov 1>(Attribute_unroll@ \
@@ -239,14 +247,6 @@ module Call_site_decision = struct
239247
Cost_metrics.print cost_metrics
240248
evaluated_to
241249
threshold
242-
| Small_function { size; small_function_size; } ->
243-
Format.fprintf ppf
244-
"@[<hov 1>(Small_function@ \
245-
@[<hov 1>(size@ %a)@]@ \
246-
@[<hov 1>(small_function_size@ %a)@]\
247-
)@]"
248-
Code_size.print size
249-
Code_size.print small_function_size
250250

251251
type can_inline =
252252
| Do_not_inline
@@ -261,8 +261,8 @@ module Call_site_decision = struct
261261
| Speculatively_not_inline _
262262
| Never_inline_attribute -> Do_not_inline
263263
| Attribute_unroll unroll_to -> Inline { unroll_to = Some unroll_to; }
264+
| Definition_says_inline
264265
| Speculatively_inline _
265-
| Small_function _
266266
| Attribute_always -> Inline { unroll_to = None; }
267267

268268
let report_reason fmt t =
@@ -281,6 +281,11 @@ module Call_site_decision = struct
281281
Format.fprintf fmt "the@ call@ has@ an@ [@@inline always]@ attribute"
282282
| Attribute_unroll n ->
283283
Format.fprintf fmt "the@ call@ has@ an@ [@@unroll %d]@ attribute" n
284+
| Definition_says_inline ->
285+
Format.fprintf fmt "this@ function@ was@ decided@ to@ be@ always@ \
286+
inlined@ at@ its@ definition@ site (annotated@ by@ \
287+
[@inlined always]@ or@ determined@ to@ be@ small@ \
288+
enough)"
284289
| Speculatively_not_inline { cost_metrics; evaluated_to; threshold } ->
285290
Format.fprintf fmt
286291
"the@ function@ was@ not@ inlined@ after@ speculation@ as@ \
@@ -297,13 +302,6 @@ module Call_site_decision = struct
297302
Cost_metrics.print cost_metrics
298303
evaluated_to
299304
threshold
300-
| Small_function { size; small_function_size; } ->
301-
Format.fprintf fmt
302-
"the@ function@ was@ classified@ as@ a@ small@ \
303-
function@ and@ was@ therefore@ inlined:@ \
304-
size=%a <= small function size=%a"
305-
Code_size.print size
306-
Code_size.print small_function_size
307305

308306
let report fmt t =
309307
Format.fprintf fmt
@@ -386,28 +384,20 @@ let speculative_inlining dacc ~apply ~function_decl ~simplify_expr
386384
let might_inline dacc ~apply ~function_decl ~simplify_expr ~return_arity
387385
: Call_site_decision.t =
388386
let denv = DA.denv dacc in
389-
let code_id = I.code_id function_decl in
390-
let code = DE.find_code denv code_id in
391-
let cost_metrics = Code.cost_metrics code in
392-
let args =
393-
Apply.inlining_arguments apply
394-
|> Inlining_arguments.meet (DA.denv dacc |> DE.inlining_arguments)
395-
in
396-
let size = Cost_metrics.size cost_metrics in
397-
let small_function_size =
398-
Inlining_arguments.small_function_size args |> Code_size.of_int
399-
in
400-
let is_a_small_function = Code_size.(<=) size small_function_size in
401387
let env_prohibits_inlining = not (DE.can_inline denv) in
402-
if is_a_small_function then
403-
Small_function { size; small_function_size }
388+
if I.must_be_inlined function_decl then
389+
Definition_says_inline
404390
else if env_prohibits_inlining then
405391
Environment_says_never_inline
406392
else
407393
let cost_metrics =
408394
speculative_inlining ~apply dacc ~simplify_expr ~return_arity
409395
~function_decl
410396
in
397+
let args =
398+
Apply.inlining_arguments apply
399+
|> Inlining_arguments.meet (DA.denv dacc |> DE.inlining_arguments)
400+
in
411401
let evaluated_to = Cost_metrics.evaluate ~args cost_metrics in
412402
let threshold = Inlining_arguments.threshold args in
413403
let is_under_inline_threshold =

middle_end/flambda/inlining/inlining_decision.mli

Lines changed: 7 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -38,7 +38,12 @@ module Function_declaration_decision : sig
3838

3939
val report : Format.formatter -> t -> unit
4040

41-
val can_inline : t -> bool
41+
type inlining_behaviour = private
42+
| Cannot_be_inlined
43+
| Must_be_inlined
44+
| Could_possibly_be_inlined
45+
46+
val behaviour : t -> inlining_behaviour
4247
end
4348

4449

@@ -70,15 +75,12 @@ module Call_site_decision : sig
7075
}
7176
| Attribute_always
7277
| Attribute_unroll of int
78+
| Definition_says_inline
7379
| Speculatively_inline of {
7480
cost_metrics: Cost_metrics.t;
7581
evaluated_to: float;
7682
threshold: float;
7783
}
78-
| Small_function of {
79-
size: Code_size.t;
80-
small_function_size: Code_size.t;
81-
}
8284

8385

8486
val print : Format.formatter -> t -> unit

middle_end/flambda/simplify/simplify_set_of_closures.ml

Lines changed: 12 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -36,16 +36,25 @@ let function_decl_type ~pass ~cost_metrics_source denv function_decl ?code_id
3636
Inlining_report.record_decision (
3737
At_function_declaration { code_id = Code_id.export code_id; pass; decision; })
3838
~dbg:(DE.add_inlined_debuginfo' denv (FD.dbg function_decl));
39-
if Inlining_decision.Function_declaration_decision.can_inline decision then
39+
match Inlining_decision.Function_declaration_decision.behaviour decision with
40+
| Cannot_be_inlined ->
41+
T.create_non_inlinable_function_declaration
42+
~code_id
43+
~is_tupled:(FD.is_tupled function_decl)
44+
| Must_be_inlined ->
4045
T.create_inlinable_function_declaration
4146
~code_id
4247
~dbg:(FD.dbg function_decl)
4348
~is_tupled:(FD.is_tupled function_decl)
49+
~must_be_inlined:true
4450
~rec_info
45-
else
46-
T.create_non_inlinable_function_declaration
51+
| Could_possibly_be_inlined ->
52+
T.create_inlinable_function_declaration
4753
~code_id
54+
~dbg:(FD.dbg function_decl)
4855
~is_tupled:(FD.is_tupled function_decl)
56+
~must_be_inlined:false
57+
~rec_info
4958

5059
module Context_for_multiple_sets_of_closures : sig
5160
(* This module deals with a sub-problem of the problem of simplifying multiple

middle_end/flambda/types/flambda_type.mli

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -245,6 +245,7 @@ module Function_declaration_type : sig
245245
val dbg : t -> Debuginfo.t
246246
val rec_info : t -> Rec_info.t
247247
val is_tupled : t -> bool
248+
val must_be_inlined : t -> bool
248249
end
249250

250251
module Non_inlinable : sig
@@ -414,6 +415,7 @@ val create_inlinable_function_declaration
414415
-> dbg:Debuginfo.t
415416
-> rec_info:Rec_info.t
416417
-> is_tupled:bool
418+
-> must_be_inlined:bool
417419
-> Function_declaration_type.t
418420

419421
(** Create a description of a function declaration whose code is unknown.

middle_end/flambda/types/structures/function_declaration_type.rec.ml

Lines changed: 27 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -25,35 +25,41 @@ module Inlinable = struct
2525
dbg : Debuginfo.t;
2626
rec_info : Rec_info.t;
2727
is_tupled : bool;
28+
must_be_inlined : bool;
2829
}
2930

30-
let print ppf { code_id; dbg; rec_info; is_tupled; } =
31+
let print ppf { code_id; dbg; rec_info; is_tupled; must_be_inlined } =
3132
Format.fprintf ppf
3233
"@[<hov 1>(Inlinable@ \
3334
@[<hov 1>(code_id@ %a)@]@ \
34-
@[<hov 1>(dbg@ %a)@] \
35-
@[<hov 1>(rec_info@ %a)@]\
36-
@[<hov 1><is_tupled@ %b)@]\
35+
@[<hov 1>(dbg@ %a)@]@ \
36+
@[<hov 1>(rec_info@ %a)@]@ \
37+
@[<hov 1><is_tupled@ %b)@]@ \
38+
@[<hov 1><must_be_inlined@ %b)@]\
3739
)@]"
3840
Code_id.print code_id
3941
Debuginfo.print_compact dbg
4042
Rec_info.print rec_info
4143
is_tupled
44+
must_be_inlined
4245

43-
let create ~code_id ~dbg ~rec_info ~is_tupled =
46+
let create ~code_id ~dbg ~rec_info ~is_tupled ~must_be_inlined =
4447
{ code_id;
4548
dbg;
4649
rec_info;
4750
is_tupled;
51+
must_be_inlined;
4852
}
4953

5054
let code_id t = t.code_id
5155
let dbg t = t.dbg
5256
let rec_info t = t.rec_info
5357
let is_tupled t = t.is_tupled
58+
let must_be_inlined t = t.must_be_inlined
5459

5560
let apply_renaming
56-
({ code_id; dbg = _; rec_info = _; is_tupled = _; } as t) renaming =
61+
({ code_id; dbg = _; rec_info = _; is_tupled = _;
62+
must_be_inlined = _ } as t) renaming =
5763
let code_id' = Renaming.apply_code_id renaming code_id in
5864
if code_id == code_id' then t
5965
else { t with code_id = code_id'; }
@@ -109,15 +115,17 @@ let print ppf t =
109115
let free_names (t : t) =
110116
match t with
111117
| Bottom | Unknown -> Name_occurrences.empty
112-
| Ok (Inlinable { code_id; dbg = _; rec_info = _; is_tupled = _; })
118+
| Ok (Inlinable { code_id; dbg = _; rec_info = _; is_tupled = _;
119+
must_be_inlined = _; })
113120
| Ok (Non_inlinable { code_id; is_tupled = _; }) ->
114121
Name_occurrences.add_code_id Name_occurrences.empty code_id
115122
Name_mode.in_types
116123

117124
let all_ids_for_export (t : t) =
118125
match t with
119126
| Bottom | Unknown -> Ids_for_export.empty
120-
| Ok (Inlinable { code_id; dbg = _; rec_info = _; is_tupled = _; })
127+
| Ok (Inlinable { code_id; dbg = _; rec_info = _; is_tupled = _;
128+
must_be_inlined = _; })
121129
| Ok (Non_inlinable { code_id; is_tupled = _; }) ->
122130
Ids_for_export.add_code_id Ids_for_export.empty code_id
123131

@@ -171,24 +179,28 @@ let meet (env : Meet_env.t) (t1 : t) (t2 : t)
171179
dbg = dbg1;
172180
rec_info = _rec_info1;
173181
is_tupled = is_tupled1;
182+
must_be_inlined = must_be_inlined1;
174183
}),
175184
Ok (Inlinable {
176185
code_id = code_id2;
177186
dbg = dbg2;
178187
rec_info = _rec_info2;
179188
is_tupled = is_tupled2;
189+
must_be_inlined = must_be_inlined2;
180190
}) ->
181191
let typing_env = Meet_env.env env in
182192
let target_code_age_rel = TE.code_age_relation typing_env in
183193
let resolver = TE.code_age_relation_resolver typing_env in
184194
let check_other_things_and_return code_id : (t * TEE.t) Or_bottom.t =
185195
assert (Int.equal (Debuginfo.compare dbg1 dbg2) 0);
186196
assert (Bool.equal is_tupled1 is_tupled2);
197+
assert (Bool.equal must_be_inlined1 must_be_inlined2);
187198
Ok (Ok (Inlinable {
188199
code_id;
189200
dbg = dbg1;
190201
rec_info = _rec_info1;
191202
is_tupled = is_tupled1;
203+
must_be_inlined = must_be_inlined1;
192204
}),
193205
TEE.empty ())
194206
in
@@ -243,24 +255,28 @@ let join (env : Join_env.t) (t1 : t) (t2 : t) : t =
243255
dbg = dbg1;
244256
rec_info = _rec_info1;
245257
is_tupled = is_tupled1;
258+
must_be_inlined = must_be_inlined1;
246259
}),
247260
Ok (Inlinable {
248261
code_id = code_id2;
249262
dbg = dbg2;
250263
rec_info = _rec_info2;
251264
is_tupled = is_tupled2;
265+
must_be_inlined = must_be_inlined2;
252266
}) ->
253267
let typing_env = Join_env.target_join_env env in
254268
let target_code_age_rel = TE.code_age_relation typing_env in
255269
let resolver = TE.code_age_relation_resolver typing_env in
256270
let check_other_things_and_return code_id : t =
257271
assert (Int.equal (Debuginfo.compare dbg1 dbg2) 0);
258272
assert (Bool.equal is_tupled1 is_tupled2);
273+
assert (Bool.equal must_be_inlined1 must_be_inlined2);
259274
Ok (Inlinable {
260275
code_id;
261276
dbg = dbg1;
262277
rec_info = _rec_info1;
263278
is_tupled = is_tupled1;
279+
must_be_inlined = must_be_inlined1;
264280
})
265281
in
266282
(* CR mshinwell: What about [rec_info]? *)
@@ -280,12 +296,14 @@ let join (env : Join_env.t) (t1 : t) (t2 : t) : t =
280296

281297
let apply_rec_info (t : t) rec_info : t Or_bottom.t =
282298
match t with
283-
| Ok (Inlinable { code_id; dbg; rec_info = rec_info'; is_tupled; }) ->
299+
| Ok (Inlinable { code_id; dbg; rec_info = rec_info'; is_tupled;
300+
must_be_inlined }) ->
284301
let rec_info = Rec_info.merge rec_info' ~newer:rec_info in
285302
Ok (Ok (Inlinable { code_id;
286303
dbg;
287304
rec_info;
288305
is_tupled;
306+
must_be_inlined;
289307
}))
290308
| Ok (Non_inlinable { code_id = _; is_tupled = _; }) -> Ok t
291309
| Unknown | Bottom -> Ok t

middle_end/flambda/types/structures/function_declaration_type.rec.mli

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -24,12 +24,14 @@ module Inlinable : sig
2424
-> dbg:Debuginfo.t
2525
-> rec_info:Rec_info.t
2626
-> is_tupled:bool
27+
-> must_be_inlined:bool
2728
-> t
2829

2930
val code_id : t -> Code_id.t
3031
val dbg : t -> Debuginfo.t
3132
val rec_info : t -> Rec_info.t
3233
val is_tupled : t -> bool
34+
val must_be_inlined : t -> bool
3335
end
3436

3537
module Non_inlinable : sig

middle_end/flambda/types/type_grammar.rec.ml

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -605,9 +605,10 @@ let any_boxed_int64 () = box_int64 (any_naked_int64 ())
605605
let any_boxed_nativeint () = box_nativeint (any_naked_nativeint ())
606606

607607
let create_inlinable_function_declaration ~code_id ~dbg ~rec_info ~is_tupled
608-
: Function_declaration_type.t =
608+
~must_be_inlined : Function_declaration_type.t =
609609
Ok (Inlinable (
610-
Function_declaration_type.Inlinable.create ~code_id ~dbg ~rec_info ~is_tupled))
610+
Function_declaration_type.Inlinable.create ~code_id ~dbg ~rec_info
611+
~is_tupled ~must_be_inlined))
611612

612613
let create_non_inlinable_function_declaration ~code_id ~is_tupled
613614
: Function_declaration_type.t =

0 commit comments

Comments
 (0)