Skip to content

Commit

Permalink
Check duplicates at parsing time
Browse files Browse the repository at this point in the history
Signed-off-by: Nicolás Ojeda Bär <n.oje.bar@gmail.com>
  • Loading branch information
nojb committed Jul 25, 2019
1 parent f2395a8 commit c9d6ba3
Show file tree
Hide file tree
Showing 4 changed files with 21 additions and 17 deletions.
16 changes: 5 additions & 11 deletions src/context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -550,26 +550,20 @@ let extend_paths t ~env =
end)
in
let t =
let f ((loc, var), t) =
let f (var, t) =
let parse ~loc:_ s = s in
let standard = Env.path env |> List.map ~f:Path.to_string in
var, (loc, Eval.eval t ~parse ~standard)
var, Eval.eval t ~parse ~standard
in
List.map ~f t
in
let vars =
let to_absolute_filename s =
Path.of_string s |> Path.to_absolute_filename in
let sep = String.make 1 Bin.path_sep in
match Env.Map.of_list t with
| Ok env ->
let f (_, l) = String.concat ~sep (List.map ~f:to_absolute_filename l) in
Env.Map.map ~f env
| Error (var, (_, _), (loc, _)) ->
User_error.raise ~loc
[ Pp.textf "the variable %S can appear at most once \
in this stanza." var
]
let env = Env.Map.of_list_exn t in
let f l = String.concat ~sep (List.map ~f:to_absolute_filename l) in
Env.Map.map ~f env
in
Env.extend ~vars env

Expand Down
14 changes: 12 additions & 2 deletions src/workspace.ml
Original file line number Diff line number Diff line change
Expand Up @@ -54,7 +54,7 @@ module Context = struct
; toolchain : string option
; name : string
; host_context : string option
; paths : ((Loc.t * string) * Ordered_set_lang.t) list
; paths : (string * Ordered_set_lang.t) list
}

let t ~profile =
Expand All @@ -66,9 +66,19 @@ module Context = struct
and+ toolchain =
field_o "toolchain" (Syntax.since syntax (1, 5) >>> string)
and+ paths =
let f l =
match Env.Map.of_list (List.map ~f:(fun ((loc, s), _) -> s, loc) l) with
| Ok _ ->
List.map ~f:(fun ((_, s), x) -> s, x) l
| Error (var, _, loc) ->
User_error.raise ~loc
[ Pp.textf "the variable %S can appear at most once \
in this stanza." var
]
in
field "paths" ~default:[]
(Syntax.since Stanza.syntax (1, 12) >>>
list (pair (located string) Ordered_set_lang.decode))
map ~f (list (pair (located string) Ordered_set_lang.decode)))
and+ loc = loc
in
Option.iter
Expand Down
2 changes: 1 addition & 1 deletion src/workspace.mli
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@ module Context : sig
; toolchain : string option
; name : string
; host_context : string option
; paths : ((Loc.t * string) * Ordered_set_lang.t) list
; paths : (string * Ordered_set_lang.t) list
}
end
module Opam : sig
Expand Down
6 changes: 3 additions & 3 deletions test/blackbox-tests/test-cases/workspace-paths/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -7,15 +7,15 @@
> (lang dune 1.12)
> (context
> (default
> (paths (FOO a) (FOO b))))
> (paths (FOO a) (FOo b))))
> EOF
$ cat > sub/dune-project <<EOF
> (lang dune 1.12)
> EOF
$ dune build --root sub
Entering directory 'sub'
File "dune-workspace", line 4, characters 19-22:
4 | (paths (FOO a) (FOO b))))
4 | (paths (FOO a) (FOo b))))
^^^
Error: the environment variable "FOO" can appear at most once in this stanza.
Error: the variable "FOo" can appear at most once in this stanza.
[1]

0 comments on commit c9d6ba3

Please sign in to comment.