Skip to content

Commit cc6dbe7

Browse files
committed
Code review
1 parent c375b09 commit cc6dbe7

File tree

5 files changed

+18
-15
lines changed

5 files changed

+18
-15
lines changed

asmcomp/cmm.mli

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -182,6 +182,9 @@ and operation =
182182
ty_args : exttype list;
183183
alloc : bool;
184184
returns : bool; }
185+
(** The [machtype] is the machine type of the result.
186+
The [exttype list] describes the unboxing types of the arguments.
187+
An empty list means "all arguments are machine words [XInt]". *)
185188
| Cload of memory_chunk * Asttypes.mutable_flag
186189
| Calloc
187190
| Cstore of memory_chunk * Lambda.initialization_or_assignment

middle_end/closure/closure.ml

Lines changed: 11 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -798,17 +798,16 @@ let direct_apply env fundesc ufunct uargs ~loc ~attribute =
798798
then app
799799
else Usequence(ufunct, app)
800800

801-
(* Add [Value_integer] or [Value_constptr] info to the approximation
802-
of an application *)
801+
(* Add [Value_integer] info to the approximation of an application *)
803802

804803
let strengthen_approx appl approx =
805804
match approx_ulam appl with
806805
(Value_const _) as intapprox ->
807806
intapprox
808807
| _ -> approx
809808

810-
(* If a term has approximation Value_integer or Value_constptr and is pure,
811-
replace it by an integer constant *)
809+
(* If a term has approximation Value_integer and is pure, replace it by an
810+
integer constant *)
812811

813812
let check_constant_result ulam approx =
814813
match approx with
@@ -1070,12 +1069,14 @@ let rec close ({ backend; fenv; cenv ; mutable_vars } as env) lam =
10701069
close env arg
10711070
| Lprim(Pdirapply,[funct;arg], loc)
10721071
| Lprim(Prevapply,[arg;funct], loc) ->
1073-
close env (Lapply{ap_loc=loc;
1074-
ap_func=funct;
1075-
ap_args=[arg];
1076-
ap_tailcall=Default_tailcall;
1077-
ap_inlined=Default_inline;
1078-
ap_specialised=Default_specialise})
1072+
close env
1073+
(Lapply{ap_loc=loc;
1074+
ap_func=funct;
1075+
ap_args=[arg];
1076+
ap_tailcall=Default_tailcall;
1077+
ap_inlined=Default_inline;
1078+
ap_specialised=Default_specialise
1079+
})
10791080
| Lprim(Pgetglobal id, [], loc) ->
10801081
let dbg = Debuginfo.from_location loc in
10811082
check_constant_result (getglobal dbg id)

middle_end/flambda/to_cmm/un_cps_helper.ml

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -17,8 +17,8 @@
1717
open Cmm_helpers
1818
module P = Flambda_primitive
1919

20-
let unsupported_32_bits () =
21-
Misc.fatal_errorf "32 bits is currently unsupported in Flambda."
20+
let unsupported_32_bits () =
21+
Misc.fatal_errorf "32 bits is currently unsupported in Flambda."
2222

2323
(* Are we compiling on/for a 32-bit architecture ? *)
2424
let arch32 = Arch.size_int = 4
@@ -39,7 +39,7 @@ let exttype_of_kind k =
3939
| Thirty_two -> Cmm.XInt32
4040
| Sixty_four -> Cmm.XInt64
4141
end
42-
| Fabricated -> Misc.fatal_error "[Fabricated] king not expected here"
42+
| Fabricated -> Misc.fatal_error "[Fabricated] kind not expected here"
4343

4444
(* Void *)
4545

middle_end/flambda/to_cmm/un_cps_helper.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -27,7 +27,7 @@ val arch64 : bool
2727
val typ_int64 : Cmm.machtype
2828
(** An adequate Cmm machtype for an int64 (including on a 32-bit target). *)
2929

30-
val exttype_of_kind : Flambda_kind.t -> Cmm.exttype
30+
val exttype_of_kind : Flambda_kind.t -> Cmm.exttype
3131

3232
(** {2 Data items} *)
3333

runtime/compact.c

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -15,7 +15,6 @@
1515

1616
#define CAML_INTERNALS
1717

18-
1918
#include <string.h>
2019

2120
#include "caml/address_class.h"

0 commit comments

Comments
 (0)