Skip to content

Commit

Permalink
Upgrade ocamlformat to 0.20.1
Browse files Browse the repository at this point in the history
Signed-off-by: Etienne Millon <[email protected]>
  • Loading branch information
emillon authored and rgrinberg committed Feb 10, 2022
1 parent c16d66e commit 065466c
Show file tree
Hide file tree
Showing 272 changed files with 1,846 additions and 4,517 deletions.
7 changes: 4 additions & 3 deletions .ocamlformat
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
version=0.19.0
version=0.20.1
profile=conventional
ocaml-version=4.08.0
break-separators=before
dock-collection-brackets=false
break-sequences=true
Expand All @@ -9,12 +10,12 @@ let-and=sparse
sequence-style=terminator
type-decl=sparse
wrap-comments=true
if-then-else=k-r
let-and=sparse
space-around-records
space-around-lists
space-around-arrays
cases-exp-indent=2
break-cases=all
break-cases=fit-or-vertical
indicate-nested-or-patterns=unsafe-no
parse-docstrings=true
module-item-spacing=sparse
3 changes: 1 addition & 2 deletions bench/bench.ml
Original file line number Diff line number Diff line change
Expand Up @@ -107,8 +107,7 @@ let run_bench () =
let+ zero =
let open Fiber.O in
let rec zero acc n =
if n = 0 then
Fiber.return (List.rev acc)
if n = 0 then Fiber.return (List.rev acc)
else
let* time = dune_build () in
zero (time :: acc) (pred n)
Expand Down
14 changes: 2 additions & 12 deletions bench/micro/memo_bench/benchmarks.ml
Original file line number Diff line number Diff line change
Expand Up @@ -143,20 +143,10 @@ let bipartite =
let first_var = Var.create 0 in
let inputs =
List.init 30 ~f:(fun i ->
let v =
if i = 0 then
first_var
else
Var.create 0
in
let v = if i = 0 then first_var else Var.create 0 in
Build.memoize (Var.read v))
in
let matrix i j =
if i = j then
1
else
0
in
let matrix i j = if i = j then 1 else 0 in
let outputs =
List.init 30 ~f:(fun i ->
Build.memoize
Expand Down
16 changes: 4 additions & 12 deletions bin/alias.ml
Original file line number Diff line number Diff line change
Expand Up @@ -11,18 +11,12 @@ type t =
let pp { name; recursive; dir; contexts = _ } =
let open Pp.O in
let s =
(if recursive then
"@"
else
"@@")
(if recursive then "@" else "@@")
^ Path.Source.to_string
(Path.Source.relative dir (Dune_engine.Alias.Name.to_string name))
in
let pp = Pp.verbatim "alias" ++ Pp.space ++ Pp.verbatim s in
if recursive then
Pp.verbatim "recursive" ++ Pp.space ++ pp
else
pp
if recursive then Pp.verbatim "recursive" ++ Pp.space ++ pp else pp

let in_dir ~name ~recursive ~contexts dir =
let checked = Util.check_path contexts dir in
Expand Down Expand Up @@ -94,8 +88,6 @@ let dep_on_alias_rec_multi_contexts ~dir:src_dir ~name ~contexts =

let request { name; recursive; dir; contexts } =
let contexts = List.map ~f:Dune_rules.Context.name contexts in
(if recursive then
dep_on_alias_rec_multi_contexts
else
dep_on_alias_multi_contexts)
(if recursive then dep_on_alias_rec_multi_contexts
else dep_on_alias_multi_contexts)
~dir ~name ~contexts
21 changes: 4 additions & 17 deletions bin/arg.ml
Original file line number Diff line number Diff line change
Expand Up @@ -39,21 +39,13 @@ module Dep = struct
let alias_rec ~dir s = Dep_conf.Alias_rec (make_alias_sw ~dir s)

let parse_alias s =
if not (String.is_prefix s ~prefix:"@") then
None
if not (String.is_prefix s ~prefix:"@") then None
else
let pos, recursive =
if String.length s >= 2 && s.[1] = '@' then
(2, false)
else
(1, true)
if String.length s >= 2 && s.[1] = '@' then (2, false) else (1, true)
in
let s = String_with_vars.make_text Loc.none (String.drop s pos) in
Some
(if recursive then
Dep_conf.Alias_rec s
else
Dep_conf.Alias s)
Some (if recursive then Dep_conf.Alias_rec s else Dep_conf.Alias s)

let dep_parser =
Dune_lang.Syntax.set Stanza.syntax (Active Stanza.latest_version)
Expand All @@ -74,12 +66,7 @@ module Dep = struct
| exception User_error.E msg -> `Error (User_message.to_string msg))

let string_of_alias ~recursive sv =
let prefix =
if recursive then
"@"
else
"@@"
in
let prefix = if recursive then "@" else "@@" in
String_with_vars.text_only sv |> Option.map ~f:(fun s -> prefix ^ s)

let printer ppf t =
Expand Down
29 changes: 14 additions & 15 deletions bin/build_cmd.ml
Original file line number Diff line number Diff line change
Expand Up @@ -6,21 +6,20 @@ let with_metrics ~common f =
Fiber.finalize f ~finally:(fun () ->
let duration = Unix.gettimeofday () -. start_time in
(if Common.print_metrics common then
let gc_stat = Gc.quick_stat () in
Console.print_user_message
(User_message.make
([ Pp.textf "%s" (Memo.Perf_counters.report_for_current_run ())
; Pp.textf "(%.2fs total, %.1fM heap words)" duration
(float_of_int gc_stat.heap_words /. 1_000_000.)
; Pp.text "Timers:"
]
@ List.map
~f:
(fun (timer, { Metrics.Timer.Measure.cumulative_time; count })
->
Pp.textf "%s - time spent = %.2fs, count = %d" timer
cumulative_time count)
(String.Map.to_list (Metrics.Timer.aggregated_timers ())))));
let gc_stat = Gc.quick_stat () in
Console.print_user_message
(User_message.make
([ Pp.textf "%s" (Memo.Perf_counters.report_for_current_run ())
; Pp.textf "(%.2fs total, %.1fM heap words)" duration
(float_of_int gc_stat.heap_words /. 1_000_000.)
; Pp.text "Timers:"
]
@ List.map
~f:
(fun (timer, { Metrics.Timer.Measure.cumulative_time; count }) ->
Pp.textf "%s - time spent = %.2fs, count = %d" timer
cumulative_time count)
(String.Map.to_list (Metrics.Timer.aggregated_timers ())))));
Fiber.return ())

let run_build_system ~common ~request =
Expand Down
4 changes: 1 addition & 3 deletions bin/cache.ml
Original file line number Diff line number Diff line change
Expand Up @@ -84,9 +84,7 @@ let term =
in
match mode with
| Some Trim -> `Ok (trim ~trimmed_size ~size)
| Some Start_deprecated
| Some Stop_deprecated ->
deprecated_error ()
| Some Start_deprecated | Some Stop_deprecated -> deprecated_error ()
| None -> `Help (`Pager, Some name)

let command = (term, info)
49 changes: 14 additions & 35 deletions bin/common.ml
Original file line number Diff line number Diff line change
Expand Up @@ -87,21 +87,17 @@ let normalize_path path =
if Sys.win32 then
let src = Path.External.to_string path in
let is_letter = function
| 'a' .. 'z'
| 'A' .. 'Z' ->
true
| 'a' .. 'z' | 'A' .. 'Z' -> true
| _ -> false
in
if String.length src >= 2 && is_letter src.[0] && src.[1] = ':' then (
let dst = Bytes.create (String.length src) in
Bytes.set dst 0 (Char.uppercase_ascii src.[0]);
Bytes.blit_string ~src ~src_pos:1 ~dst ~dst_pos:1
~len:(String.length src - 1);
Path.External.of_string (Bytes.unsafe_to_string dst)
) else
path
else
path
Path.External.of_string (Bytes.unsafe_to_string dst))
else path
else path

let print_entering_message c =
let cwd = Path.to_absolute_filename Path.root in
Expand All @@ -123,9 +119,7 @@ let print_entering_message c =
| true -> (
let descendant_simple p ~of_ =
match String.drop_prefix p ~prefix:of_ with
| None
| Some "" ->
None
| None | Some "" -> None
| Some s -> Some (String.drop s 1)
in
match descendant_simple cwd ~of_:Fpath.initial_cwd with
Expand All @@ -135,10 +129,8 @@ let print_entering_message c =
| None -> cwd
| Some s ->
let rec loop acc dir =
if dir = Filename.current_dir_name then
acc
else
loop (Filename.concat acc "..") (Filename.dirname dir)
if dir = Filename.current_dir_name then acc
else loop (Filename.concat acc "..") (Filename.dirname dir)
in
loop ".." (Filename.dirname s)))
in
Expand Down Expand Up @@ -206,10 +198,7 @@ let init ?log_file c =
Clflags.always_show_command_line := c.always_show_command_line;
Clflags.ignore_promoted_rules := c.ignore_promoted_rules;
Clflags.on_missing_dune_project_file :=
if c.require_dune_project_file then
Error
else
Warn;
if c.require_dune_project_file then Error else Warn;
Dune_util.Log.info
[ Pp.textf "Workspace root: %s"
(Path.to_absolute_filename Path.root |> String.maybe_quoted)
Expand Down Expand Up @@ -306,8 +295,7 @@ let build_info =
pr "statically linked libraries:";
let longest = String.longest_map libs ~f:fst in
List.iter libs ~f:(fun (name, v) -> pr "- %-*s %s" longest name v));
exit 0
)
exit 0)

module Options_implied_by_dash_p = struct
type t =
Expand Down Expand Up @@ -352,10 +340,8 @@ module Options_implied_by_dash_p = struct
| No_config -> Dune_config.Partial.empty
| This fname -> Dune_config.load_config_file fname
| Default ->
if Dune_util.Config.inside_dune then
Dune_config.Partial.empty
else
Dune_config.load_user_config_file ()
if Dune_util.Config.inside_dune then Dune_config.Partial.empty
else Dune_config.load_user_config_file ()

let packages =
let parser s =
Expand Down Expand Up @@ -830,10 +816,7 @@ let term ~default_root_is_cwd =
"Instead of terminating build after completion, wait \
continuously for file changes.")
in
if watch then
Some Watch_mode_config.Eager
else
None)
if watch then Some Watch_mode_config.Eager else None)
(let+ watch =
Arg.(
value & flag
Expand All @@ -842,10 +825,7 @@ let term ~default_root_is_cwd =
"Similar to [--watch], but only start a build when \
instructed externally by an RPC.")
in
if watch then
Some Watch_mode_config.Passive
else
None)
if watch then Some Watch_mode_config.Passive else None)
in
match res with
| None -> Watch_mode_config.No
Expand Down Expand Up @@ -1018,8 +998,7 @@ let term ~default_root_is_cwd =
if store_digest_preimage then Dune_engine.Reversible_digest.enable ();
if print_metrics then (
Memo.Perf_counters.enable ();
Metrics.enable ()
);
Metrics.enable ());
{ debug_dep_path
; debug_findlib
; debug_backtraces
Expand Down
9 changes: 3 additions & 6 deletions bin/describe.ml
Original file line number Diff line number Diff line change
Expand Up @@ -215,8 +215,7 @@ module Crawl = struct
>>= Dir_contents.ocaml
>>| Ml_sources.modules ~for_:(Library name)
>>| modules ~obj_dir
else
Memo.Build.return []
else Memo.Build.return []
in
let include_dirs = Obj_dir.all_cmis obj_dir in
let lib_descr =
Expand Down Expand Up @@ -295,8 +294,7 @@ module Opam_files = struct
let template =
if Path.exists template_file then
Some (template_file, Io.read_file template_file)
else
None
else None
in
Dune_rules.Opam_create.generate project pkg ~template
in
Expand Down Expand Up @@ -377,8 +375,7 @@ module Lang = struct
& info [ "lang" ] ~docv:"VERSION"
~doc:"Behave the same as this version of Dune.")
in
if v = (0, 1) then
`Ok v
if v = (0, 1) then `Ok v
else
let msg =
let pp =
Expand Down
25 changes: 8 additions & 17 deletions bin/dune_init.ml
Original file line number Diff line number Diff line change
Expand Up @@ -49,9 +49,7 @@ module File = struct
let make_text path name content = Text { path; name; content }

let full_path = function
| Dune { path; name; _ }
| Text { path; name; _ } ->
Path.relative path name
| Dune { path; name; _ } | Text { path; name; _ } -> Path.relative path name

(** Inspection and manipulation of stanzas in a file *)
module Stanza = struct
Expand Down Expand Up @@ -124,8 +122,8 @@ module File = struct
(* Stanza *)

let create_dir path =
try Path.mkdir_p path with
| Unix.Unix_error (EACCES, _, _) ->
try Path.mkdir_p path
with Unix.Unix_error (EACCES, _, _) ->
User_error.raise
[ Pp.textf
"A project directory cannot be created or accessed: Lacking \
Expand All @@ -137,8 +135,7 @@ module File = struct
let name = "dune" in
let full_path = Path.relative path name in
let content =
if not (Path.exists full_path) then
[]
if not (Path.exists full_path) then []
else
match Format_dune_lang.parse_file (Some full_path) with
| Format_dune_lang.Sexps content -> content
Expand All @@ -162,10 +159,8 @@ module File = struct
match f with
| Dune f -> Ok (write_dune_file f)
| Text f ->
if Path.exists path then
Error path
else
Ok (Io.write_file ~binary:false path f.content)
if Path.exists path then Error path
else Ok (Io.write_file ~binary:false path f.content)
end

(** The context in which the initialization is executed *)
Expand Down Expand Up @@ -315,10 +310,7 @@ module Component = struct
|> Cst.concrete (* Package as a list CSTs *) |> List.singleton

let add_to_list_set elem set =
if List.mem ~equal:Dune_lang.Atom.equal set elem then
set
else
elem :: set
if List.mem ~equal:Dune_lang.Atom.equal set elem then set else elem :: set

let public_name_field ~default = function
| (None : Options.public_name option) -> []
Expand All @@ -332,8 +324,7 @@ module Component = struct

let library (common : Options.Common.t) (options : Options.Library.t) =
let common, inline_tests =
if not options.inline_tests then
(common, [])
if not options.inline_tests then (common, [])
else
let pps =
add_to_list_set
Expand Down
Loading

0 comments on commit 065466c

Please sign in to comment.