Skip to content

Commit

Permalink
Merge pull request #3144 from rgrinberg/fix-3143
Browse files Browse the repository at this point in the history
Fix creating dummy package
  • Loading branch information
rgrinberg authored Feb 15, 2020
2 parents cb4ccaf + fcb7027 commit 06defff
Show file tree
Hide file tree
Showing 8 changed files with 51 additions and 16 deletions.
28 changes: 19 additions & 9 deletions src/dune/findlib/findlib.ml
Original file line number Diff line number Diff line change
Expand Up @@ -184,7 +184,7 @@ module Loader : sig
val lookup_and_load :
db -> Package.Name.t -> (Dune_package.t, Unavailable_reason.t) result

val dummy_package : db -> Package.Name.t -> Dune_package.t
val dummy_package : db -> Lib_name.t -> Dune_package.t
end = struct
module Findlib_package : sig
type t =
Expand Down Expand Up @@ -439,12 +439,22 @@ end = struct
~meta_file:(Path.of_string "<internal>")
~meta

let dummy_package db name =
load_builtin db
{ name = Some (Lib_name.of_package_name name)
; vars = String.Map.empty
; subs = []
}
let dummy_package db lib_name =
let pkg, names = Lib_name.split lib_name in
let top_lib = Lib_name.of_package_name pkg in
let dummy name subs =
{ Meta.Simplified.name = Some name; vars = String.Map.empty; subs }
in
let subs : Meta.Simplified.t list =
let rec loop = function
| [] -> []
| name :: names ->
[ dummy (Lib_name.of_string_exn ~loc:None name) (loop names) ]
in
loop names
in
let meta = dummy top_lib subs in
load_builtin db meta

let lookup_and_load_one_dir db ~dir ~name =
let meta_file = Path.relative dir meta_fn in
Expand Down Expand Up @@ -493,8 +503,8 @@ end

type t = db

let dummy_package t ~name =
let p = Loader.dummy_package t (Lib_name.package_name name) in
let dummy_lib t ~name =
let p = Loader.dummy_package t name in
match Lib_name.Map.find_exn p.entries name with
| Library lib -> lib
| _ -> assert false
Expand Down
2 changes: 1 addition & 1 deletion src/dune/findlib/findlib.mli
Original file line number Diff line number Diff line change
Expand Up @@ -47,7 +47,7 @@ val all_packages : t -> Dune_package.Entry.t list
val all_broken_packages : t -> (Package.Name.t * exn) list

(** A dummy package. This is used to implement [external-lib-deps] *)
val dummy_package : t -> name:Lib_name.t -> Dune_package.Lib.t
val dummy_lib : t -> name:Lib_name.t -> Dune_package.Lib.t

module Config : sig
type t
Expand Down
2 changes: 1 addition & 1 deletion src/dune/lib.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1840,7 +1840,7 @@ module DB = struct
| Invalid_dune_package why -> Invalid why
| Not_found ->
if external_lib_deps_mode then
let pkg = Findlib.dummy_package findlib ~name in
let pkg = Findlib.dummy_lib findlib ~name in
Found (Dune_package.Lib.info pkg)
else
Not_found ))
Expand Down
22 changes: 17 additions & 5 deletions test/blackbox-tests/dune.inc
Original file line number Diff line number Diff line change
Expand Up @@ -784,11 +784,21 @@
(diff? run.t run.t.corrected)))))

(rule
(alias external-lib-deps)
(deps (package dune) (source_tree test-cases/external-lib-deps))
(alias external-lib-deps-github3143)
(deps (package dune) (source_tree test-cases/external-lib-deps/github3143))
(action
(chdir
test-cases/external-lib-deps
test-cases/external-lib-deps/github3143
(progn
(run %{exe:cram.exe} run.t -sanitizer %{bin:sanitizer})
(diff? run.t run.t.corrected)))))

(rule
(alias external-lib-deps-simple)
(deps (package dune) (source_tree test-cases/external-lib-deps/simple))
(action
(chdir
test-cases/external-lib-deps/simple
(progn
(run %{exe:cram.exe} run.t -sanitizer %{bin:sanitizer})
(diff? run.t run.t.corrected)))))
Expand Down Expand Up @@ -2733,7 +2743,8 @@
(alias exec-cmd)
(alias exec-missing)
(alias exes-with-c)
(alias external-lib-deps)
(alias external-lib-deps-github3143)
(alias external-lib-deps-simple)
(alias extra-lang-line)
(alias fallback-dune)
(alias findlib)
Expand Down Expand Up @@ -2989,7 +3000,8 @@
(alias exec-cmd)
(alias exec-missing)
(alias exes-with-c)
(alias external-lib-deps)
(alias external-lib-deps-github3143)
(alias external-lib-deps-simple)
(alias extra-lang-line)
(alias fallback-dune)
(alias findlib)
Expand Down
13 changes: 13 additions & 0 deletions test/blackbox-tests/test-cases/external-lib-deps/github3143/run.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,13 @@
Reproduce #3143

$ echo "(lang dune 2.3)" > dune-project
$ touch dummypkg.opam
$ cat >dune <<EOF
> (library
> (public_name dummypkg)
> (libraries base doesnotexist.foo))
> EOF
$ dune external-lib-deps @install
These are the external library dependencies in the default context:
- base
- doesnotexist.foo

0 comments on commit 06defff

Please sign in to comment.