Skip to content

Commit 54fbf27

Browse files
committed
Use Rec_info.unknown instead of unit
1 parent 9816841 commit 54fbf27

File tree

7 files changed

+25
-15
lines changed

7 files changed

+25
-15
lines changed

.depend

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -6131,6 +6131,7 @@ middle_end/flambda/simplify/simplify.cmo : \
61316131
middle_end/flambda/lifting/reification.cmi \
61326132
middle_end/flambda/basic/reg_width_const.cmi \
61336133
middle_end/flambda/basic/recursive.cmi \
6134+
middle_end/flambda/compilenv_deps/rec_info.cmi \
61346135
utils/profile.cmi \
61356136
middle_end/flambda/basic/or_variable.cmi \
61366137
middle_end/flambda/types/basic/or_bottom.cmi \
@@ -6203,6 +6204,7 @@ middle_end/flambda/simplify/simplify.cmx : \
62036204
middle_end/flambda/lifting/reification.cmx \
62046205
middle_end/flambda/basic/reg_width_const.cmx \
62056206
middle_end/flambda/basic/recursive.cmx \
6207+
middle_end/flambda/compilenv_deps/rec_info.cmx \
62066208
utils/profile.cmx \
62076209
middle_end/flambda/basic/or_variable.cmx \
62086210
middle_end/flambda/types/basic/or_bottom.cmx \
@@ -6295,6 +6297,7 @@ middle_end/flambda/simplify/simplify_apply_expr.rec.cmo : \
62956297
middle_end/flambda/simplify/simplify_common.cmi \
62966298
middle_end/flambda/basic/simple.cmi \
62976299
middle_end/flambda/terms/set_of_closures.cmi \
6300+
middle_end/flambda/compilenv_deps/rec_info.cmi \
62986301
middle_end/flambda/types/basic/or_bottom.cmi \
62996302
middle_end/flambda/naming/name_mode.cmi \
63006303
utils/misc.cmi \
@@ -6327,6 +6330,7 @@ middle_end/flambda/simplify/simplify_apply_expr.rec.cmx : \
63276330
middle_end/flambda/simplify/simplify_common.cmx \
63286331
middle_end/flambda/basic/simple.cmx \
63296332
middle_end/flambda/terms/set_of_closures.cmx \
6333+
middle_end/flambda/compilenv_deps/rec_info.cmx \
63306334
middle_end/flambda/types/basic/or_bottom.cmx \
63316335
middle_end/flambda/naming/name_mode.cmx \
63326336
utils/misc.cmx \
@@ -6720,6 +6724,7 @@ middle_end/flambda/simplify/simplify_set_of_closures.rec.cmo : \
67206724
middle_end/flambda/basic/simple.cmi \
67216725
middle_end/flambda/terms/set_of_closures.cmi \
67226726
middle_end/flambda/basic/scope.cmi \
6727+
middle_end/flambda/compilenv_deps/rec_info.cmi \
67236728
utils/profile.cmi \
67246729
middle_end/flambda/naming/name_occurrences.cmi \
67256730
middle_end/flambda/naming/name_mode.cmi \
@@ -6759,6 +6764,7 @@ middle_end/flambda/simplify/simplify_set_of_closures.rec.cmx : \
67596764
middle_end/flambda/basic/simple.cmx \
67606765
middle_end/flambda/terms/set_of_closures.cmx \
67616766
middle_end/flambda/basic/scope.cmx \
6767+
middle_end/flambda/compilenv_deps/rec_info.cmx \
67626768
utils/profile.cmx \
67636769
middle_end/flambda/naming/name_occurrences.cmx \
67646770
middle_end/flambda/naming/name_mode.cmx \

middle_end/flambda/compilenv_deps/rec_info.ml

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -34,4 +34,6 @@ end)
3434

3535
let initial = ()
3636

37+
let unknown = ()
38+
3739
let is_initial () = true

middle_end/flambda/compilenv_deps/rec_info.mli

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -13,11 +13,13 @@
1313
(**************************************************************************)
1414

1515
[@@@ocaml.warning "+a-4-30-40-41-42"]
16-
type t = unit
16+
type t
1717

1818
include Identifiable.S with type t := t
1919

2020
val initial : t
2121

22+
val unknown : t
23+
2224
val is_initial : t -> bool
2325

middle_end/flambda/inlining/inlining_decision.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -218,7 +218,7 @@ end
218218
(* CR mshinwell: This parameter needs to be configurable *)
219219
let max_rec_depth = 1
220220

221-
let make_decision_for_call_site denv ~function_decl_rec_info:()
221+
let make_decision_for_call_site denv ~function_decl_rec_info:_
222222
~apply_inlining_state (inline : Inline_attribute.t)
223223
: Call_site_decision.t =
224224
if (not (DE.can_inline denv)) then

middle_end/flambda/simplify/simplify_apply_expr.rec.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -105,7 +105,7 @@ let simplify_direct_full_application dacc apply function_decl_opt
105105
let apply_inlining_state = Apply.inlining_state apply in
106106
let decision =
107107
Inlining_decision.make_decision_for_call_site (DA.denv dacc)
108-
~function_decl_rec_info:()
108+
~function_decl_rec_info:Rec_info.unknown
109109
~apply_inlining_state
110110
(Apply.inline apply)
111111
in

middle_end/flambda/simplify/simplify_set_of_closures.rec.ml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -153,7 +153,7 @@ end = struct
153153
~pass:Inlining_report.Before_simplify
154154
denv function_decl
155155
~code_id:new_code_id
156-
())
156+
Rec_info.unknown)
157157
(Function_declarations.funs function_decls)
158158
in
159159
Closure_id.Map.mapi (fun closure_id _function_decl ->
@@ -465,7 +465,7 @@ let simplify_function context ~used_closure_vars ~shareable_constants
465465
function_decl_type
466466
~pass:Inlining_report.After_simplify
467467
(DA.denv dacc_after_body) function_decl
468-
~params_and_body ()
468+
~params_and_body Rec_info.unknown
469469
in
470470
{ function_decl;
471471
new_code_id;

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

Lines changed: 10 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -52,10 +52,10 @@ module Inlinable = struct
5252
let is_tupled t = t.is_tupled
5353

5454
let apply_name_permutation
55-
({ code_id; dbg = _; rec_info = (); is_tupled = _; } as t) perm =
55+
({ code_id; dbg = _; rec_info = _; is_tupled = _; } as t) perm =
5656
let code_id' = Name_permutation.apply_code_id perm code_id in
5757
if code_id == code_id' then t
58-
else { t with code_id = code_id'; }
58+
else { t with code_id = code_id'; rec_info = Rec_info.unknown }
5959

6060
end
6161

@@ -108,15 +108,15 @@ let print ppf t =
108108
let free_names (t : t) =
109109
match t with
110110
| Bottom | Unknown -> Name_occurrences.empty
111-
| Ok (Inlinable { code_id; dbg = _; rec_info = (); is_tupled = _; })
111+
| Ok (Inlinable { code_id; dbg = _; rec_info = _; is_tupled = _; })
112112
| Ok (Non_inlinable { code_id; is_tupled = _; }) ->
113113
Name_occurrences.add_code_id Name_occurrences.empty code_id
114114
Name_mode.in_types
115115

116116
let all_ids_for_export (t : t) =
117117
match t with
118118
| Bottom | Unknown -> Ids_for_export.empty
119-
| Ok (Inlinable { code_id; dbg = _; rec_info = (); is_tupled = _; })
119+
| Ok (Inlinable { code_id; dbg = _; rec_info = _; is_tupled = _; })
120120
| Ok (Non_inlinable { code_id; is_tupled = _; }) ->
121121
Ids_for_export.add_code_id Ids_for_export.empty code_id
122122

@@ -178,13 +178,13 @@ let meet (env : Meet_env.t) (t1 : t) (t2 : t)
178178
| Ok (Inlinable {
179179
code_id = code_id1;
180180
dbg = dbg1;
181-
rec_info = ();
181+
rec_info = _;
182182
is_tupled = is_tupled1;
183183
}),
184184
Ok (Inlinable {
185185
code_id = code_id2;
186186
dbg = dbg2;
187-
rec_info = ();
187+
rec_info = _;
188188
is_tupled = is_tupled2;
189189
}) ->
190190
let typing_env = Meet_env.env env in
@@ -196,7 +196,7 @@ let meet (env : Meet_env.t) (t1 : t) (t2 : t)
196196
Ok (Ok (Inlinable {
197197
code_id;
198198
dbg = dbg1;
199-
rec_info = ();
199+
rec_info = Rec_info.unknown;
200200
is_tupled = is_tupled1;
201201
}),
202202
TEE.empty ())
@@ -249,13 +249,13 @@ let join (env : Join_env.t) (t1 : t) (t2 : t) : t =
249249
| Ok (Inlinable {
250250
code_id = code_id1;
251251
dbg = dbg1;
252-
rec_info = ();
252+
rec_info = _;
253253
is_tupled = is_tupled1;
254254
}),
255255
Ok (Inlinable {
256256
code_id = code_id2;
257257
dbg = dbg2;
258-
rec_info = ();
258+
rec_info = _;
259259
is_tupled = is_tupled2;
260260
}) ->
261261
let typing_env = Join_env.target_join_env env in
@@ -267,7 +267,7 @@ let join (env : Join_env.t) (t1 : t) (t2 : t) : t =
267267
Ok (Inlinable {
268268
code_id;
269269
dbg = dbg1;
270-
rec_info = ();
270+
rec_info = Rec_info.unknown;
271271
is_tupled = is_tupled1;
272272
})
273273
in

0 commit comments

Comments
 (0)