forked from ocaml-flambda/flambda-backend
-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathlambda.ml
2069 lines (1870 loc) · 69.3 KB
/
lambda.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 *)
(* *)
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
(* *)
(* Copyright 1996 Institut National de Recherche en Informatique et *)
(* en Automatique. *)
(* *)
(* 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. *)
(* *)
(**************************************************************************)
open Misc
open Asttypes
type constant = Typedtree.constant
type mutable_flag = Immutable | Immutable_unique | Mutable
type compile_time_constant =
| Big_endian
| Word_size
| Int_size
| Max_wosize
| Ostype_unix
| Ostype_win32
| Ostype_cygwin
| Backend_type
| Runtime5
type immediate_or_pointer =
| Immediate
| Pointer
type is_safe =
| Safe
| Unsafe
type field_read_semantics =
| Reads_agree
| Reads_vary
include (struct
type locality_mode =
| Alloc_heap
| Alloc_local
type alloc_mode = locality_mode
type modify_mode =
| Modify_heap
| Modify_maybe_stack
let alloc_heap = Alloc_heap
let alloc_local : alloc_mode =
if Config.stack_allocation then Alloc_local
else Alloc_heap
let join_mode a b =
match a, b with
| Alloc_local, _ | _, Alloc_local -> Alloc_local
| Alloc_heap, Alloc_heap -> Alloc_heap
let modify_heap = Modify_heap
let modify_maybe_stack : modify_mode =
if Config.stack_allocation then Modify_maybe_stack
else Modify_heap
let equal_alloc_mode mode1 mode2 =
match mode1, mode2 with
| Alloc_local, Alloc_local | Alloc_heap, Alloc_heap -> true
| (Alloc_local | Alloc_heap), _ -> false
end : sig
type locality_mode = private
| Alloc_heap
| Alloc_local
type alloc_mode = locality_mode
type modify_mode = private
| Modify_heap
| Modify_maybe_stack
val alloc_heap : locality_mode
val alloc_local : locality_mode
val modify_heap : modify_mode
val modify_maybe_stack : modify_mode
val join_mode : alloc_mode -> alloc_mode -> alloc_mode
val equal_alloc_mode : alloc_mode -> alloc_mode -> bool
end)
let is_local_mode = function
| Alloc_heap -> false
| Alloc_local -> true
let is_heap_mode = function
| Alloc_heap -> true
| Alloc_local -> false
let sub_mode a b =
match a, b with
| Alloc_heap, _ -> true
| _, Alloc_local -> true
| Alloc_local, Alloc_heap -> false
let eq_mode a b =
match a, b with
| Alloc_heap, Alloc_heap -> true
| Alloc_local, Alloc_local -> true
| Alloc_heap, Alloc_local -> false
| Alloc_local, Alloc_heap -> false
type initialization_or_assignment =
| Assignment of modify_mode
| Heap_initialization
| Root_initialization
type region_close =
| Rc_normal
| Rc_nontail
| Rc_close_at_apply
type primitive =
| Pbytes_to_string
| Pbytes_of_string
| Pignore
(* Globals *)
| Pgetglobal of Compilation_unit.t
| Psetglobal of Compilation_unit.t
| Pgetpredef of Ident.t
(* Operations on heap blocks *)
| Pmakeblock of int * mutable_flag * block_shape * alloc_mode
| Pmakefloatblock of mutable_flag * alloc_mode
| Pmakeufloatblock of mutable_flag * alloc_mode
| Pmakemixedblock of int * mutable_flag * mixed_block_shape * alloc_mode
| Pfield of int * immediate_or_pointer * field_read_semantics
| Pfield_computed of field_read_semantics
| Psetfield of int * immediate_or_pointer * initialization_or_assignment
| Psetfield_computed of immediate_or_pointer * initialization_or_assignment
| Pfloatfield of int * field_read_semantics * alloc_mode
| Pufloatfield of int * field_read_semantics
| Pmixedfield of int * mixed_block_read * field_read_semantics
| Psetfloatfield of int * initialization_or_assignment
| Psetufloatfield of int * initialization_or_assignment
| Psetmixedfield of int * mixed_block_write * initialization_or_assignment
| Pduprecord of Types.record_representation * int
(* Unboxed products *)
| Pmake_unboxed_product of layout list
| Punboxed_product_field of int * layout list
(* Context switches *)
| Prunstack
| Pperform
| Presume
| Preperform
(* External call *)
| Pccall of external_call_description
(* Exceptions *)
| Praise of raise_kind
(* Boolean operations *)
| Psequand | Psequor | Pnot
(* Integer operations *)
| Pnegint | Paddint | Psubint | Pmulint
| Pdivint of is_safe | Pmodint of is_safe
| Pandint | Porint | Pxorint
| Plslint | Plsrint | Pasrint
| Pintcomp of integer_comparison
| Pcompare_ints
| Pcompare_floats of boxed_float
| Pcompare_bints of boxed_integer
| Poffsetint of int
| Poffsetref of int
(* Float operations *)
| Pfloatoffloat32 of alloc_mode
| Pfloat32offloat of alloc_mode
| Pintoffloat of boxed_float
| Pfloatofint of boxed_float * alloc_mode
| Pnegfloat of boxed_float * alloc_mode
| Pabsfloat of boxed_float * alloc_mode
| Paddfloat of boxed_float * alloc_mode
| Psubfloat of boxed_float * alloc_mode
| Pmulfloat of boxed_float * alloc_mode
| Pdivfloat of boxed_float * alloc_mode
| Pfloatcomp of boxed_float * float_comparison
| Punboxed_float_comp of boxed_float * float_comparison
(* String operations *)
| Pstringlength | Pstringrefu | Pstringrefs
| Pbyteslength | Pbytesrefu | Pbytessetu | Pbytesrefs | Pbytessets
(* Array operations *)
| Pmakearray of array_kind * mutable_flag * alloc_mode
| Pduparray of array_kind * mutable_flag
| Parraylength of array_kind
| Parrayrefu of array_ref_kind * array_index_kind
| Parraysetu of array_set_kind * array_index_kind
| Parrayrefs of array_ref_kind * array_index_kind
| Parraysets of array_set_kind * array_index_kind
(* Test if the argument is a block or an immediate integer *)
| Pisint of { variant_only : bool }
(* Test if the (integer) argument is outside an interval *)
| Pisout
(* Operations on boxed integers (Nativeint.t, Int32.t, Int64.t) *)
| Pbintofint of boxed_integer * alloc_mode
| Pintofbint of boxed_integer
| Pcvtbint of boxed_integer (*source*) * boxed_integer (*destination*)
* alloc_mode
| Pnegbint of boxed_integer * alloc_mode
| Paddbint of boxed_integer * alloc_mode
| Psubbint of boxed_integer * alloc_mode
| Pmulbint of boxed_integer * alloc_mode
| Pdivbint of { size : boxed_integer; is_safe : is_safe; mode: alloc_mode }
| Pmodbint of { size : boxed_integer; is_safe : is_safe; mode: alloc_mode }
| Pandbint of boxed_integer * alloc_mode
| Porbint of boxed_integer * alloc_mode
| Pxorbint of boxed_integer * alloc_mode
| Plslbint of boxed_integer * alloc_mode
| Plsrbint of boxed_integer * alloc_mode
| Pasrbint of boxed_integer * alloc_mode
| Pbintcomp of boxed_integer * integer_comparison
| Punboxed_int_comp of unboxed_integer * integer_comparison
(* Operations on Bigarrays: (unsafe, #dimensions, kind, layout) *)
| Pbigarrayref of bool * int * bigarray_kind * bigarray_layout
| Pbigarrayset of bool * int * bigarray_kind * bigarray_layout
(* size of the nth dimension of a Bigarray *)
| Pbigarraydim of int
(* load/set 16,32,64,128 bits from a string: (unsafe)*)
| Pstring_load_16 of bool
| Pstring_load_32 of bool * alloc_mode
| Pstring_load_64 of bool * alloc_mode
| Pstring_load_128 of { unsafe : bool; mode: alloc_mode }
| Pbytes_load_16 of bool
| Pbytes_load_32 of bool * alloc_mode
| Pbytes_load_64 of bool * alloc_mode
| Pbytes_load_128 of { unsafe : bool; mode: alloc_mode }
| Pbytes_set_16 of bool
| Pbytes_set_32 of bool
| Pbytes_set_64 of bool
| Pbytes_set_128 of { unsafe : bool }
(* load/set 16,32,64,128 bits from a
(char, int8_unsigned_elt, c_layout) Bigarray.Array1.t : (unsafe) *)
| Pbigstring_load_16 of { unsafe : bool }
| Pbigstring_load_32 of { unsafe : bool; mode: alloc_mode; boxed : bool }
| Pbigstring_load_64 of { unsafe : bool; mode: alloc_mode; boxed : bool }
| Pbigstring_load_128 of { aligned : bool; unsafe : bool; mode: alloc_mode;
boxed : bool }
| Pbigstring_set_16 of { unsafe : bool }
| Pbigstring_set_32 of { unsafe : bool; boxed : bool }
| Pbigstring_set_64 of { unsafe : bool; boxed : bool }
| Pbigstring_set_128 of { aligned : bool; unsafe : bool; boxed : bool }
(* load/set SIMD vectors in GC-managed arrays *)
| Pfloatarray_load_128 of { unsafe : bool; mode : alloc_mode }
| Pfloat_array_load_128 of { unsafe : bool; mode : alloc_mode }
| Pint_array_load_128 of { unsafe : bool; mode : alloc_mode }
| Punboxed_float_array_load_128 of { unsafe : bool; mode : alloc_mode }
| Punboxed_int32_array_load_128 of { unsafe : bool; mode : alloc_mode }
| Punboxed_int64_array_load_128 of { unsafe : bool; mode : alloc_mode }
| Punboxed_nativeint_array_load_128 of { unsafe : bool; mode : alloc_mode }
| Pfloatarray_set_128 of { unsafe : bool }
| Pfloat_array_set_128 of { unsafe : bool }
| Pint_array_set_128 of { unsafe : bool }
| Punboxed_float_array_set_128 of { unsafe : bool }
| Punboxed_int32_array_set_128 of { unsafe : bool }
| Punboxed_int64_array_set_128 of { unsafe : bool }
| Punboxed_nativeint_array_set_128 of { unsafe : bool }
(* Compile time constants *)
| Pctconst of compile_time_constant
(* byte swap *)
| Pbswap16
| Pbbswap of boxed_integer * alloc_mode
(* Integer to external pointer *)
| Pint_as_pointer of alloc_mode
(* Atomic operations *)
| Patomic_load of {immediate_or_pointer : immediate_or_pointer}
| Patomic_exchange
| Patomic_cas
| Patomic_fetch_add
(* Inhibition of optimisation *)
| Popaque of layout
(* Statically-defined probes *)
| Pprobe_is_enabled of { name: string }
(* Primitives for [Obj] *)
| Pobj_dup
| Pobj_magic of layout
| Punbox_float of boxed_float
| Pbox_float of boxed_float * alloc_mode
| Punbox_int of boxed_integer
| Pbox_int of boxed_integer * alloc_mode
(* Jane Street extensions *)
| Parray_to_iarray
| Parray_of_iarray
| Pget_header of alloc_mode
(* Fetching domain-local state *)
| Pdls_get
and extern_repr =
| Same_as_ocaml_repr of Jkind.Sort.const
| Unboxed_float of boxed_float
| Unboxed_vector of Primitive.boxed_vector
| Unboxed_integer of Primitive.boxed_integer
| Untagged_int
and external_call_description = extern_repr Primitive.description_gen
and integer_comparison =
Ceq | Cne | Clt | Cgt | Cle | Cge
and float_comparison =
CFeq | CFneq | CFlt | CFnlt | CFgt | CFngt | CFle | CFnle | CFge | CFnge
and value_kind =
| Pgenval
| Pintval
| Pboxedfloatval of boxed_float
| Pboxedintval of boxed_integer
| Pvariant of {
consts : int list;
non_consts : (int * constructor_shape) list;
}
| Parrayval of array_kind
| Pboxedvectorval of boxed_vector
and layout =
| Ptop
| Pvalue of value_kind
| Punboxed_float of boxed_float
| Punboxed_int of boxed_integer
| Punboxed_vector of boxed_vector
| Punboxed_product of layout list
| Pbottom
and block_shape =
value_kind list option
and flat_element = Types.flat_element =
Imm | Float | Float64 | Float32 | Bits32 | Bits64 | Word
and flat_element_read =
| Flat_read of flat_element (* invariant: not [Float] *)
| Flat_read_float of alloc_mode
and mixed_block_read =
| Mread_value_prefix of immediate_or_pointer
| Mread_flat_suffix of flat_element_read
and mixed_block_write =
| Mwrite_value_prefix of immediate_or_pointer
| Mwrite_flat_suffix of flat_element
and mixed_block_shape = Types.mixed_product_shape =
{ value_prefix_len : int;
flat_suffix : flat_element array;
}
and constructor_shape =
| Constructor_uniform of value_kind list
| Constructor_mixed of
{ value_prefix : value_kind list;
flat_suffix : flat_element list;
}
and array_kind =
Pgenarray | Paddrarray | Pintarray | Pfloatarray
| Punboxedfloatarray of unboxed_float
| Punboxedintarray of unboxed_integer
and array_ref_kind =
| Pgenarray_ref of alloc_mode
| Paddrarray_ref
| Pintarray_ref
| Pfloatarray_ref of alloc_mode
| Punboxedfloatarray_ref of unboxed_float
| Punboxedintarray_ref of unboxed_integer
and array_set_kind =
| Pgenarray_set of modify_mode
| Paddrarray_set of modify_mode
| Pintarray_set
| Pfloatarray_set
| Punboxedfloatarray_set of unboxed_float
| Punboxedintarray_set of unboxed_integer
and array_index_kind =
| Ptagged_int_index
| Punboxed_int_index of unboxed_integer
and boxed_float = Primitive.boxed_float =
| Pfloat64
| Pfloat32
and boxed_integer = Primitive.boxed_integer =
Pnativeint | Pint32 | Pint64
and unboxed_float = boxed_float
and unboxed_integer = boxed_integer
and vec128_type =
| Unknown128
| Int8x16
| Int16x8
| Int32x4
| Int64x2
| Float32x4
| Float64x2
and boxed_vector =
| Pvec128 of vec128_type
and bigarray_kind =
Pbigarray_unknown
| Pbigarray_float32 | Pbigarray_float64
| Pbigarray_sint8 | Pbigarray_uint8
| Pbigarray_sint16 | Pbigarray_uint16
| Pbigarray_int32 | Pbigarray_int64
| Pbigarray_caml_int | Pbigarray_native_int
| Pbigarray_complex32 | Pbigarray_complex64
and bigarray_layout =
Pbigarray_unknown_layout
| Pbigarray_c_layout
| Pbigarray_fortran_layout
and raise_kind =
| Raise_regular
| Raise_reraise
| Raise_notrace
let vec128_name = function
| Unknown128 -> "unknown128"
| Int8x16 -> "int8x16"
| Int16x8 -> "int16x8"
| Int32x4 -> "int32x4"
| Int64x2 -> "int64x2"
| Float32x4 -> "float32x4"
| Float64x2 -> "float64x2"
let equal_boxed_integer = Primitive.equal_boxed_integer
let equal_boxed_float = Primitive.equal_boxed_float
let equal_boxed_vector_size v1 v2 =
match v1, v2 with
| Pvec128 _, Pvec128 _ -> true
let compare_boxed_vector = Stdlib.compare
let print_boxed_vector ppf t =
match t with
| Pvec128 v -> Format.pp_print_string ppf (vec128_name v)
let join_vec128_types v1 v2 =
match v1, v2 with
| Unknown128, _ | _, Unknown128 -> Unknown128
| Int8x16, Int8x16 -> Int8x16
| Int16x8, Int16x8 -> Int16x8
| Int32x4, Int32x4 -> Int32x4
| Int64x2, Int64x2 -> Int64x2
| Float32x4, Float32x4 -> Float32x4
| Float64x2, Float64x2 -> Float64x2
| (Int8x16 | Int16x8 | Int32x4 | Int64x2 | Float32x4 | Float64x2), _ ->
Unknown128
let join_boxed_vector_layout v1 v2 =
match v1, v2 with
| Pvec128 v1, Pvec128 v2 -> Punboxed_vector (Pvec128 (join_vec128_types v1 v2))
let rec equal_value_kind x y =
match x, y with
| Pgenval, Pgenval -> true
| Pboxedfloatval f1, Pboxedfloatval f2 -> equal_boxed_float f1 f2
| Pboxedintval bi1, Pboxedintval bi2 -> equal_boxed_integer bi1 bi2
| Pboxedvectorval bi1, Pboxedvectorval bi2 ->
equal_boxed_vector_size bi1 bi2
| Pintval, Pintval -> true
| Parrayval elt_kind1, Parrayval elt_kind2 -> elt_kind1 = elt_kind2
| Pvariant { consts = consts1; non_consts = non_consts1; },
Pvariant { consts = consts2; non_consts = non_consts2; } ->
let consts1 = List.sort Int.compare consts1 in
let consts2 = List.sort Int.compare consts2 in
let compare_by_tag (tag1, _) (tag2, _) = Int.compare tag1 tag2 in
let non_consts1 = List.sort compare_by_tag non_consts1 in
let non_consts2 = List.sort compare_by_tag non_consts2 in
List.equal Int.equal consts1 consts2
&& List.equal (fun (tag1, cstr1) (tag2, cstr2) ->
Int.equal tag1 tag2
&& equal_constructor_shape cstr1 cstr2)
non_consts1 non_consts2
| (Pgenval | Pboxedfloatval _ | Pboxedintval _ | Pintval | Pvariant _
| Parrayval _ | Pboxedvectorval _), _ -> false
and equal_constructor_shape x y =
match x, y with
| Constructor_uniform fields1, Constructor_uniform fields2 ->
List.length fields1 = List.length fields2
&& List.for_all2 equal_value_kind fields1 fields2
| Constructor_mixed { value_prefix = p1; flat_suffix = s1 },
Constructor_mixed { value_prefix = p2; flat_suffix = s2 } ->
List.length p1 = List.length p2
&& List.for_all2 equal_value_kind p1 p2
&& List.length s1 = List.length s2
&& List.for_all2 Types.equal_flat_element s1 s2
| (Constructor_uniform _ | Constructor_mixed _), _ -> false
let equal_layout x y =
match x, y with
| Pvalue x, Pvalue y -> equal_value_kind x y
| Ptop, Ptop -> true
| Pbottom, Pbottom -> true
| _, _ -> false
let rec compatible_layout x y =
match x, y with
| Pbottom, _
| _, Pbottom -> true
| Pvalue _, Pvalue _ -> true
| Punboxed_float f1, Punboxed_float f2 -> equal_boxed_float f1 f2
| Punboxed_int bi1, Punboxed_int bi2 ->
equal_boxed_integer bi1 bi2
| Punboxed_vector bi1, Punboxed_vector bi2 -> equal_boxed_vector_size bi1 bi2
| Punboxed_product layouts1, Punboxed_product layouts2 ->
List.compare_lengths layouts1 layouts2 = 0
&& List.for_all2 compatible_layout layouts1 layouts2
| Ptop, Ptop -> true
| Ptop, _ | _, Ptop -> false
| (Pvalue _ | Punboxed_float _ | Punboxed_int _ | Punboxed_vector _ |
Punboxed_product _), _ ->
false
let must_be_value layout =
match layout with
| Pvalue v -> v
| Pbottom ->
(* Here, we want to get the [value_kind] corresponding to
a [Pbottom] layout. Anything will do, we return [Pgenval]
as a default. *)
Pgenval
| _ -> Misc.fatal_error "Layout is not a value"
type structured_constant =
Const_base of constant
| Const_block of int * structured_constant list
| Const_float_array of string list
| Const_immstring of string
| Const_float_block of string list
type tailcall_attribute =
| Tailcall_expectation of bool
(* [@tailcall] and [@tailcall true] have [true],
[@tailcall false] has [false] *)
| Default_tailcall (* no [@tailcall] attribute *)
type inline_attribute =
| Always_inline (* [@inline] or [@inline always] *)
| Never_inline (* [@inline never] *)
| Available_inline (* [@inline available] *)
| Unroll of int (* [@unroll x] *)
| Default_inline (* no [@inline] attribute *)
type inlined_attribute =
| Always_inlined (* [@inlined] or [@inlined always] *)
| Never_inlined (* [@inlined never] *)
| Hint_inlined (* [@inlined hint] *)
| Unroll of int (* [@unroll x] *)
| Default_inlined (* no [@inlined] attribute *)
let equal_inline_attribute (x : inline_attribute) (y : inline_attribute) =
match x, y with
| Always_inline, Always_inline
| Never_inline, Never_inline
| Available_inline, Available_inline
| Default_inline, Default_inline
->
true
| Unroll u, Unroll v ->
u = v
| (Always_inline | Never_inline
| Available_inline | Unroll _ | Default_inline), _ ->
false
let equal_inlined_attribute (x : inlined_attribute) (y : inlined_attribute) =
match x, y with
| Always_inlined, Always_inlined
| Never_inlined, Never_inlined
| Hint_inlined, Hint_inlined
| Default_inlined, Default_inlined
->
true
| Unroll u, Unroll v ->
u = v
| (Always_inlined | Never_inlined
| Hint_inlined | Unroll _ | Default_inlined), _ ->
false
type probe_desc = { name: string; enabled_at_init: bool; }
type probe = probe_desc option
type specialise_attribute =
| Always_specialise (* [@specialise] or [@specialise always] *)
| Never_specialise (* [@specialise never] *)
| Default_specialise (* no [@specialise] attribute *)
let equal_specialise_attribute x y =
match x, y with
| Always_specialise, Always_specialise
| Never_specialise, Never_specialise
| Default_specialise, Default_specialise ->
true
| (Always_specialise | Never_specialise | Default_specialise), _ ->
false
type local_attribute =
| Always_local (* [@local] or [@local always] *)
| Never_local (* [@local never] *)
| Default_local (* [@local maybe] or no [@local] attribute *)
type poll_attribute =
| Error_poll (* [@poll error] *)
| Default_poll (* no [@poll] attribute *)
type zero_alloc_attribute = Builtin_attributes.zero_alloc_attribute =
| Default_zero_alloc
| Ignore_assert_all
| Check of { strict: bool;
opt: bool;
arity: int;
loc: Location.t;
}
| Assume of { strict: bool;
never_returns_normally: bool;
never_raises: bool;
arity: int;
loc: Location.t;
}
type loop_attribute =
| Always_loop (* [@loop] or [@loop always] *)
| Never_loop (* [@loop never] *)
| Default_loop (* no [@loop] attribute *)
type curried_function_kind = { nlocal : int } [@@unboxed]
type function_kind = Curried of curried_function_kind | Tupled
type let_kind = Strict | Alias | StrictOpt
type meth_kind = Self | Public | Cached
let equal_meth_kind x y =
match x, y with
| Self, Self -> true
| Public, Public -> true
| Cached, Cached -> true
| (Self | Public | Cached), _ -> false
type shared_code = (int * int) list
type static_label = int
type function_attribute = {
inline : inline_attribute;
specialise : specialise_attribute;
local: local_attribute;
zero_alloc : zero_alloc_attribute;
poll: poll_attribute;
loop: loop_attribute;
is_a_functor: bool;
is_opaque: bool;
stub: bool;
tmc_candidate: bool;
may_fuse_arity: bool;
unbox_return: bool;
}
type scoped_location = Debuginfo.Scoped_location.t
type parameter_attribute = {
unbox_param: bool;
}
type lparam = {
name : Ident.t;
layout : layout;
attributes : parameter_attribute;
mode : alloc_mode
}
type pop_region =
| Popped_region
| Same_region
type lambda =
Lvar of Ident.t
| Lmutvar of Ident.t
| Lconst of structured_constant
| Lapply of lambda_apply
| Lfunction of lfunction
| Llet of let_kind * layout * Ident.t * lambda * lambda
| Lmutlet of layout * Ident.t * lambda * lambda
| Lletrec of rec_binding list * lambda
| Lprim of primitive * lambda list * scoped_location
| Lswitch of lambda * lambda_switch * scoped_location * layout
| Lstringswitch of
lambda * (string * lambda) list * lambda option * scoped_location * layout
| Lstaticraise of static_label * lambda list
| Lstaticcatch of
lambda * (static_label * (Ident.t * layout) list) * lambda
* pop_region * layout
| Ltrywith of lambda * Ident.t * lambda * layout
| Lifthenelse of lambda * lambda * lambda * layout
| Lsequence of lambda * lambda
| Lwhile of lambda_while
| Lfor of lambda_for
| Lassign of Ident.t * lambda
| Lsend of
meth_kind * lambda * lambda * lambda list
* region_close * alloc_mode * scoped_location * layout
| Levent of lambda * lambda_event
| Lifused of Ident.t * lambda
| Lregion of lambda * layout
| Lexclave of lambda
and rec_binding = {
id : Ident.t;
def : lfunction;
}
and lfunction =
{ kind: function_kind;
params: lparam list;
return: layout;
body: lambda;
attr: function_attribute; (* specified with [@inline] attribute *)
loc: scoped_location;
mode: alloc_mode;
ret_mode: alloc_mode;
region: bool; }
and lambda_while =
{ wh_cond : lambda;
wh_body : lambda;
}
and lambda_for =
{ for_id : Ident.t;
for_loc : scoped_location;
for_from : lambda;
for_to : lambda;
for_dir : direction_flag;
for_body : lambda;
}
and lambda_apply =
{ ap_func : lambda;
ap_args : lambda list;
ap_result_layout : layout;
ap_region_close : region_close;
ap_mode : alloc_mode;
ap_loc : scoped_location;
ap_tailcall : tailcall_attribute;
ap_inlined : inlined_attribute;
ap_specialised : specialise_attribute;
ap_probe : probe;
}
and lambda_switch =
{ sw_numconsts: int;
sw_consts: (int * lambda) list;
sw_numblocks: int;
sw_blocks: (int * lambda) list;
sw_failaction : lambda option}
and lambda_event =
{ lev_loc: scoped_location;
lev_kind: lambda_event_kind;
lev_repr: int ref option;
lev_env: Env.t }
and lambda_event_kind =
Lev_before
| Lev_after of Types.type_expr
| Lev_function
| Lev_pseudo
type program =
{ compilation_unit : Compilation_unit.t;
main_module_block_size : int;
required_globals : Compilation_unit.Set.t;
code : lambda }
let const_int n = Const_base (Const_int n)
let const_unit = const_int 0
let dummy_constant = Lconst (const_int (0xBBBB / 2))
let max_arity () =
if !Clflags.native_code then 126 else max_int
(* 126 = 127 (the maximal number of parameters supported in C--)
- 1 (the hidden parameter containing the environment) *)
let lfunction' ~kind ~params ~return ~body ~attr ~loc ~mode ~ret_mode ~region =
assert (List.length params <= max_arity ());
(* A curried function type with n parameters has n arrows. Of these,
the first [n-nlocal] have return mode Heap, while the remainder
have return mode Local, except possibly the final one.
That is, after supplying the first [n-nlocal] arguments, further
partial applications must be locally allocated.
A curried function with no local parameters or returns has kind
[Curried {nlocal=0}]. *)
begin match mode, kind with
| Alloc_heap, Tupled -> ()
| Alloc_local, Tupled ->
(* Tupled optimisation does not apply to local functions *)
assert false
| mode, Curried {nlocal} ->
let nparams = List.length params in
assert (0 <= nlocal);
assert (nlocal <= nparams);
if not region then assert (nlocal >= 1);
if is_local_mode mode then assert (nlocal = nparams)
end;
{ kind; params; return; body; attr; loc; mode; ret_mode; region }
let lfunction ~kind ~params ~return ~body ~attr ~loc ~mode ~ret_mode ~region =
Lfunction
(lfunction' ~kind ~params ~return ~body ~attr ~loc ~mode ~ret_mode ~region)
let lambda_unit = Lconst const_unit
let layout_unit = Pvalue Pintval
let layout_int = Pvalue Pintval
let layout_array kind = Pvalue (Parrayval kind)
let layout_block = Pvalue Pgenval
let layout_list =
Pvalue (Pvariant { consts = [0] ;
non_consts = [0, Constructor_uniform [Pgenval; Pgenval]] })
let layout_tuple_element = Pvalue Pgenval
let layout_value_field = Pvalue Pgenval
let layout_tmc_field = Pvalue Pgenval
let layout_optional_arg = Pvalue Pgenval
let layout_variant_arg = Pvalue Pgenval
let layout_exception = Pvalue Pgenval
let layout_function = Pvalue Pgenval
let layout_object = Pvalue Pgenval
let layout_class = Pvalue Pgenval
let layout_module = Pvalue Pgenval
let layout_module_field = Pvalue Pgenval
let layout_functor = Pvalue Pgenval
let layout_boxed_float f = Pvalue (Pboxedfloatval f)
let layout_unboxed_float f = Punboxed_float f
let layout_unboxed_nativeint = Punboxed_int Pnativeint
let layout_unboxed_int32 = Punboxed_int Pint32
let layout_unboxed_int64 = Punboxed_int Pint64
let layout_string = Pvalue Pgenval
let layout_unboxed_int ubi = Punboxed_int ubi
let layout_boxedint bi = Pvalue (Pboxedintval bi)
let layout_unboxed_vector (v : Primitive.boxed_vector) =
match v with
| Pvec128 Int8x16 -> Punboxed_vector (Pvec128 Int8x16)
| Pvec128 Int16x8 -> Punboxed_vector (Pvec128 Int16x8)
| Pvec128 Int32x4 -> Punboxed_vector (Pvec128 Int32x4)
| Pvec128 Int64x2 -> Punboxed_vector (Pvec128 Int64x2)
| Pvec128 Float32x4 -> Punboxed_vector (Pvec128 Float32x4)
| Pvec128 Float64x2 -> Punboxed_vector (Pvec128 Float64x2)
let layout_boxed_vector : Primitive.boxed_vector -> layout = function
| Pvec128 Int8x16 -> Pvalue (Pboxedvectorval (Pvec128 Int8x16))
| Pvec128 Int16x8 -> Pvalue (Pboxedvectorval (Pvec128 Int16x8))
| Pvec128 Int32x4 -> Pvalue (Pboxedvectorval (Pvec128 Int32x4))
| Pvec128 Int64x2 -> Pvalue (Pboxedvectorval (Pvec128 Int64x2))
| Pvec128 Float32x4 -> Pvalue (Pboxedvectorval (Pvec128 Float32x4))
| Pvec128 Float64x2 -> Pvalue (Pboxedvectorval (Pvec128 Float64x2))
let layout_lazy = Pvalue Pgenval
let layout_lazy_contents = Pvalue Pgenval
let layout_any_value = Pvalue Pgenval
let layout_letrec = layout_any_value
let layout_probe_arg = Pvalue Pgenval
let layout_unboxed_product layouts = Punboxed_product layouts
(* CR ncourant: use [Ptop] or remove this as soon as possible. *)
let layout_top = layout_any_value
let layout_bottom = Pbottom
let default_function_attribute = {
inline = Default_inline;
specialise = Default_specialise;
local = Default_local;
zero_alloc = Default_zero_alloc ;
poll = Default_poll;
loop = Default_loop;
is_a_functor = false;
is_opaque = false;
stub = false;
tmc_candidate = false;
(* Plain functions ([fun] and [function]) set [may_fuse_arity] to [false] so
that runtime arity matches syntactic arity in more situations.
Many things compile to functions without having a notion of syntactic arity
that survives typechecking, e.g. functors. Multi-arg functors are compiled
as nested unary functions, and rely on the arity fusion in simplif to make
them multi-argument. So, we keep arity fusion turned on by default for now.
*)
may_fuse_arity = true;
unbox_return = false;
}
let default_stub_attribute =
{ default_function_attribute with stub = true; zero_alloc = Ignore_assert_all }
let default_param_attribute = { unbox_param = false }
(* Build sharing keys *)
(*
Those keys are later compared with Stdlib.compare.
For that reason, they should not include cycles.
*)
let max_raw = 32
let make_key e =
let exception Not_simple in
let count = ref 0 (* Used for controlling size *)
and make_key = Ident.make_key_generator () in
(* make_key is used for normalizing let-bound variables *)
let rec tr_rec env e =
incr count ;
if !count > max_raw then raise Not_simple ; (* Too big ! *)
match e with
| Lvar id
| Lmutvar id ->
begin
try Ident.find_same id env
with Not_found -> e
end
| Lconst (Const_base (Const_string _)) ->
(* Mutable constants are not shared *)
raise Not_simple
| Lconst _ -> e
| Lapply ap ->
Lapply {ap with ap_func = tr_rec env ap.ap_func;
ap_args = tr_recs env ap.ap_args;
ap_loc = Loc_unknown}
| Llet (Alias,_k,x,ex,e) -> (* Ignore aliases -> substitute *)
let ex = tr_rec env ex in
tr_rec (Ident.add x ex env) e
| Llet ((Strict | StrictOpt),_k,x,ex,Lvar v) when Ident.same v x ->
tr_rec env ex
| Llet (str,k,x,ex,e) ->
(* Because of side effects, keep other lets with normalized names *)
let ex = tr_rec env ex in
let y = make_key x in
Llet (str,k,y,ex,tr_rec (Ident.add x (Lvar y) env) e)
| Lmutlet (k,x,ex,e) ->
let ex = tr_rec env ex in
let y = make_key x in
Lmutlet (k,y,ex,tr_rec (Ident.add x (Lmutvar y) env) e)
| Lprim (p,es,_) ->
Lprim (p,tr_recs env es, Loc_unknown)
| Lswitch (e,sw,loc,kind) ->
Lswitch (tr_rec env e,tr_sw env sw,loc,kind)
| Lstringswitch (e,sw,d,_,kind) ->
Lstringswitch
(tr_rec env e,
List.map (fun (s,e) -> s,tr_rec env e) sw,
tr_opt env d,
Loc_unknown,kind)
| Lstaticraise (i,es) ->
Lstaticraise (i,tr_recs env es)
| Lstaticcatch (e1,xs,e2, r, kind) ->
Lstaticcatch (tr_rec env e1,xs,tr_rec env e2, r, kind)
| Ltrywith (e1,x,e2,kind) ->
Ltrywith (tr_rec env e1,x,tr_rec env e2,kind)
| Lifthenelse (cond,ifso,ifnot,kind) ->
Lifthenelse (tr_rec env cond,tr_rec env ifso,tr_rec env ifnot,kind)
| Lsequence (e1,e2) ->
Lsequence (tr_rec env e1,tr_rec env e2)
| Lassign (x,e) ->
Lassign (x,tr_rec env e)
| Lsend (m,e1,e2,es,pos,mo,_loc,layout) ->
Lsend (m,tr_rec env e1,tr_rec env e2,tr_recs env es,pos,mo,Loc_unknown,layout)
| Lifused (id,e) -> Lifused (id,tr_rec env e)
| Lregion (e,layout) -> Lregion (tr_rec env e,layout)
| Lexclave e -> Lexclave (tr_rec env e)
| Lletrec _|Lfunction _
| Lfor _ | Lwhile _
(* Beware: (PR#6412) the event argument to Levent
may include cyclic structure of type Type.typexpr *)
| Levent _ ->
raise Not_simple