Skip to content

Commit eb8644f

Browse files
Enable dev-tools when lock dir is enabled
1 parent 5c16e40 commit eb8644f

File tree

10 files changed

+22
-52
lines changed

10 files changed

+22
-52
lines changed

bin/ocaml/utop.ml

Lines changed: 3 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -51,11 +51,9 @@ let term =
5151
| true ->
5252
let* () = Build_system.build_file utop_exe in
5353
let* () = lock_utop_if_dev_tool_enabled () in
54-
let* utop_dev_tool_lock_dir_exists =
55-
Memo.Lazy.force Utop.utop_dev_tool_lock_dir_exists
56-
in
54+
let* lock_dir_enabled = Dune_rules.Lock_dir.enabled in
5755
let* () =
58-
if utop_dev_tool_lock_dir_exists
56+
if lock_dir_enabled
5957
then
6058
(* Generate the custom findlib.conf file needed when utop is run
6159
as a dev tool. *)
@@ -80,7 +78,7 @@ let term =
8078
~init:env
8179
in
8280
let env =
83-
if utop_dev_tool_lock_dir_exists
81+
if lock_dir_enabled
8482
then
8583
(* If there's a utop lockdir then dune will have built utop as a
8684
dev tool. In order for it to run correctly dune needed to

bin/pkg/pkg_enabled.ml

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,7 @@ let term =
77
Memo.run
88
@@
99
let open Memo.O in
10-
let+ workspace = Workspace.workspace () in
10+
let* workspace = Workspace.workspace () in
1111
let lock_dir_paths =
1212
Pkg_common.Lock_dirs_arg.lock_dirs_of_workspace
1313
Pkg_common.Lock_dirs_arg.all
@@ -19,7 +19,8 @@ let term =
1919
in
2020
(* CR-Leonidas-from-XIV: change this logic when we stop detecting lock
2121
directories in the source tree *)
22-
let enabled = any_lockdir_exists || workspace.config.pkg_enabled in
22+
let+ lock_dir_enabled = Dune_rules.Lock_dir.enabled in
23+
let enabled = any_lockdir_exists || lock_dir_enabled in
2324
match enabled with
2425
| true -> ()
2526
| false -> exit 1)

src/dune_pkg/lock_dir.ml

Lines changed: 0 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -1087,21 +1087,12 @@ let create_latest_version
10871087
let dev_tool_locks_name = "dev-tools.locks"
10881088
let dev_tools_path = Path.Build.(relative root dev_tool_locks_name)
10891089

1090-
(* CR-Leonidas-from-XIV: remove once obsoleted *)
1091-
let dev_tools_source_path = Path.Source.(relative root dev_tool_locks_name)
1092-
10931090
let dev_tool_lock_dir_path dev_tool =
10941091
Path.Build.relative
10951092
dev_tools_path
10961093
(Package_name.to_string (Dev_tool.package_name dev_tool))
10971094
;;
10981095

1099-
let dev_tool_lock_dir_source_path dev_tool =
1100-
Path.Source.relative
1101-
dev_tools_source_path
1102-
(Package_name.to_string (Dev_tool.package_name dev_tool))
1103-
;;
1104-
11051096
let default_path = Path.Build.(relative root "dune.lock")
11061097
let metadata_filename = "lock.dune"
11071098

src/dune_pkg/lock_dir.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -137,7 +137,7 @@ val dev_tool_lock_dir_path : Dev_tool.t -> Path.Build.t
137137
(** Temporary hack to get the path of a dev tool lock directory in the source
138138
tree. Future versions will probably handle this differently and this
139139
function should be removed *)
140-
val dev_tool_lock_dir_source_path : Dev_tool.t -> Path.Source.t
140+
(* val dev_tool_lock_dir_source_path : Dev_tool.t -> Path.Source.t *)
141141

142142
module Metadata : Dune_sexp.Versioned_file.S with type data := unit
143143

src/dune_rules/fetch_rules.ml

Lines changed: 1 addition & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -188,11 +188,7 @@ let find_checksum, find_url =
188188
Dune_pkg.Dev_tool.all
189189
~init:(Checksum.Map.empty, Digest.Map.empty)
190190
~f:(fun acc dev_tool ->
191-
Fs_memo.dir_exists
192-
(In_source_dir (Dune_pkg.Lock_dir.dev_tool_lock_dir_source_path dev_tool))
193-
>>= function
194-
| false -> Memo.return acc
195-
| true -> Lock_dir.of_dev_tool dev_tool >>| add_checksums_and_urls acc)
191+
Lock_dir.of_dev_tool dev_tool >>| add_checksums_and_urls acc)
196192
in
197193
Per_context.list ()
198194
>>= Memo.parallel_map ~f:Lock_dir.get

src/dune_rules/lock_dir.ml

Lines changed: 7 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -143,6 +143,11 @@ let select_lock_dir lock_dir_selection =
143143
Workspace.Lock_dir_selection.eval lock_dir_selection ~dir:Path.Build.root ~f:expander
144144
;;
145145

146+
let enabled =
147+
let+ workspace = Workspace.workspace () in
148+
workspace.config.pkg_enabled
149+
;;
150+
146151
let get_path ctx =
147152
let* workspace = Workspace.workspace () in
148153
match
@@ -184,16 +189,8 @@ let get ctx = get_with_path ctx >>| Result.map ~f:snd
184189
let get_exn ctx = get ctx >>| User_error.ok_exn
185190

186191
let of_dev_tool dev_tool =
187-
let source_path, path =
188-
Dune_pkg.Lock_dir.(
189-
dev_tool_lock_dir_source_path dev_tool, dev_tool_lock_dir_path dev_tool)
190-
in
191-
Fs_memo.dir_exists (In_source_dir source_path)
192-
>>= function
193-
| true -> Load.load_exn path
194-
| false ->
195-
User_error.raise
196-
[ Pp.textf "%s does not exist" (Path.Build.to_string_maybe_quoted path) ]
192+
let path = dev_tool_lock_dir_path dev_tool in
193+
Load.load_exn path
197194
;;
198195

199196
let lock_dir_active ctx =

src/dune_rules/lock_dir.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -9,6 +9,7 @@ val get_exn : Context_name.t -> t Memo.t
99
val of_dev_tool : Dune_pkg.Dev_tool.t -> t Memo.t
1010
val lock_dir_active : Context_name.t -> bool Memo.t
1111
val get_path : Context_name.t -> Path.Build.t option Memo.t
12+
val enabled : bool Memo.t
1213

1314
module Sys_vars : sig
1415
type t =

src/dune_rules/odoc.ml

Lines changed: 2 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -254,11 +254,6 @@ let odoc_base_flags quiet build_dir =
254254
| Nonfatal -> S []
255255
;;
256256

257-
let odoc_dev_tool_lock_dir_exists () =
258-
let path = Dune_pkg.Lock_dir.dev_tool_lock_dir_source_path Odoc in
259-
Fs_memo.dir_exists (Path.Outside_build_dir.In_source_dir path)
260-
;;
261-
262257
let odoc_dev_tool_exe_path_building_if_necessary () =
263258
let open Action_builder.O in
264259
let path = Path.build (Pkg_dev_tool.exe_path Odoc) in
@@ -268,10 +263,8 @@ let odoc_dev_tool_exe_path_building_if_necessary () =
268263

269264
let odoc_program sctx dir =
270265
let open Action_builder.O in
271-
let* odoc_dev_tool_lock_dir_exists =
272-
Action_builder.of_memo (odoc_dev_tool_lock_dir_exists ())
273-
in
274-
match odoc_dev_tool_lock_dir_exists with
266+
let* odoc_dev_tool_enabled = Action_builder.of_memo Lock_dir.enabled in
267+
match odoc_dev_tool_enabled with
275268
| true -> odoc_dev_tool_exe_path_building_if_necessary ()
276269
| false ->
277270
Super_context.resolve_program

src/dune_rules/utop.ml

Lines changed: 4 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -139,12 +139,6 @@ let requires ~loc ~db ~libs =
139139
>>= Lib.closure ~linking:true
140140
;;
141141

142-
let utop_dev_tool_lock_dir_exists =
143-
Memo.Lazy.create (fun () ->
144-
let path = Dune_pkg.Lock_dir.dev_tool_lock_dir_source_path Utop in
145-
Fs_memo.dir_exists (Path.Outside_build_dir.In_source_dir path))
146-
;;
147-
148142
let utop_findlib_conf = Filename.concat utop_dir_basename "findlib.conf"
149143

150144
(* The lib directory of the utop package and of each of its dependencies within
@@ -161,8 +155,8 @@ let utop_ocamlpath = Memo.Lazy.create (fun () -> Pkg_rules.dev_tool_ocamlpath Ut
161155
we need to tell findlib where to look for libraries by means of a custom
162156
findlib.conf file. *)
163157
let findlib_conf sctx ~dir =
164-
let* lock_dir_exists = Memo.Lazy.force utop_dev_tool_lock_dir_exists in
165-
match lock_dir_exists with
158+
let* lock_dir_enabled = Lock_dir.enabled in
159+
match lock_dir_enabled with
166160
| false ->
167161
(* If there isn't lockdir don't create the findlib.conf rule. *)
168162
Memo.return ()
@@ -178,8 +172,8 @@ let findlib_conf sctx ~dir =
178172

179173
let lib_db sctx ~dir =
180174
let* scope = Scope.DB.find_by_dir dir in
181-
let* lock_dir_exists = Memo.Lazy.force utop_dev_tool_lock_dir_exists in
182-
match lock_dir_exists with
175+
let* lock_dir_enabled = Lock_dir.enabled in
176+
match lock_dir_enabled with
183177
| false -> Memo.return (Scope.libs scope)
184178
| true ->
185179
let* ocamlpath = Memo.Lazy.force utop_ocamlpath in

src/dune_rules/utop.mli

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,6 @@ val utop_exe : Filename.t
88

99
val utop_dir_basename : Filename.t
1010
val utop_findlib_conf : Filename.t
11-
val utop_dev_tool_lock_dir_exists : bool Memo.Lazy.t
1211
val libs_under_dir : Super_context.t -> db:Lib.DB.t -> dir:Path.t -> Lib.t list Memo.t
1312
val setup : Super_context.t -> dir:Path.Build.t -> unit Memo.t
1413

0 commit comments

Comments
 (0)