Skip to content

Commit

Permalink
refactor: revert some of the environment detection changes
Browse files Browse the repository at this point in the history
Signed-off-by: Antonio Nuno Monteiro <[email protected]>
  • Loading branch information
anmonteiro committed Apr 3, 2023
1 parent 1159c96 commit 02260ce
Show file tree
Hide file tree
Showing 3 changed files with 28 additions and 21 deletions.
42 changes: 26 additions & 16 deletions src/dune_rules/context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -368,26 +368,36 @@ let create ~(kind : Kind.t) ~path ~env ~env_nodes ~name ~merlin ~targets
~dynamically_linked_foreign_archives ~instrument_with =
let which = Program.which ~path in
let env_ocamlpath = Findlib.Config.ocamlpath env in
let ocamlpath =
let initial_ocamlpath = Findlib.Config.ocamlpath Env.initial in
match (env_ocamlpath, initial_ocamlpath) with
| [], [] -> []
| _ :: _, [] -> env_ocamlpath
| [], _ :: _ -> initial_ocamlpath
| _, _ -> (
match
List.compare ~compare:Path.compare env_ocamlpath initial_ocamlpath
with
| Eq -> []
| _ -> env_ocamlpath)
in

let create_one ~(name : Context_name.t) ~implicit ~findlib_toolchain ~host
~merlin =
let ocamlpath =
match (kind, findlib_toolchain) with
| Default, None -> env_ocamlpath
| _, _ -> ocamlpath
| Default, None -> Option.value env_ocamlpath ~default:[]
| _, _ -> (
let initial_ocamlpath = Findlib.Config.ocamlpath Env.initial in
(* 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_ocamlpath, initial_ocamlpath) with
| None, None -> []
| Some s, None ->
(* [OCAMLPATH] set for the target context, unset in the
[initial_env]. This means it's the [OCAMLPATH] specific to this
build context. *)
s
| None, Some _ ->
(* Clear [OCAMLPATH] for this build context if it's defined
initially but not for this build context. *)
[]
| Some env_ocamlpath, Some initial_ocamlpath -> (
(* Clear [OCAMLPATH] for this build context Unless it's different
from the initial [OCAMLPATH] variable. *)
match
List.compare ~compare:Path.compare env_ocamlpath initial_ocamlpath
with
| Eq -> []
| _ -> env_ocamlpath))
in
let* findlib =
Findlib.Config.discover_from_env ~env ~which ~ocamlpath ~findlib_toolchain
Expand Down
5 changes: 1 addition & 4 deletions src/dune_rules/findlib/findlib.ml
Original file line number Diff line number Diff line change
Expand Up @@ -183,10 +183,7 @@ module Config = struct

let path_var = Bin.parse_path ~sep:ocamlpath_sep

let ocamlpath env =
match Env.get env "OCAMLPATH" with
| None -> []
| Some s -> path_var s
let ocamlpath env = Env.get env "OCAMLPATH" |> Option.map ~f:path_var

let set_toolchain t ~toolchain =
match t.toolchain with
Expand Down
2 changes: 1 addition & 1 deletion src/dune_rules/findlib/findlib.mli
Original file line number Diff line number Diff line change
Expand Up @@ -61,7 +61,7 @@ module Config : sig
val ocamlpath_sep : char

(** Read and parse the [OCAMLPATH] environment variable *)
val ocamlpath : Env.t -> Path.t list
val ocamlpath : Env.t -> Path.t list option

val extra_env : t -> Env.t

Expand Down

0 comments on commit 02260ce

Please sign in to comment.