Skip to content

Commit ca3d70f

Browse files
committed
Preview: Upgrade to OCamlformat 0.27.0 (unreleased)
The aim of this preview is to gather feedback. Changelog can be found here: https://github.com/ocaml-ppx/ocamlformat/blob/main/CHANGES.md Signed-off-by: Jules Aguillon <[email protected]>
1 parent 832acca commit ca3d70f

File tree

229 files changed

+3812
-3472
lines changed

Some content is hidden

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

229 files changed

+3812
-3472
lines changed

.ocamlformat

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,3 @@
1-
version=0.26.2
1+
version=0.27.0
22
profile=janestreet
33
ocaml-version=4.08.0

bench/bench.ml

Lines changed: 22 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -180,28 +180,28 @@ let tag_results { size; clean; zero } =
180180
- stack_size - not very useful
181181
- forced_collections - only available in OCaml >= 4.12 *)
182182
let display_clean_and_zero_with_sandboxing
183-
({ elapsed_time
184-
; user_cpu_time
185-
; system_cpu_time
186-
; minor_words
187-
; promoted_words
188-
; major_words
189-
; minor_collections
190-
; major_collections
191-
; heap_words
192-
; heap_chunks
193-
; live_words
194-
; live_blocks
195-
; free_words
196-
; free_blocks
197-
; largest_free
198-
; fragments = _
199-
; compactions
200-
; top_heap_words
201-
; stack_size = _
202-
} :
203-
_ Metrics.t)
204-
(zero : _ Metrics.t)
183+
({ elapsed_time
184+
; user_cpu_time
185+
; system_cpu_time
186+
; minor_words
187+
; promoted_words
188+
; major_words
189+
; minor_collections
190+
; major_collections
191+
; heap_words
192+
; heap_chunks
193+
; live_words
194+
; live_blocks
195+
; free_words
196+
; free_blocks
197+
; largest_free
198+
; fragments = _
199+
; compactions
200+
; top_heap_words
201+
; stack_size = _
202+
} :
203+
_ Metrics.t)
204+
(zero : _ Metrics.t)
205205
=
206206
let display what units clean zero =
207207
{ Output.name = what

bench/gen_synthetic.ml

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -8,10 +8,12 @@ let write_modules basedir num_modules =
88
done
99
;;
1010

11-
let dune = {|
11+
let dune =
12+
{|
1213
(library
1314
(name test))
1415
|}
16+
;;
1517

1618
let write basedir =
1719
let () = Unix.mkdir basedir 0o777 in

bench/gen_synthetic_dune_watch.ml

Lines changed: 12 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -21,10 +21,10 @@ let write_subset base_dir library_index subset =
2121
List.flatten
2222
(List.map
2323
(fun k ->
24-
List.map
25-
(fun j ->
26-
sprintf "M_%d_%d_%d_%d.f()" (library_index - 1) j mod_rows k)
27-
(count subsets_per_library))
24+
List.map
25+
(fun j ->
26+
sprintf "M_%d_%d_%d_%d.f()" (library_index - 1) j mod_rows k)
27+
(count subsets_per_library))
2828
(count mod_cols))
2929
else
3030
List.map
@@ -68,17 +68,21 @@ let write_lib ~base_dir ~lib ~dune =
6868

6969
let write base_dir =
7070
let () = Unix.mkdir base_dir 0o777 in
71-
let dune = {|
71+
let dune =
72+
{|
7273
(library
7374
(name leaf)
7475
(libraries internal))
75-
|} in
76+
|}
77+
in
7678
write_lib ~base_dir ~lib:Leaf ~dune;
77-
let dune = {|
79+
let dune =
80+
{|
7881
(library
7982
(name internal)
8083
(wrapped false))
81-
|} in
84+
|}
85+
in
8286
write_lib ~base_dir ~lib:Internal ~dune
8387
;;
8488

bench/metrics.mli

Lines changed: 11 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -6,41 +6,41 @@ open Stdune
66
[unzip] functions which make serialisation easier. *)
77
type ('float, 'int) t =
88
{ elapsed_time : 'float
9-
(** Real time elapsed since the process started and the process
9+
(** Real time elapsed since the process started and the process
1010
finished. *)
1111
; user_cpu_time : 'float
12-
(** The amount of CPU time spent in user mode during the process. Other
12+
(** The amount of CPU time spent in user mode during the process. Other
1313
processes and blocked time are not included. *)
1414
; system_cpu_time : 'float
15-
(** The amount of CPU time spent in kernel mode during the process.
15+
(** The amount of CPU time spent in kernel mode during the process.
1616
Similar to user time, other processes and time spent blocked by
1717
other processes are not counted. *)
1818
; minor_words : 'float
19-
(** Number of words allocated in the minor heap since the program was
19+
(** Number of words allocated in the minor heap since the program was
2020
started. *)
2121
; promoted_words : 'float
22-
(** Number of words that have been promoted from the minor to the major
22+
(** Number of words that have been promoted from the minor to the major
2323
heap since the program was started. *)
2424
; major_words : 'float
25-
(** Number of words allocated in the major heap since the program was
25+
(** Number of words allocated in the major heap since the program was
2626
started. *)
2727
; minor_collections : 'int
28-
(** Number of minor collections since the program was started. *)
28+
(** Number of minor collections since the program was started. *)
2929
; major_collections : 'int
30-
(** Number of major collection cycles completed since the program was
30+
(** Number of major collection cycles completed since the program was
3131
started. *)
3232
; heap_words : 'int (** Total size of the major heap, in words. *)
3333
; heap_chunks : 'int
34-
(** Number of contiguous pieces of memory that make up the major heap. *)
34+
(** Number of contiguous pieces of memory that make up the major heap. *)
3535
; live_words : 'int
36-
(** Number of words of live data in the major heap, including the header
36+
(** Number of words of live data in the major heap, including the header
3737
words. *)
3838
; live_blocks : 'int (** Number of live blocks in the major heap. *)
3939
; free_words : 'int (** Number of words in the free list. *)
4040
; free_blocks : 'int (** Number of blocks in the free list. *)
4141
; largest_free : 'int (** Size (in words) of the largest block in the free list. *)
4242
; fragments : 'int
43-
(** Number of wasted words due to fragmentation. These are 1-words free
43+
(** Number of wasted words due to fragmentation. These are 1-words free
4444
blocks placed between two live blocks. They are not available for
4545
allocation. *)
4646
; compactions : 'int (** Number of heap compactions since the program was started. *)

bench/micro/path_bench.ml

Lines changed: 34 additions & 33 deletions
Original file line numberDiff line numberDiff line change
@@ -8,56 +8,57 @@ let root = "."
88
let short_path = "a/b/c"
99
let long_path = List.init 20 ~f:(fun _ -> "foo-bar-baz") |> String.concat ~sep:"/"
1010

11-
let%bench_fun ("is_root" [@params
12-
path
13-
= [ "root", "."
14-
; "short path", short_path
15-
; "long path", long_path
16-
]])
11+
let%bench_fun
12+
("is_root"
13+
[@params path = [ "root", "."; "short path", short_path; "long path", long_path ]])
1714
=
1815
fun () -> ignore (Fpath.is_root path)
1916
;;
2017

21-
let%bench_fun ("reach" [@params
22-
t
23-
= [ "from root long path", (long_path, root)
24-
; "from root short path", (short_path, root)
25-
; "reach root from short path", (root, short_path)
26-
; "reach root from long path", (root, long_path)
27-
; ( "reach long path from similar long path"
28-
, ( Filename.concat long_path "a"
29-
, Filename.concat long_path "b" ) )
30-
; ( "reach short path from similar short path"
31-
, ( Filename.concat short_path "a"
32-
, Filename.concat short_path "b" ) )
33-
]])
18+
let%bench_fun
19+
("reach"
20+
[@params
21+
t
22+
= [ "from root long path", (long_path, root)
23+
; "from root short path", (short_path, root)
24+
; "reach root from short path", (root, short_path)
25+
; "reach root from long path", (root, long_path)
26+
; ( "reach long path from similar long path"
27+
, (Filename.concat long_path "a", Filename.concat long_path "b") )
28+
; ( "reach short path from similar short path"
29+
, (Filename.concat short_path "a", Filename.concat short_path "b") )
30+
]])
3431
=
3532
let t, from = t in
3633
let t = Path.of_string t in
3734
let from = Path.of_string from in
3835
fun () -> ignore (Path.reach t ~from)
3936
;;
4037

41-
let%bench_fun ("Path.Local.relative" [@params
42-
t
43-
= [ "left root", (".", long_path)
44-
; "right root", (long_path, ".")
45-
; "short paths", (short_path, short_path)
46-
; "long paths", (long_path, long_path)
47-
]])
38+
let%bench_fun
39+
("Path.Local.relative"
40+
[@params
41+
t
42+
= [ "left root", (".", long_path)
43+
; "right root", (long_path, ".")
44+
; "short paths", (short_path, short_path)
45+
; "long paths", (long_path, long_path)
46+
]])
4847
=
4948
let x, y = t in
5049
let x = Path.Local.of_string x in
5150
fun () -> ignore (Path.Local.relative x y)
5251
;;
5352

54-
let%bench_fun ("Path.Local.append" [@params
55-
t
56-
= [ "left root", (".", long_path)
57-
; "right root", (long_path, ".")
58-
; "short paths", (short_path, short_path)
59-
; "long paths", (long_path, long_path)
60-
]])
53+
let%bench_fun
54+
("Path.Local.append"
55+
[@params
56+
t
57+
= [ "left root", (".", long_path)
58+
; "right root", (long_path, ".")
59+
; "short paths", (short_path, short_path)
60+
; "long paths", (long_path, long_path)
61+
]])
6162
=
6263
let x, y = t in
6364
let x = Path.Local.of_string x in

bin/build_cmd.ml

Lines changed: 32 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -37,46 +37,47 @@ let run_build_system ~common ~request =
3737
let open Fiber.O in
3838
Fiber.finalize
3939
(fun () ->
40-
(* CR-someday amokhov: Currently we invalidate cached timestamps on every
40+
(* CR-someday amokhov: Currently we invalidate cached timestamps on every
4141
incremental rebuild. This conservative approach helps us to work around
4242
some [mtime] resolution problems (e.g. on Mac OS). It would be nice to
4343
find a way to avoid doing this. In fact, this may be unnecessary even
4444
for the initial build if we assume that the user does not modify files
4545
in the [_build] directory. For now, it's unclear if optimising this is
4646
worth the effort. *)
47-
Cached_digest.invalidate_cached_timestamps ();
48-
let* setup = Import.Main.setup () in
49-
let request =
50-
Action_builder.bind (Action_builder.of_memo setup) ~f:(fun setup -> request setup)
51-
in
52-
(* CR-someday cmoseley: Can we avoid creating a new lazy memo node every
47+
Cached_digest.invalidate_cached_timestamps ();
48+
let* setup = Import.Main.setup () in
49+
let request =
50+
Action_builder.bind (Action_builder.of_memo setup) ~f:(fun setup ->
51+
request setup)
52+
in
53+
(* CR-someday cmoseley: Can we avoid creating a new lazy memo node every
5354
time the build system is rerun? *)
54-
(* This top-level node is used for traversing the whole Memo graph. *)
55-
let toplevel_cell, toplevel =
56-
Memo.Lazy.Expert.create ~name:"toplevel" (fun () ->
57-
let open Memo.O in
58-
let+ (), (_ : Dep.Fact.t Dep.Map.t) =
59-
Action_builder.evaluate_and_collect_facts request
60-
in
61-
())
62-
in
63-
let* res = run ~toplevel in
64-
let+ () =
65-
match Common.dump_memo_graph_file common with
66-
| None -> Fiber.return ()
67-
| Some file ->
68-
let path = Path.external_ file in
69-
let+ graph =
70-
Memo.dump_cached_graph
71-
~time_nodes:(Common.dump_memo_graph_with_timing common)
72-
toplevel_cell
73-
in
74-
Graph.serialize graph ~path ~format:(Common.dump_memo_graph_format common)
75-
(* CR-someday cmoseley: It would be nice to use Persistent to dump a
55+
(* This top-level node is used for traversing the whole Memo graph. *)
56+
let toplevel_cell, toplevel =
57+
Memo.Lazy.Expert.create ~name:"toplevel" (fun () ->
58+
let open Memo.O in
59+
let+ (), (_ : Dep.Fact.t Dep.Map.t) =
60+
Action_builder.evaluate_and_collect_facts request
61+
in
62+
())
63+
in
64+
let* res = run ~toplevel in
65+
let+ () =
66+
match Common.dump_memo_graph_file common with
67+
| None -> Fiber.return ()
68+
| Some file ->
69+
let path = Path.external_ file in
70+
let+ graph =
71+
Memo.dump_cached_graph
72+
~time_nodes:(Common.dump_memo_graph_with_timing common)
73+
toplevel_cell
74+
in
75+
Graph.serialize graph ~path ~format:(Common.dump_memo_graph_format common)
76+
(* CR-someday cmoseley: It would be nice to use Persistent to dump a
7677
copy of the graph's internal representation here, so it could be used
7778
without needing to re-run the build*)
78-
in
79-
res)
79+
in
80+
res)
8081
~finally:(fun () ->
8182
Hooks.End_of_build.run ();
8283
Fiber.return ())

bin/describe/aliases_targets.ml

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -24,9 +24,10 @@ let ls_term (fetch_results : Path.Build.t -> string list Action_builder.t) =
2424
(* We only drop the build context if it is correct. *)
2525
match Path.Build.extract_build_context d with
2626
| Some (dir_context_name, d) ->
27-
if Dune_engine.Context_name.equal
28-
context
29-
(Dune_engine.Context_name.of_string dir_context_name)
27+
if
28+
Dune_engine.Context_name.equal
29+
context
30+
(Dune_engine.Context_name.of_string dir_context_name)
3031
then d
3132
else
3233
User_error.raise

0 commit comments

Comments
 (0)