Skip to content

Commit b5d1929

Browse files
committed
Whitespace and overlong line fixes.
1 parent c226df2 commit b5d1929

File tree

248 files changed

+983
-660
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

248 files changed

+983
-660
lines changed

Changes

Lines changed: 10 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -192,8 +192,8 @@ OCaml 4.07
192192
- GPR#1638: add a Float module.
193193
(Nicolás Ojeda Bär, review by Alain Frisch and Jeremy Yallop)
194194

195-
- GPR#1697: Tune [List.init] tailrec threshold so that it does not stack overflow
196-
when compiled with the Js_of_ocaml backend.
195+
- GPR#1697: Tune [List.init] tailrec threshold so that it does not stack
196+
overflow when compiled with the Js_of_ocaml backend.
197197
(Hugo Heuzard, reviewed by Gabriel Scherer)
198198

199199
### Other libraries:
@@ -273,8 +273,8 @@ OCaml 4.07
273273
- GPR#1618: add the -dno-unique-ids and -dunique-ids compiler flags
274274
(Sébastien Hinderer, review by Leo White and Damien Doligez)
275275

276-
- GPR#1649 change compilation order of toplevel definitions, so that some warnings
277-
emitted by the bytecode compiler appear more in-order than before.
276+
- GPR#1649 change compilation order of toplevel definitions, so that some
277+
warnings emitted by the bytecode compiler appear more in-order than before.
278278
(Luc Maranget, advice and review by Damien Doligez)
279279

280280
- GPR#1806: add linscan to OCAMLPARAM options
@@ -492,7 +492,8 @@ OCaml 4.07
492492

493493
- GPR#1513: Allow compilation units to shadow sub-modules of Pervasives.
494494
For instance users can now use a largeFile.ml file in their project.
495-
(Jérémie Dimino, review by Nicolas Ojeda Bar, Alain Frisch and Gabriel Radanne)
495+
(Jérémie Dimino, review by Nicolas Ojeda Bar, Alain Frisch and Gabriel
496+
Radanne)
496497

497498
- GPR#1516: Allow float array construction in recursive bindings
498499
when configured with -no-flat-float-array
@@ -852,9 +853,10 @@ OCaml 4.06.0 (3 Nov 2017):
852853
pretty-printing items. New fields have been added to the
853854
formatter_out_functions record, thus this change will break any code building
854855
such record from scratch.
855-
When building Format.formatter_out_functions values redefining the out_spaces field,
856-
"{ fmt_out_funs with out_spaces = f; }" should be replaced by
857-
"{ fmt_out_funs with out_spaces = f; out_indent = f; }" to maintain the old behavior.
856+
When building Format.formatter_out_functions values redefining the out_spaces
857+
field, "{ fmt_out_funs with out_spaces = f; }" should be replaced by
858+
"{ fmt_out_funs with out_spaces = f; out_indent = f; }" to maintain the old
859+
behavior.
858860
(Richard Bonichon and Pierre Weis, review by Alain Frisch, original request by
859861
Spiros Eliopoulos in GPR#506)
860862

README.adoc

Lines changed: 16 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -1,14 +1,22 @@
11
|=====
22
| Branch `trunk` | Branch `4.06` | Branch `4.05` | Branch `4.04`
33

4-
| image:https://travis-ci.org/ocaml/ocaml.svg?branch=trunk["TravisCI Build Status (trunk branch)",link="https://travis-ci.org/ocaml/ocaml"]
5-
image:https://ci.appveyor.com/api/projects/status/github/ocaml/ocaml?branch=trunk&svg=true["AppVeyor Build Status (trunk branch)",link="https://ci.appveyor.com/project/avsm/ocaml"]
6-
| image:https://travis-ci.org/ocaml/ocaml.svg?branch=4.06["TravisCI Build Status (4.06 branch)",link="https://travis-ci.org/ocaml/ocaml"]
7-
image:https://ci.appveyor.com/api/projects/status/github/ocaml/ocaml?branch=4.06&svg=true["AppVeyor Build Status (4.06 branch)",link="https://ci.appveyor.com/project/avsm/ocaml"]
8-
| image:https://travis-ci.org/ocaml/ocaml.svg?branch=4.05["TravisCI Build Status (4.05 branch)",link="https://travis-ci.org/ocaml/ocaml"]
9-
image:https://ci.appveyor.com/api/projects/status/github/ocaml/ocaml?branch=4.05&svg=true["AppVeyor Build Status (4.05 branch)",link="https://ci.appveyor.com/project/avsm/ocaml"]
10-
| image:https://travis-ci.org/ocaml/ocaml.svg?branch=4.04["TravisCI Build Status (4.04 branch)",link="https://travis-ci.org/ocaml/ocaml"]
11-
image:https://ci.appveyor.com/api/projects/status/github/ocaml/ocaml?branch=4.04&svg=true["AppVeyor Build Status (4.04 branch)",link="https://ci.appveyor.com/project/avsm/ocaml"]
4+
| image:https://travis-ci.org/ocaml/ocaml.svg?branch=trunk["TravisCI Build Status (trunk branch)",
5+
link="https://travis-ci.org/ocaml/ocaml"]
6+
image:https://ci.appveyor.com/api/projects/status/github/ocaml/ocaml?branch=trunk&svg=true["AppVeyor Build Status (trunk branch)",
7+
link="https://ci.appveyor.com/project/avsm/ocaml"]
8+
| image:https://travis-ci.org/ocaml/ocaml.svg?branch=4.06["TravisCI Build Status (4.06 branch)",
9+
link="https://travis-ci.org/ocaml/ocaml"]
10+
image:https://ci.appveyor.com/api/projects/status/github/ocaml/ocaml?branch=4.06&svg=true["AppVeyor Build Status (4.06 branch)",
11+
link="https://ci.appveyor.com/project/avsm/ocaml"]
12+
| image:https://travis-ci.org/ocaml/ocaml.svg?branch=4.05["TravisCI Build Status (4.05 branch)",
13+
link="https://travis-ci.org/ocaml/ocaml"]
14+
image:https://ci.appveyor.com/api/projects/status/github/ocaml/ocaml?branch=4.05&svg=true["AppVeyor Build Status (4.05 branch)",
15+
link="https://ci.appveyor.com/project/avsm/ocaml"]
16+
| image:https://travis-ci.org/ocaml/ocaml.svg?branch=4.04["TravisCI Build Status (4.04 branch)",
17+
link="https://travis-ci.org/ocaml/ocaml"]
18+
image:https://ci.appveyor.com/api/projects/status/github/ocaml/ocaml?branch=4.04&svg=true["AppVeyor Build Status (4.04 branch)",
19+
link="https://ci.appveyor.com/project/avsm/ocaml"]
1220

1321
|=====
1422

README.win32.adoc

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -96,7 +96,7 @@ Visual C/C++ Compiler as well as the Build Tools for Visual Studio.
9696

9797
|=====
9898
| | `cl` Version | Express | SDK/Build Tools
99-
| Visual Studio 2005 | 14.00.x.x | 32-bit only <<vs1,(*)>> |
99+
| Visual Studio 2005 | 14.00.x.x | 32-bit only <<vs1,(*)>> |
100100
| Visual Studio 2008 | 15.00.x.x | 32-bit only | Windows SDK 7.0 also provides 32/64-bit compilers
101101
| Visual Studio 2010 | 16.00.x.x | 32-bit only | Windows SDK 7.1 also provides 32/64-bit compilers
102102
| Visual Studio 2012 | 17.00.x.x | 32/64-bit |

asmcomp/arm/reload.ml

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -44,9 +44,9 @@ method! reload_operation op arg res =
4444
| Iabsf | Inegf when !fpu = Soft ->
4545
(* Soft FP neg and abs also have a "two-address" constraint of sorts.
4646
64-bit floats are represented by pairs of 32-bit integers,
47-
hence there are two arguments and two results.
48-
The code emitter assumes [arg.(0) = res.(0)] but supports
49-
[arg.(1)] and [res.(1)] being in different registers. *)
47+
hence there are two arguments and two results.
48+
The code emitter assumes [arg.(0) = res.(0)] but supports
49+
[arg.(1)] and [res.(1)] being in different registers. *)
5050
res'.(0) <- arg'.(0);
5151
argres'
5252
| _ ->

asmcomp/asmlink.ml

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -353,7 +353,8 @@ let link ppf objfiles output_name =
353353
(fun () -> make_startup_file ppf units_tolink);
354354
Misc.try_finally
355355
(fun () ->
356-
call_linker (List.map object_file_name objfiles) startup_obj output_name)
356+
call_linker (List.map object_file_name objfiles)
357+
startup_obj output_name)
357358
(fun () -> remove_file startup_obj)
358359
)
359360

asmcomp/build_export_info.ml

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -652,13 +652,14 @@ let build_transient ~(backend : (module Backend_intf.S))
652652
let closure_id_to_set_of_closures_id =
653653
Set_of_closures_id.Map.fold
654654
(fun set_of_closure_id
655-
(function_declarations : Simple_value_approx.function_declarations) acc ->
656-
Variable.Map.fold
657-
(fun fun_var _ acc ->
655+
(function_declarations : Simple_value_approx.function_declarations)
656+
acc ->
657+
Variable.Map.fold
658+
(fun fun_var _ acc ->
658659
let closure_id = Closure_id.wrap fun_var in
659660
Closure_id.Map.add closure_id set_of_closure_id acc)
660-
function_declarations.funs
661-
acc)
661+
function_declarations.funs
662+
acc)
662663
function_declarations_map
663664
Closure_id.Map.empty
664665
in
@@ -710,4 +711,3 @@ let build_transient ~(backend : (module Backend_intf.S))
710711
~relevant_imported_closure_ids
711712
~relevant_local_vars_within_closure
712713
~relevant_imported_vars_within_closure
713-

asmcomp/closure.ml

Lines changed: 8 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -645,19 +645,24 @@ let rec substitute loc fpc sb rn ulam =
645645
(fun id id' s -> Tbl.add id (Uvar id') s)
646646
ids ids' sb
647647
in
648-
Ucatch(nfail, ids', substitute loc fpc sb rn u1, substitute loc fpc sb' rn u2)
648+
Ucatch(nfail, ids', substitute loc fpc sb rn u1,
649+
substitute loc fpc sb' rn u2)
649650
| Utrywith(u1, id, u2) ->
650651
let id' = Ident.rename id in
651652
Utrywith(substitute loc fpc sb rn u1, id',
652653
substitute loc fpc (Tbl.add id (Uvar id') sb) rn u2)
653654
| Uifthenelse(u1, u2, u3) ->
654655
begin match substitute loc fpc sb rn u1 with
655656
Uconst (Uconst_ptr n) ->
656-
if n <> 0 then substitute loc fpc sb rn u2 else substitute loc fpc sb rn u3
657+
if n <> 0 then
658+
substitute loc fpc sb rn u2
659+
else
660+
substitute loc fpc sb rn u3
657661
| Uprim(Pmakeblock _, _, _) ->
658662
substitute loc fpc sb rn u2
659663
| su1 ->
660-
Uifthenelse(su1, substitute loc fpc sb rn u2, substitute loc fpc sb rn u3)
664+
Uifthenelse(su1, substitute loc fpc sb rn u2,
665+
substitute loc fpc sb rn u3)
661666
end
662667
| Usequence(u1, u2) ->
663668
Usequence(substitute loc fpc sb rn u1, substitute loc fpc sb rn u2)

asmcomp/cmmgen.ml

Lines changed: 25 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -612,7 +612,7 @@ let set_field ptr n newval init dbg =
612612
Cop(Cstore (Word_val, init), [field_address ptr n dbg; newval], dbg)
613613

614614
let non_profinfo_mask =
615-
if Config.profinfo
615+
if Config.profinfo
616616
then (1 lsl (64 - Config.profinfo_width)) - 1
617617
else 0 (* [non_profinfo_mask] is unused in this case *)
618618

@@ -1106,13 +1106,14 @@ let bigarray_get unsafe elt_kind layout b args dbg =
11061106
Pbigarray_complex32 | Pbigarray_complex64 ->
11071107
let kind = bigarray_word_kind elt_kind in
11081108
let sz = bigarray_elt_size elt_kind / 2 in
1109-
bind "addr" (bigarray_indexing unsafe elt_kind layout b args dbg) (fun addr ->
1110-
bind "reval"
1111-
(Cop(Cload (kind, Mutable), [addr], dbg)) (fun reval ->
1112-
bind "imval"
1113-
(Cop(Cload (kind, Mutable),
1114-
[Cop(Cadda, [addr; Cconst_int sz], dbg)], dbg)) (fun imval ->
1115-
box_complex dbg reval imval)))
1109+
bind "addr"
1110+
(bigarray_indexing unsafe elt_kind layout b args dbg) (fun addr ->
1111+
bind "reval"
1112+
(Cop(Cload (kind, Mutable), [addr], dbg)) (fun reval ->
1113+
bind "imval"
1114+
(Cop(Cload (kind, Mutable),
1115+
[Cop(Cadda, [addr; Cconst_int sz], dbg)], dbg))
1116+
(fun imval -> box_complex dbg reval imval)))
11161117
| _ ->
11171118
Cop(Cload (bigarray_word_kind elt_kind, Mutable),
11181119
[bigarray_indexing unsafe elt_kind layout b args dbg],
@@ -2081,7 +2082,8 @@ and transl_prim_1 env p arg dbg =
20812082
bind "header" hdr (fun hdr ->
20822083
Cifthenelse(is_addr_array_hdr hdr dbg,
20832084
Cop(Clsr, [hdr; Cconst_int wordsize_shift], dbg),
2084-
Cop(Clsr, [hdr; Cconst_int numfloat_shift], dbg))) in
2085+
Cop(Clsr, [hdr; Cconst_int numfloat_shift], dbg)))
2086+
in
20852087
Cop(Cor, [len; Cconst_int 1], dbg)
20862088
| Paddrarray | Pintarray ->
20872089
Cop(Cor, [addr_array_length hdr dbg; Cconst_int 1], dbg)
@@ -2213,23 +2215,28 @@ and transl_prim_2 env p arg1 arg2 dbg =
22132215
(* Float operations *)
22142216
| Paddfloat ->
22152217
box_float dbg (Cop(Caddf,
2216-
[transl_unbox_float dbg env arg1; transl_unbox_float dbg env arg2],
2218+
[transl_unbox_float dbg env arg1;
2219+
transl_unbox_float dbg env arg2],
22172220
dbg))
22182221
| Psubfloat ->
22192222
box_float dbg (Cop(Csubf,
2220-
[transl_unbox_float dbg env arg1; transl_unbox_float dbg env arg2],
2223+
[transl_unbox_float dbg env arg1;
2224+
transl_unbox_float dbg env arg2],
22212225
dbg))
22222226
| Pmulfloat ->
22232227
box_float dbg (Cop(Cmulf,
2224-
[transl_unbox_float dbg env arg1; transl_unbox_float dbg env arg2],
2228+
[transl_unbox_float dbg env arg1;
2229+
transl_unbox_float dbg env arg2],
22252230
dbg))
22262231
| Pdivfloat ->
22272232
box_float dbg (Cop(Cdivf,
2228-
[transl_unbox_float dbg env arg1; transl_unbox_float dbg env arg2],
2233+
[transl_unbox_float dbg env arg1;
2234+
transl_unbox_float dbg env arg2],
22292235
dbg))
22302236
| Pfloatcomp cmp ->
22312237
tag_int(Cop(Ccmpf(transl_float_comparison cmp),
2232-
[transl_unbox_float dbg env arg1; transl_unbox_float dbg env arg2],
2238+
[transl_unbox_float dbg env arg1;
2239+
transl_unbox_float dbg env arg2],
22332240
dbg)) dbg
22342241

22352242
(* String operations *)
@@ -2404,7 +2411,8 @@ and transl_prim_2 env p arg1 arg2 dbg =
24042411
untag_int(transl env arg2) dbg], dbg))
24052412
| Plsrbint bi ->
24062413
box_int dbg bi (Cop(Clsr,
2407-
[make_unsigned_int bi (transl_unbox_int dbg env bi arg1) dbg;
2414+
[make_unsigned_int bi (transl_unbox_int dbg env bi arg1)
2415+
dbg;
24082416
untag_int(transl env arg2) dbg], dbg))
24092417
| Pasrbint bi ->
24102418
box_int dbg bi (Cop(Casr,
@@ -3331,7 +3339,8 @@ let final_curry_function arity =
33313339
let newclos = Ident.create "clos" in
33323340
Clet(newclos,
33333341
get_field env (Cvar clos) 4 dbg,
3334-
curry_fun (get_field env (Cvar clos) 3 dbg :: args) newclos (n-1))
3342+
curry_fun (get_field env (Cvar clos) 3 dbg :: args)
3343+
newclos (n-1))
33353344
end in
33363345
Cfunction
33373346
{fun_name = "caml_curry" ^ string_of_int arity ^

asmcomp/export_info.ml

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -277,7 +277,9 @@ let merge (t1 : t) (t2 : t) : t =
277277
sets_of_closures =
278278
Set_of_closures_id.Map.disjoint_union t1.sets_of_closures
279279
t2.sets_of_closures;
280-
symbol_id = Symbol.Map.disjoint_union ~print:Export_id.print t1.symbol_id t2.symbol_id;
280+
symbol_id =
281+
Symbol.Map.disjoint_union ~print:Export_id.print t1.symbol_id
282+
t2.symbol_id;
281283
offset_fun = Closure_id.Map.disjoint_union
282284
~eq:int_eq t1.offset_fun t2.offset_fun;
283285
offset_fv = Var_within_closure.Map.disjoint_union

asmcomp/flambda_to_clambda.ml

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -24,8 +24,10 @@ type 'a for_one_or_more_units = {
2424
}
2525

2626
type t = {
27-
current_unit : Set_of_closures_id.t for_one_or_more_units;
28-
imported_units : Simple_value_approx.function_declarations for_one_or_more_units;
27+
current_unit :
28+
Set_of_closures_id.t for_one_or_more_units;
29+
imported_units :
30+
Simple_value_approx.function_declarations for_one_or_more_units;
2931
}
3032

3133
let get_fun_offset t closure_id =

0 commit comments

Comments
 (0)