Skip to content

Commit

Permalink
fix: allow shadowing builtins
Browse files Browse the repository at this point in the history
Previously, builtins would always shadow librares in findlib

Signed-off-by: Rudi Grinberg <me@rgrinberg.com>

<!-- ps-id: 5ee1186b-105e-4b69-95fe-4d770cfef55b -->
  • Loading branch information
rgrinberg committed Sep 10, 2023
1 parent eeb1307 commit fc68fa9
Show file tree
Hide file tree
Showing 6 changed files with 58 additions and 18 deletions.
21 changes: 9 additions & 12 deletions src/dune_rules/findlib.ml
Original file line number Diff line number Diff line change
Expand Up @@ -401,19 +401,16 @@ end = struct
;;

let lookup_and_load (db : t) name =
match Package.Name.Map.find db.builtins name with
| Some meta ->
(* XXX DUNE4 weird to favor these hardcoded packages over user possibly
user defined libraries *)
load_builtin db meta >>| Result.ok
Monad.List.find_map db.paths ~f:(lookup db name)
>>= function
| Some m -> Monad.return m
| None ->
Monad.List.find_map db.paths ~f:(lookup db name)
>>| (function
| Some m -> m
| None ->
(match Package.Name.to_string name with
| "dune" -> Ok builtin_for_dune
| _ -> Error Unavailable_reason.Not_found))
(match Package.Name.to_string name with
| "dune" -> Monad.return (Ok builtin_for_dune)
| _ ->
(match Package.Name.Map.find db.builtins name with
| None -> Monad.return (Error Unavailable_reason.Not_found)
| Some meta -> load_builtin db meta >>| Result.ok))
;;
end

Expand Down
23 changes: 20 additions & 3 deletions test/blackbox-tests/test-cases/describe/describe-workspace-pp.t
Original file line number Diff line number Diff line change
Expand Up @@ -104,7 +104,8 @@ not stable across different setups.
(executables
((names (exe))
(requires
(c9367091ddd9a70d99fc22ede348f17c
(c39d8e11db2363236e69af7750ce7b9a
c9367091ddd9a70d99fc22ede348f17c
1f2b5eb300ea716920494385a31bb5fb
5014e215e204cf8da6c32644cda1b31e
249b2edaf3cc552a247667041bb5f015
Expand All @@ -125,11 +126,19 @@ not stable across different setups.
(cmt (_build/default/exe/.exe.eobjs/byte/dune__exe__Exe.cmt))
(cmti ()))))
(include_dirs (_build/default/exe/.exe.eobjs/byte))))
(library
((name compiler-libs)
(uid c39d8e11db2363236e69af7750ce7b9a)
(local false)
(requires ())
(source_dir /FINDLIB/ocaml/compiler-libs)
(modules ())
(include_dirs (/FINDLIB/ocaml/compiler-libs))))
(library
((name compiler-libs.common)
(uid c9367091ddd9a70d99fc22ede348f17c)
(local false)
(requires ())
(requires (c39d8e11db2363236e69af7750ce7b9a))
(source_dir /FINDLIB/ocaml/compiler-libs)
(modules ())
(include_dirs (/FINDLIB/ocaml/compiler-libs))))
Expand Down Expand Up @@ -266,11 +275,19 @@ not stable across different setups.
$ dune describe workspace --lang 0.1 --sanitize-for-tests --with-pps lib
((root /WORKSPACE_ROOT)
(build_context _build/default)
(library
((name compiler-libs)
(uid c39d8e11db2363236e69af7750ce7b9a)
(local false)
(requires ())
(source_dir /FINDLIB/ocaml/compiler-libs)
(modules ())
(include_dirs (/FINDLIB/ocaml/compiler-libs))))
(library
((name compiler-libs.common)
(uid c9367091ddd9a70d99fc22ede348f17c)
(local false)
(requires ())
(requires (c39d8e11db2363236e69af7750ce7b9a))
(source_dir /FINDLIB/ocaml/compiler-libs)
(modules ())
(include_dirs (/FINDLIB/ocaml/compiler-libs))))
Expand Down
20 changes: 18 additions & 2 deletions test/blackbox-tests/test-cases/describe/describe.t
Original file line number Diff line number Diff line change
Expand Up @@ -377,11 +377,19 @@ not stable across different setups.
(source_dir /FINDLIB/cmdliner)
(modules ())
(include_dirs (/FINDLIB/cmdliner))))
(library
((name compiler-libs)
(uid c39d8e11db2363236e69af7750ce7b9a)
(local false)
(requires ())
(source_dir /FINDLIB/ocaml/compiler-libs)
(modules ())
(include_dirs (/FINDLIB/ocaml/compiler-libs))))
(library
((name compiler-libs.common)
(uid c9367091ddd9a70d99fc22ede348f17c)
(local false)
(requires ())
(requires (c39d8e11db2363236e69af7750ce7b9a))
(source_dir /FINDLIB/ocaml/compiler-libs)
(modules ())
(include_dirs (/FINDLIB/ocaml/compiler-libs))))
Expand Down Expand Up @@ -909,11 +917,19 @@ not stable across different setups.
(source_dir /FINDLIB/cmdliner)
(modules ())
(include_dirs (/FINDLIB/cmdliner))))
(library
((name compiler-libs)
(uid c39d8e11db2363236e69af7750ce7b9a)
(local false)
(requires ())
(source_dir /FINDLIB/ocaml/compiler-libs)
(modules ())
(include_dirs (/FINDLIB/ocaml/compiler-libs))))
(library
((name compiler-libs.common)
(uid c9367091ddd9a70d99fc22ede348f17c)
(local false)
(requires ())
(requires (c39d8e11db2363236e69af7750ce7b9a))
(source_dir /FINDLIB/ocaml/compiler-libs)
(modules ())
(include_dirs (/FINDLIB/ocaml/compiler-libs))))
Expand Down
4 changes: 4 additions & 0 deletions test/blackbox-tests/test-cases/merlin/instrumentation.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -40,12 +40,14 @@ up a project with instrumentation and testing checking the merlin config.
Foo
((STDLIB /OCAMLC_WHERE)
(EXCLUDE_QUERY_DIR)
(B lib/bytes)
(B lib/findlib)
(B /OCAMLC_WHERE)
(B
$TESTCASE_ROOT/_build/default/lib/.foo.objs/byte)
(B
$TESTCASE_ROOT/_build/default/ppx/.hello.objs/byte)
(S lib/bytes)
(S lib/findlib)
(S /OCAMLC_WHERE)
(S
Expand All @@ -58,12 +60,14 @@ up a project with instrumentation and testing checking the merlin config.
Privmod
((STDLIB /OCAMLC_WHERE)
(EXCLUDE_QUERY_DIR)
(B lib/bytes)
(B lib/findlib)
(B /OCAMLC_WHERE)
(B
$TESTCASE_ROOT/_build/default/lib/.foo.objs/byte)
(B
$TESTCASE_ROOT/_build/default/ppx/.hello.objs/byte)
(S lib/bytes)
(S lib/findlib)
(S /OCAMLC_WHERE)
(S
Expand Down
6 changes: 6 additions & 0 deletions test/blackbox-tests/test-cases/merlin/merlin-tests.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -9,12 +9,14 @@ CRAM sanitization
X
((STDLIB /OCAMLC_WHERE)
(EXCLUDE_QUERY_DIR)
(B lib/bytes)
(B lib/findlib)
(B /OCAMLC_WHERE)
(B
$TESTCASE_ROOT/_build/default/exe/.x.eobjs/byte)
(B
$TESTCASE_ROOT/_build/default/lib/.foo.objs/public_cmi)
(S lib/bytes)
(S lib/findlib)
(S /OCAMLC_WHERE)
(S
Expand Down Expand Up @@ -64,10 +66,12 @@ CRAM sanitization
Foo
((STDLIB /OCAMLC_WHERE)
(EXCLUDE_QUERY_DIR)
(B lib/bytes)
(B lib/findlib)
(B /OCAMLC_WHERE)
(B
$TESTCASE_ROOT/_build/default/lib/.foo.objs/byte)
(S lib/bytes)
(S lib/findlib)
(S /OCAMLC_WHERE)
(S
Expand All @@ -84,10 +88,12 @@ CRAM sanitization
Privmod
((STDLIB /OCAMLC_WHERE)
(EXCLUDE_QUERY_DIR)
(B lib/bytes)
(B lib/findlib)
(B /OCAMLC_WHERE)
(B
$TESTCASE_ROOT/_build/default/lib/.foo.objs/byte)
(S lib/bytes)
(S lib/findlib)
(S /OCAMLC_WHERE)
(S
Expand Down
2 changes: 1 addition & 1 deletion test/expect-tests/findlib_tests.ml
Original file line number Diff line number Diff line change
Expand Up @@ -109,7 +109,7 @@ let%expect_test "builtins" =
print_pkg_archives "str";
[%expect
{|
Hidden { byte = [ "stdlib/str.cma" ]; native = [ "stdlib/str.cmxa" ] } |}];
Available { byte = []; native = [] } |}];
print_pkg_archives "dynlink";
[%expect
{|
Expand Down

0 comments on commit fc68fa9

Please sign in to comment.