Skip to content

Commit

Permalink
Inspect OCAMLPATH when not using ocamlfind (#642)
Browse files Browse the repository at this point in the history
  • Loading branch information
jeremiedimino committed Mar 20, 2018
1 parent 54b17cc commit f5f151d
Show file tree
Hide file tree
Showing 3 changed files with 39 additions and 26 deletions.
17 changes: 3 additions & 14 deletions src/bin.ml
Original file line number Diff line number Diff line change
Expand Up @@ -5,25 +5,14 @@ let path_sep =
';'
else
':'
;;

let parse_path s =
let rec loop i j =
if j = String.length s then
[Path.absolute (String.sub s ~pos:i ~len:(j - i))]
else if s.[j] = path_sep then
Path.absolute (String.sub s ~pos:i ~len:(j - i)) :: loop (j + 1) (j + 1)
else
loop i (j + 1)
in
loop 0 0
;;

let parse_path ?(sep=path_sep) s =
List.map (String.split s ~on:sep) ~f:Path.absolute

let path =
match Sys.getenv "PATH" with
| exception Not_found -> []
| s -> parse_path s
;;

let exe = if Sys.win32 then ".exe" else ""

Expand Down
3 changes: 2 additions & 1 deletion src/bin.mli
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,8 @@ val path_sep : char
(** Contents of [PATH] *)
val path : Path.t list

val parse_path : string -> Path.t list
(** Parse a [PATH] like variable *)
val parse_path : ?sep:char -> string -> Path.t list

(** The opam tool *)
val opam : Path.t option
Expand Down
45 changes: 34 additions & 11 deletions src/context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -121,6 +121,13 @@ let opam_config_var ~env ~cache var =
let which ~cache ~path x =
Hashtbl.find_or_add cache x ~f:(Bin.which ~path)

let ocamlpath_sep =
if Sys.cygwin then
(* because that's what ocamlfind expects *)
';'
else
Bin.path_sep

let create ~(kind : Kind.t) ~path ~env ~name ~merlin ~targets () =
let opam_var_cache = Hashtbl.create 128 in
(match kind with
Expand Down Expand Up @@ -190,10 +197,30 @@ let create ~(kind : Kind.t) ~path ~env ~name ~merlin ~targets () =
in

let build_dir = Path.of_string (sprintf "_build/%s" name) in
let ocamlpath =
match
let var = "OCAMLPATH" in
match kind, findlib_toolchain with
| Default, None -> Env.get env var
| _ ->
(* If we are not in the default context, we can only use the
OCAMLPATH variable if it is specific to this build
context *)
(* CR-someday diml: maybe we should actually clear OCAMLPATH
in other build contexts *)
match Env.get env var, Env.get (Env.initial ()) var with
| None , None -> None
| Some s, None -> Some s
| None , Some _ -> None
| Some x, Some y -> Option.some_if (x <> y) x
with
| None -> []
| Some s -> Bin.parse_path s ~sep:ocamlpath_sep
in
let findlib_path () =
match kind, findlib_toolchain, Setup.library_path with
| Default, None, Some l ->
Fiber.return (List.map l ~f:Path.absolute)
Fiber.return (ocamlpath @ List.map l ~f:Path.absolute)
| _ ->
(* If ocamlfind is present, it has precedence over everything else. *)
match which "ocamlfind" with
Expand All @@ -205,17 +232,20 @@ let create ~(kind : Kind.t) ~path ~env ~name ~merlin ~targets () =
| Some s -> "-toolchain" :: s :: args
in
Process.run_capture_lines ~env Strict (Path.to_string fn) args
>>| List.map ~f:Path.absolute
>>| fun l ->
(* Don't prepend the contents of [OCAMLPATH] since findlib
does it already *)
List.map l ~f:Path.absolute
| None ->
(* If there no ocamlfind in the PATH, check if we have opam
and assume a standard opam setup *)
opam_config_var ~env ~cache:opam_var_cache "lib"
>>| function
| Some s -> [Path.absolute s]
| Some s -> ocamlpath @ [Path.absolute s]
| None ->
(* If neither opam neither ocamlfind are present, assume
that libraries are [dir ^ "/../lib"] *)
[Path.relative (Path.parent dir) "lib"]
ocamlpath @ [Path.relative (Path.parent dir) "lib"]
in
let ocaml_config_ok_exn = function
| Ok x -> x
Expand Down Expand Up @@ -255,13 +285,6 @@ let create ~(kind : Kind.t) ~path ~env ~name ~merlin ~targets () =
in
let env =
let cwd = Sys.getcwd () in
let ocamlpath_sep =
if Sys.cygwin then
(* because that's what ocamlfind expects *)
';'
else
Bin.path_sep
in
let extend_var var ?(path_sep=Bin.path_sep) v =
let v = Filename.concat cwd (Path.to_string v) in
match Env.get env var with
Expand Down

0 comments on commit f5f151d

Please sign in to comment.