Skip to content
Closed
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
2 changes: 1 addition & 1 deletion bin/build.ml
Original file line number Diff line number Diff line change
Expand Up @@ -227,7 +227,7 @@ let build =
let open Fiber.O in
Rpc.Rpc_common.fire_request
~name:"build"
~wait:true
~wait:false
~lock_held_by
builder
Dune_rpc_impl.Decl.build
Expand Down
2 changes: 1 addition & 1 deletion bin/exec.ml
Original file line number Diff line number Diff line change
Expand Up @@ -229,7 +229,7 @@ let build_prog_via_rpc_if_necessary ~dir ~no_rebuild builder lock_held_by prog =
let open Fiber.O in
Rpc.Rpc_common.fire_request
~name:"build"
~wait:true
~wait:false
~lock_held_by
builder
Dune_rpc_impl.Decl.build
Expand Down
2 changes: 1 addition & 1 deletion bin/fmt.ml
Original file line number Diff line number Diff line change
Expand Up @@ -48,7 +48,7 @@ let run_fmt_command ~common ~config ~preview builder =
Scheduler.no_build_no_rpc ~config (fun () ->
Rpc.Rpc_common.fire_request
~name:"format"
~wait:true
~wait:false
~warn_forwarding:false
~lock_held_by
builder
Expand Down
2 changes: 1 addition & 1 deletion bin/promotion.ml
Original file line number Diff line number Diff line change
Expand Up @@ -61,7 +61,7 @@ module Apply = struct
let open Fiber.O in
Rpc.Rpc_common.fire_request
~name:"promote_many"
~wait:true
~wait:false
~lock_held_by
builder
Dune_rpc_private.Procedures.Public.promote_many
Expand Down
32 changes: 30 additions & 2 deletions bin/rpc/rpc_common.ml
Original file line number Diff line number Diff line change
Expand Up @@ -122,6 +122,18 @@ let send_request ~f connection name =
~f
;;

let raise_rpc_not_found ~lock_held_by =
User_error.raise
(match lock_held_by with
| Dune_util.Global_lock.Lock_held_by.Unknown -> [ Pp.text "RPC server not running." ]
| Pid_from_lockfile pid ->
[ Pp.textf
"Another dune instance (pid: %d) has the build directory locked but is not \
running an RPC server."
pid
])
;;

let fire_request
~name
~wait
Expand All @@ -132,7 +144,15 @@ let fire_request
arg
=
let open Fiber.O in
let* connection = establish_client_session ~wait in
let* connection =
Fiber.map_reduce_errors
(module Monoid.Unit)
~on_error:(fun _ -> Fiber.return ())
(fun () -> establish_client_session ~wait)
>>| function
| Ok conn -> conn
| Error () -> raise_rpc_not_found ~lock_held_by
in
if should_warn ~warn_forwarding builder then warn_ignore_arguments lock_held_by;
send_request connection name ~f:(fun client -> request_exn client request arg)
;;
Expand All @@ -147,7 +167,15 @@ let fire_notification
arg
=
let open Fiber.O in
let* connection = establish_client_session ~wait in
let* connection =
Fiber.map_reduce_errors
(module Monoid.Unit)
~on_error:(fun _ -> Fiber.return ())
(fun () -> establish_client_session ~wait)
>>| function
| Ok conn -> conn
| Error () -> raise_rpc_not_found ~lock_held_by
in
if should_warn ~warn_forwarding builder then warn_ignore_arguments lock_held_by;
send_request connection name ~f:(fun client -> notify_exn client notification arg)
;;
Expand Down
2 changes: 1 addition & 1 deletion bin/tools/tools_common.ml
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,7 @@ let build_dev_tool_via_rpc builder lock_held_by dev_tool =
let open Fiber.O in
Rpc.Rpc_common.fire_request
~name:"build"
~wait:true
~wait:false
~lock_held_by
builder
Dune_rpc_impl.Decl.build
Expand Down
100 changes: 100 additions & 0 deletions test/blackbox-tests/test-cases/build-lock-no-rpc.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,100 @@
Test that dune fails fast when the build lock is held but no RPC server is
available. This is a regression test for
https://github.com/ocaml/dune/issues/12900

$ cat > dune-project <<EOF
> (lang dune 3.18)
> EOF

$ cat > dune <<EOF
> (executable (name foo))
> EOF

$ cat > foo.ml <<EOF
> let () = print_endline "hello"
> EOF

Helper to run a command while holding the build lock without an RPC server:

$ with_build_lock_held() {
> mkdir -p _build
> (
> flock -x 9
> printf '1' > _build/.lock
> "$@"
> ) 9>_build/.lock
> }

Hold the lock without running an RPC server, then try various commands.
They should all fail immediately instead of hanging.

$ with_build_lock_held dune build
Error: Another dune instance (pid: 1) has the build directory locked but is
not running an RPC server.
[1]

$ with_build_lock_held dune exec ./foo.exe
Error: Another dune instance (pid: 1) has the build directory locked but is
not running an RPC server.
[1]

$ with_build_lock_held dune fmt
Error: Another dune instance (pid: 1) has the build directory locked but is
not running an RPC server.
[1]

$ with_build_lock_held dune promote
Error: Another dune instance (pid: 1) has the build directory locked but is
not running an RPC server.
[1]

$ with_build_lock_held dune runtest
Error: Another dune instance (pid: 1) has the build directory locked but is
not running an RPC server.
[1]

We are not starting an RPC server for clean, but we do care if the lock is
held.

$ with_build_lock_held dune clean
Error: A running dune (pid: 1) instance has locked the build directory. If
this is not the case, please delete "_build/.lock".
[1]

Explicit RPC commands do not check the lock first, so they get a simpler error:

$ dune rpc ping
Error: RPC server not running.
[1]

$ dune rpc build
Error: RPC server not running.
[1]

$ dune shutdown
Error: RPC server not running.
[1]

$ dune diagnostics
Error: RPC server not running.
[1]

Commands that start their own RPC server will fail when trying to acquire the
lock:

$ with_build_lock_held dune utop . 2>&1 | head -3
Error: A running dune (pid: 1) instance has locked the build directory. If
this is not the case, please delete "_build/.lock".

$ with_build_lock_held dune ocaml top 2>&1 | head -3
Error: A running dune (pid: 1) instance has locked the build directory. If
this is not the case, please delete "_build/.lock".

$ with_build_lock_held dune printenv 2>&1 | head -3
Error: A running dune (pid: 1) instance has locked the build directory. If
this is not the case, please delete "_build/.lock".

$ with_build_lock_held dune describe workspace 2>&1 | head -3
Error: A running dune (pid: 1) instance has locked the build directory. If
this is not the case, please delete "_build/.lock".

5 changes: 5 additions & 0 deletions test/blackbox-tests/test-cases/dune
Original file line number Diff line number Diff line change
Expand Up @@ -131,3 +131,8 @@
(applies_to hidden-deps-unsupported)
(enabled_if
(< %{ocaml_version} 5.2.0)))

(cram
(applies_to build-lock-no-rpc)
(deps %{bin:flock})
(timeout 5))
Loading