Skip to content

Commit

Permalink
Fix creating dummy package
Browse files Browse the repository at this point in the history
Used in --external-libs-deps

Signed-off-by: Rudi Grinberg <[email protected]>
  • Loading branch information
rgrinberg committed Feb 15, 2020
1 parent 7a8ff30 commit fcb7027
Show file tree
Hide file tree
Showing 4 changed files with 24 additions and 42 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
34 changes: 3 additions & 31 deletions test/blackbox-tests/test-cases/external-lib-deps/github3143/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -8,34 +8,6 @@ Reproduce #3143
> (libraries base doesnotexist.foo))
> EOF
$ dune external-lib-deps @install
Internal error, please report upstream including the contents of _build/log.
Description:
("Map.find_exn: failed to find key",
{ key = "doesnotexist.foo"; keys = [ "doesnotexist" ] })
Backtrace:
Raised at file "src/stdune/code_error.ml", line 9, characters 30-62
Called from file "src/dune/findlib/findlib.ml", line 498, characters 8-44
Called from file "src/dune/lib.ml", line 1843, characters 24-59
Called from file "src/dune/lib.ml", line 1189, characters 10-25
Called from file "src/dune/lib.ml", line 1203, characters 21-49
Called from file "src/dune/lib.ml", line 1203, characters 21-49
Called from file "src/dune/lib.ml", line 1181, characters 10-38
Called from file "src/dune/lib.ml", line 1287, characters 25-76
Called from file "list.ml", line 121, characters 24-34
Called from file "src/dune/lib.ml", line 1269, characters 6-1023
Called from file "src/dune/lib.ml" (inlined), line 1110, characters 9-75
Called from file "src/dune/lib.ml", line 1109, characters 6-104
Called from file "src/dune/lib.ml", line 1192, characters 12-42
Called from file "src/dune/lib.ml", line 1851, characters 10-61
Called from file "src/dune/super_context.ml", line 529, characters 18-56
Called from file "src/dune/dir_with_dune.ml", line 23, characters 55-67
Called from file "src/dune/super_context.ml", line 526, characters 6-692
Called from file "src/dune/gen_rules.ml", line 412, characters 6-102
Called from file "src/fiber/fiber.ml", line 102, characters 8-15

I must not segfault. Uncertainty is the mind-killer. Exceptions are
the little-death that brings total obliteration. I will fully express
my cases. Execution will pass over me and through me. And when it
has gone past, I will unwind the stack along its path. Where the
cases are handled there will be nothing. Only I will remain.
[1]
These are the external library dependencies in the default context:
- base
- doesnotexist.foo

0 comments on commit fcb7027

Please sign in to comment.