Skip to content

Commit

Permalink
WIP: case preserving environment variable keys
Browse files Browse the repository at this point in the history
  • Loading branch information
dra27 committed Nov 18, 2022
1 parent 4966295 commit d2f4031
Show file tree
Hide file tree
Showing 3 changed files with 50 additions and 15 deletions.
13 changes: 10 additions & 3 deletions src/core/opamStd.ml
Original file line number Diff line number Diff line change
Expand Up @@ -736,16 +736,23 @@ module Env = struct
) in
fun () -> Lazy.force lazy_env

let get =
let get_full =
if Sys.win32 then
fun n ->
let n = String.uppercase_ascii n in
snd (List.find (fun (k,_) -> String.uppercase_ascii k = n) (list ()))
List.find (fun (k,_) -> String.uppercase_ascii k = n) (list ())
else
fun n -> List.assoc n (list ())
fun n -> n, List.assoc n (list ())

let get n = snd (get_full n)

let getopt n = try Some (get n) with Not_found -> None

let getopt_full n =
try let (n, v) = get_full n in
(n, Some v)
with Not_found -> (n, None)

let escape_single_quotes ?(using_backslashes=false) =
if using_backslashes then
Re.(replace (compile (set "\\\'")) ~f:(fun g -> "\\"^Group.get g 0))
Expand Down
4 changes: 4 additions & 0 deletions src/core/opamStd.mli
Original file line number Diff line number Diff line change
Expand Up @@ -381,6 +381,10 @@ module Env : sig
*)
val cut_value: prefix:string -> char -> string -> string list * string list

val get_full: string -> string * string

val getopt_full: string -> string * string option

val get: string -> string

val getopt: string -> string option
Expand Down
48 changes: 36 additions & 12 deletions src/state/opamEnv.ml
Original file line number Diff line number Diff line change
Expand Up @@ -128,13 +128,21 @@ let expand (updates: env_update list) : env =
| None -> []
| Some updates ->
List.fold_right (fun (var, op, arg, _) defs0 ->
let v_opt, defs = OpamStd.List.pick_assoc var defs0 in
let v =
OpamStd.Option.Op.((v_opt >>| rezip >>+ fun () ->
OpamStd.Env.getopt var >>| split_var) +! [])
let v_opt, defs = OpamStd.List.pick_assoc (String.lowercase_ascii var) defs0 in
let var, v =
match Option.map rezip v_opt with
| Some v -> var, v
| None ->
let var, v = OpamStd.Env.getopt_full var in
var, OpamStd.Option.map_default split_var[] v
in
<<<<<<< Updated upstream
match reverse_env_update op arg v with
| Some v -> (var, v)::defs
=======
match reverse_env_update var op arg v with
| Some v -> (String.lowercase_ascii var, v)::defs
>>>>>>> Stashed changes
| None -> defs0)
updates []
in
Expand Down Expand Up @@ -172,16 +180,32 @@ let expand (updates: env_update list) : env =
apply_updates reverts [] updates

let add (env: env) (updates: env_update list) =
let env =
let updates =
(* Environment variable names are case-preserving on Windows (as for
filenames). Convert the names in updates to use the same case as any
pre-existing values in env.
*)
if Sys.win32 then
(*
* Environment variable names are case insensitive on Windows
*)
let updates = List.rev_map (fun (u,_,_,_) -> (String.uppercase_ascii u, "", "", None)) updates in
List.filter (fun (k,_,_) -> let k = String.uppercase_ascii k in List.for_all (fun (u,_,_,_) -> u <> k) updates) env
let env_keys =
List.fold_left (fun m (k,_,_) -> OpamStd.String.Map.add (String.lowercase_ascii k) k m) OpamStd.String.Map.empty env
in
(* Preserve the case of updates which are already in env *)
let convert (k, o, a, d) =
let k =
try OpamStd.String.Map.find (String.lowercase_ascii k) env_keys
with Not_found -> k
in
k, o, a, d
in
List.map convert updates
else
List.filter (fun (k,_,_) -> List.for_all (fun (u,_,_,_) -> u <> k) updates)
env
updates
in
let update_keys =
List.fold_left (fun m (k,_,_,_) -> OpamStd.String.Set.add k m) OpamStd.String.Set.empty updates
in
let env =
List.filter (fun (k,_,_) -> not (OpamStd.String.Set.mem k update_keys)) env
in
env @ expand updates

Expand Down

0 comments on commit d2f4031

Please sign in to comment.