forked from ocaml/ocaml
-
Notifications
You must be signed in to change notification settings - Fork 0
/
inline_and_simplify.ml
executable file
·1672 lines (1613 loc) · 69.2 KB
/
inline_and_simplify.ml
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
454
455
456
457
458
459
460
461
462
463
464
465
466
467
468
469
470
471
472
473
474
475
476
477
478
479
480
481
482
483
484
485
486
487
488
489
490
491
492
493
494
495
496
497
498
499
500
501
502
503
504
505
506
507
508
509
510
511
512
513
514
515
516
517
518
519
520
521
522
523
524
525
526
527
528
529
530
531
532
533
534
535
536
537
538
539
540
541
542
543
544
545
546
547
548
549
550
551
552
553
554
555
556
557
558
559
560
561
562
563
564
565
566
567
568
569
570
571
572
573
574
575
576
577
578
579
580
581
582
583
584
585
586
587
588
589
590
591
592
593
594
595
596
597
598
599
600
601
602
603
604
605
606
607
608
609
610
611
612
613
614
615
616
617
618
619
620
621
622
623
624
625
626
627
628
629
630
631
632
633
634
635
636
637
638
639
640
641
642
643
644
645
646
647
648
649
650
651
652
653
654
655
656
657
658
659
660
661
662
663
664
665
666
667
668
669
670
671
672
673
674
675
676
677
678
679
680
681
682
683
684
685
686
687
688
689
690
691
692
693
694
695
696
697
698
699
700
701
702
703
704
705
706
707
708
709
710
711
712
713
714
715
716
717
718
719
720
721
722
723
724
725
726
727
728
729
730
731
732
733
734
735
736
737
738
739
740
741
742
743
744
745
746
747
748
749
750
751
752
753
754
755
756
757
758
759
760
761
762
763
764
765
766
767
768
769
770
771
772
773
774
775
776
777
778
779
780
781
782
783
784
785
786
787
788
789
790
791
792
793
794
795
796
797
798
799
800
801
802
803
804
805
806
807
808
809
810
811
812
813
814
815
816
817
818
819
820
821
822
823
824
825
826
827
828
829
830
831
832
833
834
835
836
837
838
839
840
841
842
843
844
845
846
847
848
849
850
851
852
853
854
855
856
857
858
859
860
861
862
863
864
865
866
867
868
869
870
871
872
873
874
875
876
877
878
879
880
881
882
883
884
885
886
887
888
889
890
891
892
893
894
895
896
897
898
899
900
901
902
903
904
905
906
907
908
909
910
911
912
913
914
915
916
917
918
919
920
921
922
923
924
925
926
927
928
929
930
931
932
933
934
935
936
937
938
939
940
941
942
943
944
945
946
947
948
949
950
951
952
953
954
955
956
957
958
959
960
961
962
963
964
965
966
967
968
969
970
971
972
973
974
975
976
977
978
979
980
981
982
983
984
985
986
987
988
989
990
991
992
993
994
995
996
997
998
999
1000
(**************************************************************************)
(* *)
(* OCaml *)
(* *)
(* Pierre Chambart, OCamlPro *)
(* Mark Shinwell and Leo White, Jane Street Europe *)
(* *)
(* Copyright 2013--2016 OCamlPro SAS *)
(* Copyright 2014--2016 Jane Street Group LLC *)
(* *)
(* All rights reserved. This file is distributed under the terms of *)
(* the GNU Lesser General Public License version 2.1, with the *)
(* special exception on linking described in the file LICENSE. *)
(* *)
(**************************************************************************)
[@@@ocaml.warning "+a-4-9-30-40-41-42"]
module A = Simple_value_approx
module B = Inlining_cost.Benefit
module E = Inline_and_simplify_aux.Env
module R = Inline_and_simplify_aux.Result
(** Values of two types hold the information propagated during simplification:
- [E.t] "environments", top-down, almost always called "env";
- [R.t] "results", bottom-up approximately following the evaluation order,
almost always called "r". These results come along with rewritten
Flambda terms.
The environments map variables to approximations, which enable various
simplifications to be performed; for example, some variable may be known
to always hold a particular constant.
*)
let ret = R.set_approx
type simplify_variable_result =
| No_binding of Variable.t
| Binding of Variable.t * (Flambda.named Flambda.With_free_variables.t)
let simplify_free_variable_internal env original_var =
let var = Freshening.apply_variable (E.freshening env) original_var in
let original_var = var in
(* In the case where an approximation is useful, we introduce a [let]
to bind (e.g.) the constant or symbol replacing [var], unless this
would introduce a useless [let] as a consequence of [var] already being
in the current scope.
Even when the approximation is not useful, this simplification helps.
In particular, it squashes aliases of the form:
let var1 = var2 in ... var2 ...
by replacing [var2] in the body with [var1]. Simplification can then
eliminate the [let].
*)
let var =
let approx = E.find_exn env var in
match approx.var with
| Some var when E.mem env var -> var
| Some _ | None -> var
in
(* CR-soon mshinwell: Should we update [r] when we *add* code?
Aside from that, it looks like maybe we don't need [r] in this function,
because the approximation within it wouldn't be used by any of the
call sites. *)
match E.find_with_scope_exn env var with
| Current, approx -> No_binding var, approx (* avoid useless [let] *)
| Outer, approx ->
match A.simplify_var approx with
| None -> No_binding var, approx
| Some (named, approx) ->
let module W = Flambda.With_free_variables in
Binding (original_var, W.of_named named), approx
let simplify_free_variable env var ~f : Flambda.t * R.t =
match simplify_free_variable_internal env var with
| No_binding var, approx -> f env var approx
| Binding (var, named), approx ->
let module W = Flambda.With_free_variables in
let var = Variable.rename var in
let env = E.add env var approx in
let body, r = f env var approx in
(W.create_let_reusing_defining_expr var named body), r
let simplify_free_variables env vars ~f : Flambda.t * R.t =
let rec collect_bindings vars env bound_vars approxs : Flambda.t * R.t =
match vars with
| [] -> f env (List.rev bound_vars) (List.rev approxs)
| var::vars ->
match simplify_free_variable_internal env var with
| No_binding var, approx ->
collect_bindings vars env (var::bound_vars) (approx::approxs)
| Binding (var, named), approx ->
let module W = Flambda.With_free_variables in
let var = Variable.rename var in
let env = E.add env var approx in
let body, r =
collect_bindings vars env (var::bound_vars) (approx::approxs)
in
(W.create_let_reusing_defining_expr var named body), r
in
collect_bindings vars env [] []
let simplify_free_variables_named env vars ~f : Flambda.named * R.t =
let rec collect_bindings vars env bound_vars approxs
: Flambda.maybe_named * R.t =
match vars with
| [] ->
let named, r = f env (List.rev bound_vars) (List.rev approxs) in
Is_named named, r
| var::vars ->
match simplify_free_variable_internal env var with
| No_binding var, approx ->
collect_bindings vars env (var::bound_vars) (approx::approxs)
| Binding (var, named), approx ->
let module W = Flambda.With_free_variables in
let var = Variable.rename var in
let env = E.add env var approx in
let body, r =
collect_bindings vars env (var::bound_vars) (approx::approxs)
in
let body =
match body with
| Is_named body -> Flambda_utils.name_expr body ~name:"simplify_fv"
| Is_expr body -> body
in
Is_expr (W.create_let_reusing_defining_expr var named body), r
in
let named_or_expr, r = collect_bindings vars env [] [] in
match named_or_expr with
| Is_named named -> named, r
| Is_expr expr -> Expr expr, r
(* CR-soon mshinwell: tidy this up *)
let simplify_free_variable_named env var ~f : Flambda.named * R.t =
simplify_free_variables_named env [var] ~f:(fun env vars vars_approxs ->
match vars, vars_approxs with
| [var], [approx] -> f env var approx
| _ -> assert false)
let simplify_named_using_approx r lam approx =
let lam, _summary, approx = A.simplify_named approx lam in
lam, R.set_approx r approx
let simplify_using_approx_and_env env r original_lam approx =
let lam, summary, approx =
A.simplify_using_env approx ~is_present_in_env:(E.mem env) original_lam
in
let r =
let r = ret r approx in
match summary with
(* CR-soon mshinwell: Why is [r] not updated with the cost of adding the
new code?
mshinwell: similar to CR above *)
| Replaced_term -> R.map_benefit r (B.remove_code original_lam)
| Nothing_done -> r
in
lam, r
let simplify_named_using_approx_and_env env r original_named approx =
let named, summary, approx =
A.simplify_named_using_env approx ~is_present_in_env:(E.mem env)
original_named
in
let r =
let r = ret r approx in
match summary with
| Replaced_term -> R.map_benefit r (B.remove_code_named original_named)
| Nothing_done -> r
in
named, r
let simplify_const (const : Flambda.const) =
match const with
| Int i -> A.value_int i
| Char c -> A.value_char c
| Const_pointer i -> A.value_constptr i
let approx_for_allocated_const (const : Allocated_const.t) =
match const with
| String s -> A.value_string (String.length s) None
| Immutable_string s -> A.value_string (String.length s) (Some s)
| Int32 i -> A.value_boxed_int Int32 i
| Int64 i -> A.value_boxed_int Int64 i
| Nativeint i -> A.value_boxed_int Nativeint i
| Float f -> A.value_float f
| Float_array a -> A.value_mutable_float_array ~size:(List.length a)
| Immutable_float_array a ->
A.value_immutable_float_array
(Array.map A.value_float (Array.of_list a))
type filtered_switch_branches =
| Must_be_taken of Flambda.t
| Can_be_taken of (int * Flambda.t) list
(* Determine whether a given closure ID corresponds directly to a variable
(bound to a closure) in the given environment. This happens when the body
of a [let rec]-bound function refers to another in the same set of closures.
If we succeed in this process, we can change [Project_closure]
expressions into [Var] expressions, thus sharing closure projections. *)
let reference_recursive_function_directly env closure_id =
let closure_id = Closure_id.unwrap closure_id in
match E.find_opt env closure_id with
| None -> None
| Some approx -> Some (Flambda.Expr (Var closure_id), approx)
(* Simplify an expression that takes a set of closures and projects an
individual closure from it. *)
let simplify_project_closure env r ~(project_closure : Flambda.project_closure)
: Flambda.named * R.t =
simplify_free_variable_named env project_closure.set_of_closures
~f:(fun _env set_of_closures set_of_closures_approx ->
match A.check_approx_for_set_of_closures set_of_closures_approx with
| Wrong ->
Misc.fatal_errorf "Wrong approximation when projecting closure: %a"
Flambda.print_project_closure project_closure
| Unresolved value ->
(* A set of closures coming from another compilation unit, whose .cmx is
missing; as such, we cannot have rewritten the function and don't
need to do any freshening. *)
Project_closure {
set_of_closures;
closure_id = project_closure.closure_id;
}, ret r (A.value_unresolved value)
| Unknown ->
(* CR-soon mshinwell: see CR comment in e.g. simple_value_approx.ml
[check_approx_for_closure_allowing_unresolved] *)
Project_closure {
set_of_closures;
closure_id = project_closure.closure_id;
}, ret r (A.value_unknown Other)
| Unknown_because_of_unresolved_value value ->
Project_closure {
set_of_closures;
closure_id = project_closure.closure_id;
}, ret r (A.value_unknown (Unresolved_value value))
| Ok (set_of_closures_var, value_set_of_closures) ->
let closure_id =
A.freshen_and_check_closure_id value_set_of_closures
project_closure.closure_id
in
let projecting_from =
match set_of_closures_var with
| None -> None
| Some set_of_closures_var ->
let projection : Projection.t =
Project_closure {
set_of_closures = set_of_closures_var;
closure_id;
}
in
match E.find_projection env ~projection with
| None -> None
| Some var -> Some (var, projection)
in
match projecting_from with
| Some (var, projection) ->
simplify_free_variable_named env var ~f:(fun _env var var_approx ->
let r = R.map_benefit r (B.remove_projection projection) in
Expr (Var var), ret r var_approx)
| None ->
match reference_recursive_function_directly env closure_id with
| Some (flam, approx) -> flam, ret r approx
| None ->
let set_of_closures_var =
match set_of_closures_var with
| Some set_of_closures_var' when E.mem env set_of_closures_var' ->
set_of_closures_var
| Some _ | None -> None
in
let approx =
A.value_closure ?set_of_closures_var value_set_of_closures
closure_id
in
Project_closure { set_of_closures; closure_id; }, ret r approx)
(* Simplify an expression that, given one closure within some set of
closures, returns another closure (possibly the same one) within the
same set. *)
let simplify_move_within_set_of_closures env r
~(move_within_set_of_closures : Flambda.move_within_set_of_closures)
: Flambda.named * R.t =
simplify_free_variable_named env move_within_set_of_closures.closure
~f:(fun _env closure closure_approx ->
match A.check_approx_for_closure_allowing_unresolved closure_approx with
| Wrong ->
Misc.fatal_errorf "Wrong approximation when moving within set of \
closures. Approximation: %a Term: %a"
A.print closure_approx
Flambda.print_move_within_set_of_closures move_within_set_of_closures
| Unresolved sym ->
Move_within_set_of_closures {
closure;
start_from = move_within_set_of_closures.start_from;
move_to = move_within_set_of_closures.move_to;
},
ret r (A.value_unresolved sym)
| Unknown ->
Move_within_set_of_closures {
closure;
start_from = move_within_set_of_closures.start_from;
move_to = move_within_set_of_closures.move_to;
},
ret r (A.value_unknown Other)
| Unknown_because_of_unresolved_value value ->
(* For example: a move upon a (move upon a closure whose .cmx file
is missing). *)
Move_within_set_of_closures {
closure;
start_from = move_within_set_of_closures.start_from;
move_to = move_within_set_of_closures.move_to;
},
ret r (A.value_unknown (Unresolved_value value))
| Ok (_value_closure, set_of_closures_var, set_of_closures_symbol,
value_set_of_closures) ->
let freshen =
(* CR-soon mshinwell: potentially misleading name---not freshening with
new names, but with previously fresh names *)
A.freshen_and_check_closure_id value_set_of_closures
in
let move_to = freshen move_within_set_of_closures.move_to in
let start_from = freshen move_within_set_of_closures.start_from in
let projection : Projection.t =
Move_within_set_of_closures {
closure;
start_from;
move_to;
}
in
match E.find_projection env ~projection with
| Some var ->
simplify_free_variable_named env var ~f:(fun _env var var_approx ->
let r = R.map_benefit r (B.remove_projection projection) in
Expr (Var var), ret r var_approx)
| None ->
match reference_recursive_function_directly env move_to with
| Some (flam, approx) -> flam, ret r approx
| None ->
if Closure_id.equal start_from move_to then
(* Moving from one closure to itself is a no-op. We can return an
[Var] since we already have a variable bound to the closure. *)
Expr (Var closure), ret r closure_approx
else
match set_of_closures_var with
| Some set_of_closures_var when E.mem env set_of_closures_var ->
(* A variable bound to the set of closures is in scope,
meaning we can rewrite the [Move_within_set_of_closures] to a
[Project_closure]. *)
let project_closure : Flambda.project_closure =
{ set_of_closures = set_of_closures_var;
closure_id = move_to;
}
in
let approx =
A.value_closure ~set_of_closures_var value_set_of_closures
move_to
in
Project_closure project_closure, ret r approx
| Some _ | None ->
match set_of_closures_symbol with
| Some set_of_closures_symbol ->
let set_of_closures_var = Variable.create "symbol" in
let project_closure : Flambda.project_closure =
{ set_of_closures = set_of_closures_var;
closure_id = move_to;
}
in
let project_closure_var = Variable.create "project_closure" in
let let1 =
Flambda.create_let project_closure_var
(Project_closure project_closure)
(Var project_closure_var)
in
let expr =
Flambda.create_let set_of_closures_var
(Symbol set_of_closures_symbol)
let1
in
let approx =
A.value_closure ~set_of_closures_var ~set_of_closures_symbol
value_set_of_closures move_to
in
Expr expr, ret r approx
| None ->
(* The set of closures is not available in scope, and we
have no other information by which to simplify the move. *)
let move_within : Flambda.move_within_set_of_closures =
{ closure; start_from; move_to; }
in
let approx = A.value_closure value_set_of_closures move_to in
Move_within_set_of_closures move_within, ret r approx)
(* Transform an expression denoting an access to a variable bound in
a closure. Variables in the closure ([project_var.closure]) may
have been freshened since [expr] was constructed; as such, we
must ensure the same happens to [expr]. The renaming information is
contained within the approximation deduced from [closure] (as
such, that approximation *must* identify which closure it is).
For instance in some imaginary syntax for flambda:
[let f x =
let g y ~closure:{a} = a + y in
let closure = { a = x } in
g 12 ~closure]
when [f] is traversed, [g] can be inlined, resulting in the
expression
[let f z =
let g y ~closure:{a} = a + y in
let closure = { a = x } in
closure.a + 12]
[closure.a] being a notation for:
[Project_var{closure = closure; closure_id = g; var = a}]
If [f] is inlined later, the resulting code will be
[let x = ... in
let g' y' ~closure':{a'} = a' + y' in
let closure' = { a' = x } in
closure'.a' + 12]
in particular the field [a] of the closure has been alpha renamed to [a'].
This information must be carried from the declaration to the use.
If the function is declared outside of the alpha renamed part, there is
no need for renaming in the [Ffunction] and [Project_var].
This is not usually the case, except when the closure declaration is a
symbol.
What ensures that this information is available at [Project_var]
point is that those constructions can only be introduced by inlining,
which requires that same information. For this to still be valid,
other transformation must avoid transforming the information flow in
a way that the inline function can't propagate it.
*)
let rec simplify_project_var env r ~(project_var : Flambda.project_var)
: Flambda.named * R.t =
simplify_free_variable_named env project_var.closure
~f:(fun _env closure approx ->
match A.check_approx_for_closure_allowing_unresolved approx with
| Ok (value_closure, _set_of_closures_var, _set_of_closures_symbol,
value_set_of_closures) ->
let module F = Freshening.Project_var in
let freshening = value_set_of_closures.freshening in
let var = F.apply_var_within_closure freshening project_var.var in
let closure_id = F.apply_closure_id freshening project_var.closure_id in
let closure_id_in_approx = value_closure.closure_id in
if not (Closure_id.equal closure_id closure_id_in_approx) then begin
Misc.fatal_errorf "When simplifying [Project_var], the closure ID %a \
in the approximation of the set of closures did not match the \
closure ID %a in the [Project_var] term. Approximation: %a@. \
Var-within-closure being projected: %a@."
Closure_id.print closure_id_in_approx
Closure_id.print closure_id
Simple_value_approx.print approx
Var_within_closure.print var
end;
let projection : Projection.t =
Project_var {
closure;
closure_id;
var;
}
in
begin match E.find_projection env ~projection with
| Some var ->
simplify_free_variable_named env var ~f:(fun _env var var_approx ->
let r = R.map_benefit r (B.remove_projection projection) in
Expr (Var var), ret r var_approx)
| None ->
let approx = A.approx_for_bound_var value_set_of_closures var in
let expr : Flambda.named = Project_var { closure; closure_id; var; } in
let unwrapped = Var_within_closure.unwrap var in
let expr =
if E.mem env unwrapped then
Flambda.Expr (Var unwrapped)
else
expr
in
simplify_named_using_approx_and_env env r expr approx
end
| Unresolved symbol ->
(* This value comes from a symbol for which we couldn't find any
approximation, telling us that names within the closure couldn't
have been renamed. So we don't need to change the variable or
closure ID in the [Project_var] expression. *)
Project_var { project_var with closure },
ret r (A.value_unresolved symbol)
| Unknown ->
Project_var { project_var with closure },
ret r (A.value_unknown Other)
| Unknown_because_of_unresolved_value value ->
Project_var { project_var with closure },
ret r (A.value_unknown (Unresolved_value value))
| Wrong ->
(* We must have the correct approximation of the value to ensure
we take account of all freshenings. *)
Misc.fatal_errorf "[Project_var] from a value with wrong \
approximation: %a@.closure=%a@.approx of closure=%a@."
Flambda.print_project_var project_var
Variable.print closure
Simple_value_approx.print approx)
(* Transforms closure definitions by applying [loop] on the code of every
one of the set and on the expressions of the free variables.
If the substitution is activated, alpha renaming also occur on everything
defined by the set of closures:
* Variables bound by a closure of the set
* closure identifiers
* parameters
The rewriting occurs in a clean environment without any of the variables
defined outside reachable. This helps increase robustness against
accidental, potentially unsound simplification of variable accesses by
[simplify_using_approx_and_env].
The rewriting occurs in an environment filled with:
* The approximation of the free variables
* An explicitely unknown approximation for function parameters,
except for those where it is known to be safe: those present in the
[specialised_args] set.
* An approximation for the closures in the set. It contains the code of
the functions before rewriting.
The approximation of the currently defined closures is available to
allow marking recursives calls as direct and in some cases, allow
inlining of one closure from the set inside another one. For this to
be correct an alpha renaming is first applied on the expressions by
[apply_function_decls_and_free_vars].
For instance when rewriting the declaration
[let rec f_1 x_1 =
let y_1 = x_1 + 1 in
g_1 y_1
and g_1 z_1 = f_1 (f_1 z_1)]
When rewriting this function, the first substitution will contain
some mapping:
{ f_1 -> f_2;
g_1 -> g_2;
x_1 -> x_2;
z_1 -> z_2 }
And the approximation for the closure will contain
{ f_2:
fun x_2 ->
let y_1 = x_2 + 1 in
g_2 y_1
g_2:
fun z_2 -> f_2 (f_2 z_2) }
Note that no substitution is applied to the let-bound variable [y_1].
If [f_2] where to be inlined inside [g_2], we known that a new substitution
will be introduced in the current scope for [y_1] each time.
If the function where a recursive one coming from another compilation
unit, the code already went through [Flambdasym] that could have
replaced the function variable by the symbol identifying the function
(this occur if the function contains only constants in its closure).
To handle that case, we first replace those symbols by the original
variable.
*)
and simplify_set_of_closures original_env r
(set_of_closures : Flambda.set_of_closures)
: Flambda.set_of_closures * R.t * Freshening.Project_var.t =
let function_decls =
let module Backend = (val (E.backend original_env) : Backend_intf.S) in
(* CR-soon mshinwell: Does this affect
[reference_recursive_function_directly]?
mshinwell: This should be thought about as part of the wider issue of
references to functions via symbols or variables. *)
Freshening.rewrite_recursive_calls_with_symbols (E.freshening original_env)
set_of_closures.function_decls
~make_closure_symbol:Backend.closure_symbol
in
let env = E.increase_closure_depth original_env in
let free_vars, specialised_args, function_decls, parameter_approximations,
internal_value_set_of_closures, set_of_closures_env =
Inline_and_simplify_aux.prepare_to_simplify_set_of_closures ~env
~set_of_closures ~function_decls ~only_for_function_decl:None
~freshen:true
in
let simplify_function fun_var (function_decl : Flambda.function_declaration)
(funs, used_params, r)
: Flambda.function_declaration Variable.Map.t * Variable.Set.t * R.t =
let closure_env =
Inline_and_simplify_aux.prepare_to_simplify_closure ~function_decl
~free_vars ~specialised_args ~parameter_approximations
~set_of_closures_env
in
let body, r =
E.enter_closure closure_env ~closure_id:(Closure_id.wrap fun_var)
~inline_inside:
(Inlining_decision.should_inline_inside_declaration function_decl)
~dbg:function_decl.dbg
~f:(fun body_env -> simplify body_env r function_decl.body)
in
let inline : Lambda.inline_attribute =
match function_decl.inline with
| Default_inline ->
if !Clflags.classic_inlining && not function_decl.stub then
(* In classic-inlining mode, the inlining decision is taken at
definition site (here). If the function is small enough
(below the -inline threshold) it will always be inlined. *)
let inlining_threshold =
Inline_and_simplify_aux.initial_inlining_threshold
~round:(E.round env)
in
if Inlining_cost.can_inline body inlining_threshold ~bonus:0
then
Always_inline
else
Default_inline
else
Default_inline
| inline ->
inline
in
let function_decl =
Flambda.create_function_declaration ~params:function_decl.params
~body ~stub:function_decl.stub ~dbg:function_decl.dbg
~inline ~specialise:function_decl.specialise
~is_a_functor:function_decl.is_a_functor
in
let used_params' = Flambda.used_params function_decl in
Variable.Map.add fun_var function_decl funs,
Variable.Set.union used_params used_params', r
in
let funs, _used_params, r =
Variable.Map.fold simplify_function function_decls.funs
(Variable.Map.empty, Variable.Set.empty, r)
in
let function_decls =
Flambda.update_function_declarations function_decls ~funs
in
let invariant_params =
lazy (Invariant_params.invariant_params_in_recursion function_decls
~backend:(E.backend env))
in
let value_set_of_closures =
A.create_value_set_of_closures ~function_decls
~bound_vars:internal_value_set_of_closures.bound_vars
~invariant_params
~specialised_args:internal_value_set_of_closures.specialised_args
~freshening:internal_value_set_of_closures.freshening
~direct_call_surrogates:
internal_value_set_of_closures.direct_call_surrogates
in
let direct_call_surrogates =
Closure_id.Map.fold (fun existing surrogate surrogates ->
Variable.Map.add (Closure_id.unwrap existing)
(Closure_id.unwrap surrogate) surrogates)
internal_value_set_of_closures.direct_call_surrogates
Variable.Map.empty
in
let set_of_closures =
Flambda.create_set_of_closures ~function_decls
~free_vars:(Variable.Map.map fst free_vars)
~specialised_args
~direct_call_surrogates
in
let r = ret r (A.value_set_of_closures value_set_of_closures) in
set_of_closures, r, value_set_of_closures.freshening
and simplify_apply env r ~(apply : Flambda.apply) : Flambda.t * R.t =
let {
Flambda. func = lhs_of_application; args; kind = _; dbg;
inline = inline_requested; specialise = specialise_requested;
} = apply in
let dbg = E.add_inlined_debuginfo env ~dbg in
simplify_free_variable env lhs_of_application
~f:(fun env lhs_of_application lhs_of_application_approx ->
simplify_free_variables env args ~f:(fun env args args_approxs ->
(* By using the approximation of the left-hand side of the
application, attempt to determine which function is being applied
(even if the application is currently [Indirect]). If
successful---in which case we then have a direct
application---consider inlining. *)
match A.check_approx_for_closure lhs_of_application_approx with
| Ok (value_closure, set_of_closures_var,
set_of_closures_symbol, value_set_of_closures) ->
let lhs_of_application, closure_id_being_applied,
value_set_of_closures, env, wrap =
let closure_id_being_applied = value_closure.closure_id in
(* If the call site is a direct call to a function that has a
"direct call surrogate" (see inline_and_simplify_aux.mli),
repoint the call to the surrogate. *)
let surrogates = value_set_of_closures.direct_call_surrogates in
match Closure_id.Map.find closure_id_being_applied surrogates with
| exception Not_found ->
lhs_of_application, closure_id_being_applied,
value_set_of_closures, env, (fun expr -> expr)
| surrogate ->
let rec find_transitively surrogate =
match Closure_id.Map.find surrogate surrogates with
| exception Not_found -> surrogate
| surrogate -> find_transitively surrogate
in
let surrogate = find_transitively surrogate in
let surrogate_var =
Variable.rename lhs_of_application ~append:"_surrogate"
in
let move_to_surrogate : Projection.move_within_set_of_closures =
{ closure = lhs_of_application;
start_from = closure_id_being_applied;
move_to = surrogate;
}
in
let approx_for_surrogate =
A.value_closure ~closure_var:surrogate_var
?set_of_closures_var ?set_of_closures_symbol
value_set_of_closures surrogate
in
let env = E.add env surrogate_var approx_for_surrogate in
let wrap expr =
Flambda.create_let surrogate_var
(Move_within_set_of_closures move_to_surrogate)
expr
in
surrogate_var, surrogate, value_set_of_closures, env, wrap
in
let function_decls = value_set_of_closures.function_decls in
let function_decl =
try
Flambda_utils.find_declaration closure_id_being_applied
function_decls
with
| Not_found ->
Misc.fatal_errorf "When handling application expression, \
approximation references non-existent closure %a@."
Closure_id.print closure_id_being_applied
in
let r =
match apply.kind with
| Indirect ->
R.map_benefit r Inlining_cost.Benefit.direct_call_of_indirect
| Direct _ -> r
in
let nargs = List.length args in
let arity = Flambda_utils.function_arity function_decl in
let result, r =
if nargs = arity then
simplify_full_application env r ~function_decls
~lhs_of_application ~closure_id_being_applied ~function_decl
~value_set_of_closures ~args ~args_approxs ~dbg
~inline_requested ~specialise_requested
else if nargs > arity then
simplify_over_application env r ~args ~args_approxs
~function_decls ~lhs_of_application ~closure_id_being_applied
~function_decl ~value_set_of_closures ~dbg ~inline_requested
~specialise_requested
else if nargs > 0 && nargs < arity then
simplify_partial_application env r ~lhs_of_application
~closure_id_being_applied ~function_decl ~args ~dbg
~inline_requested ~specialise_requested
else
Misc.fatal_errorf "Function with arity %d when simplifying \
application expression: %a"
arity Flambda.print (Flambda.Apply apply)
in
wrap result, r
| Wrong -> (* Insufficient approximation information to simplify. *)
Apply ({ func = lhs_of_application; args; kind = Indirect; dbg;
inline = inline_requested; specialise = specialise_requested; }),
ret r (A.value_unknown Other)))
and simplify_full_application env r ~function_decls ~lhs_of_application
~closure_id_being_applied ~function_decl ~value_set_of_closures ~args
~args_approxs ~dbg ~inline_requested ~specialise_requested =
Inlining_decision.for_call_site ~env ~r ~function_decls
~lhs_of_application ~closure_id_being_applied ~function_decl
~value_set_of_closures ~args ~args_approxs ~dbg ~simplify
~inline_requested ~specialise_requested
and simplify_partial_application env r ~lhs_of_application
~closure_id_being_applied ~function_decl ~args ~dbg
~inline_requested ~specialise_requested =
let arity = Flambda_utils.function_arity function_decl in
assert (arity > List.length args);
(* For simplicity, we disallow [@inline] attributes on partial
applications. The user may always write an explicit wrapper instead
with such an attribute. *)
(* CR-someday mshinwell: Pierre noted that we might like a function to be
inlined when applied to its first set of arguments, e.g. for some kind
of type class like thing. *)
begin match (inline_requested : Lambda.inline_attribute) with
| Always_inline | Never_inline ->
Location.prerr_warning (Debuginfo.to_location dbg)
(Warnings.Inlining_impossible "[@inlined] attributes may not be used \
on partial applications")
| Unroll _ ->
Location.prerr_warning (Debuginfo.to_location dbg)
(Warnings.Inlining_impossible "[@unroll] attributes may not be used \
on partial applications")
| Default_inline -> ()
end;
begin match (specialise_requested : Lambda.specialise_attribute) with
| Always_specialise | Never_specialise ->
Location.prerr_warning (Debuginfo.to_location dbg)
(Warnings.Inlining_impossible "[@specialised] attributes may not be used \
on partial applications")
| Default_specialise -> ()
end;
let freshened_params =
List.map (fun p -> Parameter.rename p) function_decl.Flambda.params
in
let applied_args, remaining_args =
Misc.Stdlib.List.map2_prefix (fun arg id' -> id', arg)
args freshened_params
in
let wrapper_accepting_remaining_args =
let body : Flambda.t =
Apply {
func = lhs_of_application;
args = Parameter.List.vars freshened_params;
kind = Direct closure_id_being_applied;
dbg;
inline = Default_inline;
specialise = Default_specialise;
}
in
let closure_variable =
Variable.rename
~append:"_partial_fun"
(Closure_id.unwrap closure_id_being_applied)
in
Flambda_utils.make_closure_declaration ~id:closure_variable
~body
~params:remaining_args
~stub:true
in
let with_known_args =
Flambda_utils.bind
~bindings:(List.map (fun (param, arg) ->
Parameter.var param, Flambda.Expr (Var arg)) applied_args)
~body:wrapper_accepting_remaining_args
in
simplify env r with_known_args
and simplify_over_application env r ~args ~args_approxs ~function_decls
~lhs_of_application ~closure_id_being_applied ~function_decl
~value_set_of_closures ~dbg ~inline_requested ~specialise_requested =
let arity = Flambda_utils.function_arity function_decl in
assert (arity < List.length args);
assert (List.length args = List.length args_approxs);
let full_app_args, remaining_args =
Misc.Stdlib.List.split_at arity args
in
let full_app_approxs, _ =
Misc.Stdlib.List.split_at arity args_approxs
in
let expr, r =
simplify_full_application env r ~function_decls ~lhs_of_application
~closure_id_being_applied ~function_decl ~value_set_of_closures
~args:full_app_args ~args_approxs:full_app_approxs ~dbg
~inline_requested ~specialise_requested
in
let func_var = Variable.create "full_apply" in
let expr : Flambda.t =
Flambda.create_let func_var (Expr expr)
(Apply { func = func_var; args = remaining_args; kind = Indirect; dbg;
inline = inline_requested; specialise = specialise_requested; })
in
let expr = Lift_code.lift_lets_expr expr ~toplevel:true in
simplify (E.set_never_inline env) r expr
and simplify_named env r (tree : Flambda.named) : Flambda.named * R.t =
match tree with
| Symbol sym ->
(* New Symbol construction could have been introduced during
transformation (by simplify_named_using_approx_and_env).
When this comes from another compilation unit, we must load it. *)
let approx = E.find_or_load_symbol env sym in
simplify_named_using_approx r tree approx
| Const cst -> tree, ret r (simplify_const cst)
| Allocated_const cst -> tree, ret r (approx_for_allocated_const cst)
| Read_mutable mut_var ->
(* See comment on the [Assign] case. *)
let mut_var =
Freshening.apply_mutable_variable (E.freshening env) mut_var
in
Read_mutable mut_var, ret r (A.value_unknown Other)
| Read_symbol_field (symbol, field_index) ->
let approx = E.find_or_load_symbol env symbol in
begin match A.get_field approx ~field_index with
(* CR-someday mshinwell: Think about [Unreachable] vs. [Value_bottom]. *)
| Unreachable -> (Flambda.Expr Proved_unreachable), r
| Ok approx ->
let approx = A.augment_with_symbol_field approx symbol field_index in
simplify_named_using_approx_and_env env r tree approx
end
| Set_of_closures set_of_closures -> begin
let backend = E.backend env in
let set_of_closures, r, first_freshening =
simplify_set_of_closures env r set_of_closures
in
let simplify env r expr ~pass_name : Flambda.named * R.t =
(* If simplifying a set of closures more than once during any given round
of simplification, the [Freshening.Project_var] substitutions arising
from each call to [simplify_set_of_closures] must be composed.
Note that this function only composes with [first_freshening] owing
to the structure of the code below (this new [simplify] is always
in tail position). *)
(* CR-someday mshinwell: It was mooted that maybe we could try
structurally-typed closures (i.e. where we would never rename the
closure elements), or something else, to try to remove
the "closure freshening" thing in the approximation which is hard
to deal with. *)
let expr, r = simplify (E.set_never_inline env) r expr in
let approx = R.approx r in
let value_set_of_closures =
match A.strict_check_approx_for_set_of_closures approx with
| Wrong ->
Misc.fatal_errorf "Unexpected approximation returned from \
simplification of [%s] result: %a"
pass_name A.print approx
| Ok (_var, value_set_of_closures) ->
let freshening =
Freshening.Project_var.compose ~earlier:first_freshening
~later:value_set_of_closures.freshening
in
A.update_freshening_of_value_set_of_closures value_set_of_closures
~freshening
in
Expr expr, (ret r (A.value_set_of_closures value_set_of_closures))
in
(* This does the actual substitutions of specialised args introduced
by [Unbox_closures] for free variables. (Apart from simplifying
the [Unbox_closures] output, this also prevents applying
[Unbox_closures] over and over.) *)
let set_of_closures =
match Remove_free_vars_equal_to_args.run set_of_closures with
| None -> set_of_closures
| Some set_of_closures -> set_of_closures
in
(* Do [Unbox_closures] next to try to decide which things are
free variables and which things are specialised arguments before
unboxing them. *)
match
Unbox_closures.rewrite_set_of_closures ~env
~duplicate_function ~set_of_closures
with
| Some (expr, benefit) ->
let r = R.add_benefit r benefit in
simplify env r expr ~pass_name:"Unbox_closures"
| None ->
match Unbox_free_vars_of_closures.run ~env ~set_of_closures with
| Some (expr, benefit) ->
let r = R.add_benefit r benefit in
simplify env r expr ~pass_name:"Unbox_free_vars_of_closures"
| None ->
(* CR-soon mshinwell: should maybe add one allocation for the stub *)
match
Unbox_specialised_args.rewrite_set_of_closures ~env
~duplicate_function ~set_of_closures
with
| Some (expr, benefit) ->
let r = R.add_benefit r benefit in
simplify env r expr ~pass_name:"Unbox_specialised_args"
| None ->
match
Remove_unused_arguments.
separate_unused_arguments_in_set_of_closures
set_of_closures ~backend
with
| Some set_of_closures ->
let expr =
Flambda_utils.name_expr (Set_of_closures set_of_closures)
~name:"remove_unused_arguments"
in
simplify env r expr ~pass_name:"Remove_unused_arguments"
| None ->
Set_of_closures set_of_closures, r
end
| Project_closure project_closure ->
simplify_project_closure env r ~project_closure
| Project_var project_var -> simplify_project_var env r ~project_var
| Move_within_set_of_closures move_within_set_of_closures ->
simplify_move_within_set_of_closures env r ~move_within_set_of_closures
| Prim (prim, args, dbg) ->
let dbg = E.add_inlined_debuginfo env ~dbg in
simplify_free_variables_named env args ~f:(fun env args args_approxs ->
let tree = Flambda.Prim (prim, args, dbg) in
begin match prim, args, args_approxs with
| Pgetglobal _, _, _ ->
Misc.fatal_error "Pgetglobal is forbidden in Inline_and_simplify"
(* CR-someday mshinwell: Optimise [Pfield_computed]. *)
| Pfield field_index, [arg], [arg_approx] ->
let projection : Projection.t = Field (field_index, arg) in
begin match E.find_projection env ~projection with
| Some var ->
simplify_free_variable_named env var ~f:(fun _env var var_approx ->
let r = R.map_benefit r (B.remove_projection projection) in
Expr (Var var), ret r var_approx)
| None ->