Skip to content

Commit 6065172

Browse files
committed
refactor: revert some of the environment detection changes
Signed-off-by: Antonio Nuno Monteiro <anmonteiro@gmail.com>
1 parent f6153cc commit 6065172

File tree

3 files changed

+28
-21
lines changed

3 files changed

+28
-21
lines changed

src/dune_rules/context.ml

Lines changed: 26 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -368,26 +368,36 @@ let create ~(kind : Kind.t) ~path ~env ~env_nodes ~name ~merlin ~targets
368368
~dynamically_linked_foreign_archives ~instrument_with =
369369
let which = Program.which ~path in
370370
let env_ocamlpath = Findlib.Config.ocamlpath env in
371-
let ocamlpath =
372-
let initial_ocamlpath = Findlib.Config.ocamlpath Env.initial in
373-
match (env_ocamlpath, initial_ocamlpath) with
374-
| [], [] -> []
375-
| _ :: _, [] -> env_ocamlpath
376-
| [], _ :: _ -> initial_ocamlpath
377-
| _, _ -> (
378-
match
379-
List.compare ~compare:Path.compare env_ocamlpath initial_ocamlpath
380-
with
381-
| Eq -> []
382-
| _ -> env_ocamlpath)
383-
in
384-
385371
let create_one ~(name : Context_name.t) ~implicit ~findlib_toolchain ~host
386372
~merlin =
387373
let ocamlpath =
388374
match (kind, findlib_toolchain) with
389-
| Default, None -> env_ocamlpath
390-
| _, _ -> ocamlpath
375+
| Default, None -> Option.value env_ocamlpath ~default:[]
376+
| _, _ -> (
377+
let initial_ocamlpath = Findlib.Config.ocamlpath Env.initial in
378+
(* If we are not in the default context, we can only use the OCAMLPATH
379+
variable if it is specific to this build context *)
380+
(* CR-someday diml: maybe we should actually clear OCAMLPATH in other
381+
build contexts *)
382+
match (env_ocamlpath, initial_ocamlpath) with
383+
| None, None -> []
384+
| Some s, None ->
385+
(* [OCAMLPATH] set for the target context, unset in the
386+
[initial_env]. This means it's the [OCAMLPATH] specific to this
387+
build context. *)
388+
s
389+
| None, Some _ ->
390+
(* Clear [OCAMLPATH] for this build context if it's defined
391+
initially but not for this build context. *)
392+
[]
393+
| Some env_ocamlpath, Some initial_ocamlpath -> (
394+
(* Clear [OCAMLPATH] for this build context Unless it's different
395+
from the initial [OCAMLPATH] variable. *)
396+
match
397+
List.compare ~compare:Path.compare env_ocamlpath initial_ocamlpath
398+
with
399+
| Eq -> []
400+
| _ -> env_ocamlpath))
391401
in
392402
let* findlib =
393403
Findlib.Config.discover_from_env ~env ~which ~ocamlpath ~findlib_toolchain

src/dune_rules/findlib/findlib.ml

Lines changed: 1 addition & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -183,10 +183,7 @@ module Config = struct
183183

184184
let path_var = Bin.parse_path ~sep:ocamlpath_sep
185185

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

191188
let set_toolchain t ~toolchain =
192189
match t.toolchain with

src/dune_rules/findlib/findlib.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -61,7 +61,7 @@ module Config : sig
6161
val ocamlpath_sep : char
6262

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

6666
val extra_env : t -> Env.t
6767

0 commit comments

Comments
 (0)