@@ -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-
148142let 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. *)
163157let 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
179173let 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
0 commit comments