Skip to content

Commit

Permalink
Quick fix multiple definitions of the same library when several scope…
Browse files Browse the repository at this point in the history
…s define the same library.

Signed-off-by: Lucas Pluvinage <lucas.pluvinage@gmail.com>
Signed-off-by: Rudi Grinberg <rudi.grinberg@gmail.com>
  • Loading branch information
TheLortex authored and rgrinberg committed Apr 3, 2019
1 parent 47d401e commit ac1e29b
Show file tree
Hide file tree
Showing 4 changed files with 8 additions and 9 deletions.
4 changes: 4 additions & 0 deletions src/lib.ml
Original file line number Diff line number Diff line change
Expand Up @@ -762,6 +762,10 @@ let rec find_implementation_for db lib ~variants =
~f:(fun variant acc ->
List.rev_append acc
(Variant.Map.Multi.find available_implementations variant))
|> List.sort_uniq ~compare:(fun (a:Lib_info.t) (b:Lib_info.t) ->
match Lib_name.compare a.name b.name with
| Eq -> Path.compare a.src_dir b.src_dir
| x -> x)
|> fun x -> match x, db.parent with
| [], None -> Ok None
| [], Some db -> find_implementation_for db lib ~variants
Expand Down
3 changes: 3 additions & 0 deletions src/stdune/list.ml
Original file line number Diff line number Diff line change
Expand Up @@ -111,6 +111,9 @@ let sort t ~compare =
let stable_sort t ~compare =
stable_sort t ~cmp:(fun a b -> Ordering.to_int (compare a b))

let sort_uniq t ~compare =
sort_uniq t ~cmp:(fun a b -> Ordering.to_int (compare a b))

let rec compare a b ~compare:f : Ordering.t =
match a, b with
| [], [] -> Eq
Expand Down
1 change: 1 addition & 0 deletions src/stdune/list.mli
Original file line number Diff line number Diff line change
Expand Up @@ -41,6 +41,7 @@ val destruct_last : 'a t -> ('a list * 'a) option

val sort : 'a t -> compare:('a -> 'a -> Ordering.t) -> 'a t
val stable_sort : 'a t -> compare:('a -> 'a -> Ordering.t) -> 'a t
val sort_uniq : 'a t -> compare:('a -> 'a -> Ordering.t) -> 'a t

val compare : 'a t -> 'a t -> compare:('a -> 'a -> Ordering.t) -> Ordering.t

Expand Down
9 changes: 0 additions & 9 deletions test/blackbox-tests/test-cases/variants/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -82,12 +82,3 @@ Solving variant ambiguity by specifying a concrete implementation.
Don't fail when the same library is defined in multiple scopes.
$ dune build --root same-lib-in-multiple-scopes
Entering directory 'same-lib-in-multiple-scopes'
File "dune", line 3, characters 12-16:
3 | (variants unix)
^^^^
Error: Multiple solutions for the implementation
of test with variants [ "unix" ]
-> test-unix ("unix")
-> test-unix ("unix")
-> required by executable exe in dune:2
[1]

0 comments on commit ac1e29b

Please sign in to comment.