Skip to content

Commit

Permalink
Better error handling when toolchain isn't defined
Browse files Browse the repository at this point in the history
  • Loading branch information
rgrinberg committed Dec 14, 2017
1 parent 917f22b commit 0658695
Show file tree
Hide file tree
Showing 2 changed files with 13 additions and 4 deletions.
15 changes: 12 additions & 3 deletions src/context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -192,7 +192,7 @@ let create ?host ~implicit ~(kind : Kind.t) ~path ~base_env ~env_extra ~name ~me
let which_cache = Hashtbl.create 128 in
let which x = which ~cache:which_cache ~path x in
(match findlib_toolchain with
| None -> Future.return Findlib.Config.empty
| None -> Future.return (None, Findlib.Config.empty)
| Some _ ->
match which "ocamlfind" with
| None -> assert false
Expand All @@ -201,8 +201,8 @@ let create ?host ~implicit ~(kind : Kind.t) ~path ~base_env ~env_extra ~name ~me
(Path.to_string fn) ["printconf"; "conf"]
>>| fun s ->
let path = Path.absolute s in
Findlib.Config.load path)
>>= fun findlib_cfg ->
(Some path, Findlib.Config.load path))
>>= fun (findlib_conf, findlib_cfg) ->
let get_findlib_var =
let predicates =
match findlib_toolchain with
Expand All @@ -211,6 +211,15 @@ let create ?host ~implicit ~(kind : Kind.t) ~path ~base_env ~env_extra ~name ~me
in
fun var -> Findlib.Config.get findlib_cfg ~predicates ~var
in
let () =
Option.iter findlib_toolchain ~f:(fun toolchain ->
match get_findlib_var "ocamlc", findlib_conf with
| "", _ -> ()
| _, None -> ()
| _, Some fc ->
die "@{<error>Error@}: Toolchain %s isn't defined found in %a \
(context: %s)" toolchain Path.pp fc name)
in
let which prog =
let s = get_findlib_var prog in
if s = "" then
Expand Down
2 changes: 1 addition & 1 deletion src/findlib.ml
Original file line number Diff line number Diff line change
Expand Up @@ -122,7 +122,7 @@ module Config = struct
type t = Vars.t

let empty = String_map.empty

let load path =
let files =
let path_d = Path.extend_basename path ~suffix:".d" in
Expand Down

0 comments on commit 0658695

Please sign in to comment.