@@ -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
130139end
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
386384let 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 =
0 commit comments