Skip to content

Commit

Permalink
fix(pkg): dune fmt missing extra files from the locks.
Browse files Browse the repository at this point in the history
Signed-off-by: Alpha DIALLO <[email protected]>
  • Loading branch information
moyodiallo committed Oct 3, 2024
1 parent 57f435d commit ad7c1f2
Show file tree
Hide file tree
Showing 2 changed files with 59 additions and 37 deletions.
69 changes: 50 additions & 19 deletions bin/build_cmd.ml
Original file line number Diff line number Diff line change
Expand Up @@ -82,12 +82,40 @@ let run_build_system ~common ~request =
Fiber.return ())
;;

let run_build_command_poll_eager ~(common : Common.t) ~config ~request : unit =
let lock_ocamlformat () =
if Lazy.force Lock_dev_tool.is_enabled
then
(* Note that generating the ocamlformat lockdir here means
that it will be created when a user runs `dune fmt` but not
when a user runs `dune build @fmt`. It's important that
this logic remain outside of `dune build`, as `dune
build` is intended to only build targets, and generating
a lockdir is not building a target. *)
Lock_dev_tool.lock_ocamlformat () |> Memo.run
else Fiber.return ()
;;

let run_build_command_poll_eager
~with_lock_ocamlformat
~(common : Common.t)
~config
~request
: unit
=
let open Fiber.O in
Scheduler.go_with_rpc_server_and_console_status_reporting ~common ~config (fun () ->
Scheduler.Run.poll (run_build_system ~common ~request))
Scheduler.Run.poll
(let* () = if with_lock_ocamlformat then lock_ocamlformat () else Fiber.return () in
run_build_system ~common ~request))
;;

let run_build_command_poll_passive ~(common : Common.t) ~config ~request:_ : unit =
let run_build_command_poll_passive
~with_lock_ocamlformat
~(common : Common.t)
~config
~request:_
: unit
=
(* CR-someday aalekseyev: It would've been better to complain if [request] is
non-empty, but we can't check that here because [request] is a function.*)
let open Fiber.O in
Expand All @@ -99,16 +127,20 @@ let run_build_command_poll_passive ~(common : Common.t) ~config ~request:_ : uni
Scheduler.go_with_rpc_server_and_console_status_reporting ~common ~config (fun () ->
Scheduler.Run.poll_passive
~get_build_request:
(let+ (Build (targets, ivar)) = Dune_rpc_impl.Server.pending_build_action rpc in
(let* () =
if with_lock_ocamlformat then lock_ocamlformat () else Fiber.return ()
in
let+ (Build (targets, ivar)) = Dune_rpc_impl.Server.pending_build_action rpc in
let request setup =
Target.interpret_targets (Common.root common) config setup targets
in
run_build_system ~common ~request, ivar))
;;

let run_build_command_once ~(common : Common.t) ~config ~request =
let run_build_command_once ~with_lock_ocamlformat ~(common : Common.t) ~config ~request =
let open Fiber.O in
let once () =
let* () = if with_lock_ocamlformat then lock_ocamlformat () else Fiber.return () in
let+ res = run_build_system ~common ~request in
match res with
| Error `Already_reported -> raise Dune_util.Report_error.Already_reported
Expand All @@ -122,6 +154,18 @@ let run_build_command ~(common : Common.t) ~config ~request =
| Yes Eager -> run_build_command_poll_eager
| Yes Passive -> run_build_command_poll_passive
| No -> run_build_command_once)
~with_lock_ocamlformat:false
~common
~config
~request
;;

let run_build_command_fmt ~(common : Common.t) ~config ~request =
(match Common.watch common with
| Yes Eager -> run_build_command_poll_eager
| Yes Passive -> run_build_command_poll_passive
| No -> run_build_command_once)
~with_lock_ocamlformat:true
~common
~config
~request
Expand Down Expand Up @@ -231,24 +275,11 @@ let fmt =
in
let common, config = Common.init builder in
let request (setup : Import.Main.build_system) =
let open Action_builder.O in
let* () =
if Lazy.force Lock_dev_tool.is_enabled
then
(* Note that generating the ocamlformat lockdir here means
that it will be created when a user runs `dune fmt` but not
when a user runs `dune build @fmt`. It's important that
this logic remain outside of `dune build`, as `dune
build` is intended to only build targets, and generating
a lockdir is not building a target. *)
Action_builder.of_memo (Lock_dev_tool.lock_ocamlformat ())
else Action_builder.return ()
in
let dir = Path.(relative root) (Common.prefix_target common ".") in
Alias.in_dir ~name:Dune_rules.Alias.fmt ~recursive:true ~contexts:setup.contexts dir
|> Alias.request
in
run_build_command ~common ~config ~request
run_build_command_fmt ~common ~config ~request
in
Cmd.v (Cmd.info "fmt" ~doc ~man ~envs:Common.envs) term
;;
Original file line number Diff line number Diff line change
Expand Up @@ -3,17 +3,21 @@ ocamlformat and its dependencies during the same run of the "dune fmt" command.
loaded before the lock files are produced, this is why any 'patch' file inside
'dev-tools.locks/ocmalformat' is not copied inside the 'build' directory when a rule depends on it.

In the case of this issue, there is a rule that depends on an 'patch' file in order to copy the file
The issue was that there is a rule that depends on an 'patch' file in order to copy the file
inside '_private/default/..' directory, since the file could not be copied, the rule is not activated.
So it fails when 'dune' trying to apply the patch. After any follwing run of 'dune fmt', it works
because the 'patch' file is already present.

The issue is now fixed.


$ . ./helpers.sh
$ mkrepo

Make a fake ocamlformat:
$ make_fake_ocamlformat "0.1"

A patch that changes the version from "0.1" to "0.26.2":
$ cat > patch-for-ocamlformat.patch <<EOF
> diff a/ocamlformat.ml b/ocamlformat.ml
> --- a/ocamlformat.ml
Expand Down Expand Up @@ -55,29 +59,16 @@ Make the ocamlformat opam package which uses a patch:
Make a project that uses the fake ocamlformat:
$ make_project_with_dev_tool_lockdir
First run of 'dune fmt'
$ DUNE_CONFIG__LOCK_DEV_TOOL=enabled dune fmt 2>&1 | sed -E 's#.*.sandbox/[^/]+#.sandbox/$SANDBOX#g'
First run of 'dune fmt' is supposed to format the fail.
$ DUNE_CONFIG__LOCK_DEV_TOOL=enabled dune fmt
Solution for dev-tools.locks/ocamlformat:
- ocamlformat.0.26.2
Error:
.sandbox/$SANDBOX/_private/default/.dev-tool/ocamlformat/ocamlformat/source/patch-for-ocamlformat.patch:
No such file or directory
-> required by
_build/_private/default/.dev-tool/ocamlformat/ocamlformat/target/bin/ocamlformat
-> required by _build/default/.formatted/foo.ml
-> required by alias .formatted/fmt
-> required by alias fmt

The second run will works because the 'patch' is already in the source.
$ ls dev-tools.locks/ocamlformat/ocamlformat.files
patch-for-ocamlformat.patch

Second run of 'dune fmt'
$ DUNE_CONFIG__LOCK_DEV_TOOL=enabled dune fmt
File "foo.ml", line 1, characters 0-0:
Error: Files _build/default/foo.ml and _build/default/.formatted/foo.ml
differ.
Promoting _build/default/.formatted/foo.ml to foo.ml.
[1]

The foo.ml file is now formatted with the patched version of ocamlformat.
$ cat foo.ml
formatted with version 0.26.2

0 comments on commit ad7c1f2

Please sign in to comment.