Skip to content

Commit

Permalink
Rename Alias.of_path to Alias.of_user_written_path
Browse files Browse the repository at this point in the history
And add a loc argument for correct error messages
  • Loading branch information
rgrinberg committed May 8, 2018
1 parent fae6c0d commit 7050d06
Show file tree
Hide file tree
Showing 4 changed files with 12 additions and 7 deletions.
5 changes: 3 additions & 2 deletions src/build_system.ml
Original file line number Diff line number Diff line change
Expand Up @@ -238,9 +238,10 @@ module Alias0 = struct

let suffix = "-" ^ String.make 32 '0'

let of_path path =
let of_user_written_path ~loc path =
if not (Path.is_in_build_dir path) then
die "Invalid alias!\nTried to reference alias %S"
Loc.fail loc "Invalid alias!\n\
Tried to reference path outside build dir: %S"
(Path.to_string_maybe_quoted path);
make ~dir:(Path.parent path) (Path.basename path)

Expand Down
2 changes: 1 addition & 1 deletion src/build_system.mli
Original file line number Diff line number Diff line change
Expand Up @@ -99,7 +99,7 @@ module Alias : sig

val make : string -> dir:Path.t -> t

val of_path : Path.t -> t
val of_user_written_path : loc:Loc.t -> Path.t -> t

(** The following always holds:
Expand Down
4 changes: 3 additions & 1 deletion src/super_context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -457,7 +457,9 @@ module Deps = struct
open Dep_conf

let make_alias t ~scope ~dir s =
Alias.of_path (Path.relative dir (expand_vars t ~scope ~dir s))
let loc = String_with_vars.loc s in
Alias.of_user_written_path ~loc
(Path.relative ~error_loc:loc dir (expand_vars t ~scope ~dir s))

let dep t ~scope ~dir = function
| File s ->
Expand Down
8 changes: 5 additions & 3 deletions test/blackbox-tests/test-cases/bad-alias-error/run.t
Original file line number Diff line number Diff line change
@@ -1,5 +1,7 @@
$ dune runtest --root absolute-path 2>&1 | grep -v Entering
Invalid alias!
Tried to reference alias "/foo/bar"
File "jbuild", line 3, characters 16-24:
Error: Invalid alias!
Tried to reference path outside build dir: "/foo/bar"
$ dune runtest --root outside-workspace 2>&1 | grep -v Entering
Path outside the workspace: ./../../../foobar from _build/default
File "jbuild", line 4, characters 16-39:
Error: path outside the workspace: ./../../../foobar from _build/default

0 comments on commit 7050d06

Please sign in to comment.