@@ -274,12 +274,13 @@ module Sanitize_for_tests = struct
274
274
let fake_workspace = lazy (Path.External. of_string " /WORKSPACE_ROOT" )
275
275
276
276
let sanitize_with_findlib ~findlib_paths path =
277
+ let path = Path. external_ path in
277
278
List. find_map findlib_paths ~f: (fun candidate ->
278
279
let open Option.O in
279
280
let * candidate = Path. as_external candidate in
280
281
(* if the path to rename is an external path, try to find the
281
282
OCaml root inside, and replace it with a fixed string *)
282
- let + without_prefix = Path.External. drop_prefix ~prefix: candidate path in
283
+ let + without_prefix = Path. drop_prefix ~prefix: ( Path. external_ candidate) path in
283
284
(* we have found the OCaml root path: let's replace it with a
284
285
constant string *)
285
286
Path.External. append_local (Lazy. force fake_findlib) without_prefix)
@@ -371,7 +372,9 @@ module Crawl = struct
371
372
372
373
(* Builds the list of modules *)
373
374
let modules ~obj_dir ~deps_of modules_ : Descr.Mod.t list Memo.t =
374
- Modules. fold_no_vlib ~init: (Memo. return [] ) modules_ ~f: (fun m macc ->
375
+ modules_
376
+ |> Modules.With_vlib. drop_vlib
377
+ |> Modules. fold ~init: (Memo. return [] ) ~f: (fun m macc ->
375
378
let * acc = macc in
376
379
let deps = deps_of m in
377
380
let + { Ocaml.Ml_kind.Dict. intf = deps_for_intf; impl = deps_for_impl }, _ =
@@ -389,11 +392,14 @@ module Crawl = struct
389
392
Scope.DB. find_by_project (Super_context. context sctx |> Context. name) project
390
393
in
391
394
let * modules_, obj_dir =
392
- Dir_contents. get sctx ~dir
393
- >> = Dir_contents. ocaml
394
- >> = Ml_sources. modules_and_obj_dir
395
- ~libs: (Scope. libs scope)
396
- ~for_: (Exe { first_exe })
395
+ let + modules_, obj_dir =
396
+ Dir_contents. get sctx ~dir
397
+ >> = Dir_contents. ocaml
398
+ >> = Ml_sources. modules_and_obj_dir
399
+ ~libs: (Scope. libs scope)
400
+ ~for_: (Exe { first_exe })
401
+ in
402
+ Modules.With_vlib. modules modules_, obj_dir
397
403
in
398
404
let * pp_map =
399
405
let + version =
@@ -454,11 +460,14 @@ module Crawl = struct
454
460
let * libs =
455
461
Scope.DB. find_by_dir (Path. as_in_build_dir_exn src_dir) >> | Scope. libs
456
462
in
457
- Dir_contents. get sctx ~dir: (Path. as_in_build_dir_exn src_dir)
458
- >> = Dir_contents. ocaml
459
- >> = Ml_sources. modules_and_obj_dir
460
- ~libs
461
- ~for_: (Library (Lib_info. lib_id info |> Lib_id. to_local_exn))
463
+ let + modules_, obj_dir_ =
464
+ Dir_contents. get sctx ~dir: (Path. as_in_build_dir_exn src_dir)
465
+ >> = Dir_contents. ocaml
466
+ >> = Ml_sources. modules_and_obj_dir
467
+ ~libs
468
+ ~for_: (Library (Lib_info. lib_id info |> Lib_id. to_local_exn))
469
+ in
470
+ Modules.With_vlib. modules modules_, obj_dir_
462
471
in
463
472
let * pp_map =
464
473
let + version =
0 commit comments