Skip to content

Commit

Permalink
Remove no longer useful function to parse contexts
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <rudi.grinberg@gmail.com>
  • Loading branch information
rgrinberg committed Sep 13, 2018
1 parent b95d2b9 commit b34384d
Show file tree
Hide file tree
Showing 3 changed files with 2 additions and 22 deletions.
13 changes: 0 additions & 13 deletions bin/alias.ml
Original file line number Diff line number Diff line change
Expand Up @@ -16,19 +16,6 @@ let to_log_string { name ; recursive; dir ; contexts = _ } =
(Path.to_string_maybe_quoted dir)
name

let parse_dir_and_contexts path contexts =
let dir = Path.parent_exn path in
match Path.extract_build_context dir with
| None -> (dir, contexts)
| Some ("install", _) ->
die "Invalid alias: %s.\n\
There are no aliases in %s."
(Path.to_string_maybe_quoted Path.(relative build_dir "install"))
(Path.to_string_maybe_quoted path)
| Some (ctx, dir) ->
Util.check_path contexts dir;
(dir, [List.find_exn contexts ~f:(fun c -> Dune.Context.name c = ctx)])

let in_dir ~name ~recursive ~contexts dir =
Util.check_path contexts dir;
match Path.extract_build_context dir with
Expand Down
5 changes: 0 additions & 5 deletions bin/alias.mli
Original file line number Diff line number Diff line change
Expand Up @@ -17,8 +17,3 @@ val in_dir
val of_string : Common.t -> string -> contexts:Dune.Context.t list -> t option

val to_log_string : t -> string

val parse_dir_and_contexts
: Path.t
-> Dune.Context.t list
-> Path.t * Dune.Context.t list
6 changes: 2 additions & 4 deletions bin/target.ml
Original file line number Diff line number Diff line change
Expand Up @@ -62,16 +62,14 @@ let target_hint (setup : Dune.Main.setup) path =
let candidates = String.Set.of_list candidates |> String.Set.to_list in
hint (Path.to_string path) candidates


let resolve_path path ~(setup : Dune.Main.setup) =
Util.check_path setup.contexts path;
let can't_build path =
Error (path, target_hint setup path);
in
if Dune.File_tree.dir_exists setup.file_tree path then
let (dir, contexts) =
Alias.parse_dir_and_contexts path setup.contexts in
Ok [ Alias (Alias.in_dir ~name:"default" ~recursive:true ~contexts dir) ]
Ok [ Alias (Alias.in_dir ~name:"default" ~recursive:true
~contexts:setup.contexts path) ]
else if not (Path.is_managed path) then
Ok [File path]
else if Path.is_in_build_dir path then begin
Expand Down

0 comments on commit b34384d

Please sign in to comment.