Skip to content

Commit

Permalink
do not allow the definition of duplicate packages
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <[email protected]>
  • Loading branch information
rgrinberg committed Apr 30, 2019
1 parent 78d7e14 commit 4af27be
Showing 1 changed file with 10 additions and 3 deletions.
13 changes: 10 additions & 3 deletions src/dune_project.ml
Original file line number Diff line number Diff line change
Expand Up @@ -576,7 +576,7 @@ let parse ~dir ~lang ~packages ~file =
and+ source = field_o "source" (Syntax.since Stanza.syntax (1, 7)
>>> Source_kind.decode)
and+ dune_defined_packages =
multi_field "package" (package_decode ~dir)
multi_field "package" (located (package_decode ~dir))
and+ authors = field ~default:[] "authors"
(Syntax.since Stanza.syntax (1, 9) >>> repeat string)
and+ license = field_o "license"
Expand Down Expand Up @@ -614,8 +614,15 @@ let parse ~dir ~lang ~packages ~file =
let allow_approx_merlin =
Option.value ~default:false allow_approx_merlin in
let packages =
List.fold_left ~init:packages ~f:(fun acc (p : Package.t) ->
Package.Name.Map.add acc p.name p) dune_defined_packages
match
dune_defined_packages
|> Package.Name.Map.of_list_map
~f:(fun (_loc, (p : Package.t)) -> p.name, p)
with
| Error (p, (_, _), (loc, _)) ->
of_sexp_errorf loc "Package %s is already defined"
(Package.Name.to_string p)
| Ok d -> Package.Name.Map.superpose packages d
in
{ name
; root = dir
Expand Down

0 comments on commit 4af27be

Please sign in to comment.