Skip to content

Commit

Permalink
Merge pull request #5350 from dra27/empty-envs
Browse files Browse the repository at this point in the history
Fix crash for updates to environment with empty strings
  • Loading branch information
dra27 authored Jan 24, 2023
2 parents c7662f4 + eccd5d1 commit 79affca
Show file tree
Hide file tree
Showing 4 changed files with 57 additions and 8 deletions.
4 changes: 4 additions & 0 deletions doc/pages/Manual.md
Original file line number Diff line number Diff line change
Expand Up @@ -647,6 +647,10 @@ other system).
by opam, the new value will replace the old one at the same position instead
of being put in front.

`FOO = ""` causes `FOO` to be set _but empty_ on Unix but _unset_ on Windows.

`FOO += ""`, `FOO := ""`, etc. are all ignored - i.e. opam never adds empty segments to an existing variable.

### URLs

URLs are provided as strings. They can refer to:
Expand Down
4 changes: 4 additions & 0 deletions master_changes.md
Original file line number Diff line number Diff line change
Expand Up @@ -280,6 +280,8 @@ users)
* Don’t rebuild packages when updating dependencies or availablity, unless the current state needs to be changed [#5118 @kit-ty-kate - fix #4647]
* Rebuild packages when removing or adding the "plugin" flag [#5118 @kit-ty-kate]
* Do not rebuild packages when an extra-source's url changes but not its checksum [#5258 @kit-ty-kate]
* Correctly handle empty environment variable additions [#5350 @dra27]
* Skip empty environment variable additions [#5350 @dra27]

## Opam file format
*
Expand Down Expand Up @@ -537,6 +539,8 @@ users)
* Add optional argument `?env:(variable_contents option Lazy.t * string) OpamVariable.Map.t` to `OpamSysPoll` and `OpamSysInteract` functions. It is used to get syspolling variables from the environment first. [#4892 @rjbou]
* `OpamSwitchState`: move and reimplement `opam-solver` `dependencies` and `reverse_dependencies` [#5337 @rjbou]
* `OpamEnv`: add `env_expansion` [#5352 @dra27]
* `OpamEnv`: fix invalid argument raised when trying to unzip empty string [#5350 @dra27]
* `OpamEnv`: skip environment updates and revert with empty strings [#5350 @dra27]

## opam-solver
* `OpamCudf`: Change type of `conflict_case.Conflict_cycle` (`string list list` to `Cudf.package action list list`) and `cycle_conflict`, `string_of_explanations`, `conflict_explanations_raw` types accordingly [#4039 @gasche]
Expand Down
21 changes: 13 additions & 8 deletions src/state/opamEnv.ml
Original file line number Diff line number Diff line change
Expand Up @@ -40,19 +40,19 @@ let unzip_to elt current =
| ([], rs) -> Some rs
| _ -> None
in
match split_var elt with
| [] -> invalid_arg "OpamEnv.unzip_to"
| hd::tl ->
let rec aux acc = function
match (if String.equal elt "" then [""] else split_var elt) with
| [] -> invalid_arg "OpamEnv.unzip_to"
| hd::tl ->
let rec aux acc = function
| [] -> None
| x::r ->
if x = hd then
if String.equal x hd then
match remove_prefix tl r with
| Some r -> Some (acc, r)
| None -> aux (x::acc) r
else aux (x::acc) r
in
aux [] current
in
aux [] current

let rezip ?insert (l1, l2) =
List.rev_append l1 (match insert with None -> l2 | Some i -> i::l2)
Expand Down Expand Up @@ -91,6 +91,7 @@ let apply_op_zip op arg (rl1,l2 as zip) =
or empty lists is returned if the variable should be unset or has an unknown
previous value. *)
let reverse_env_update op arg cur_value =
if String.equal arg "" && op <> Eq then None else
match op with
| Eq ->
if arg = join_var cur_value
Expand Down Expand Up @@ -157,9 +158,13 @@ let expand (updates: env_update list) : env =
| Some s -> ([], split_var s), reverts
| None -> ([], []), reverts
in
let acc =
if String.equal arg "" && op <> Eq then acc else
((var, apply_op_zip op arg zip, doc) :: acc)
in
apply_updates
reverts
((var, apply_op_zip op arg zip, doc) :: acc)
acc
updates
| [] ->
List.rev @@
Expand Down
36 changes: 36 additions & 0 deletions tests/reftests/env.test
Original file line number Diff line number Diff line change
Expand Up @@ -70,6 +70,42 @@ The following actions will be performed:
Done.
### cat $OPAMROOT/build-env/doc/pkg.version
V1.2.3
### : empty environment variables update :
### NV_VARS=''
### <pkg:nv.1>
opam-version: "2.0"
setenv: [
[ NV_VARS += "" ]
[ NV_VARS2 := "" ]
[ NV_VARS3 := "" ]
[ NV_VARS3 := "foo" ]
[ NV_VARS4 = "" ]
]
flags: compiler
### opam switch create emptyvar nv

<><> Installing new switch packages <><><><><><><><><><><><><><><><><><><><><><>
Switch invariant: ["nv"]

<><> Processing actions <><><><><><><><><><><><><><><><><><><><><><><><><><><><>
-> installed nv.1
Done.
### opam env | grep "NV_VARS" | ';' -> ':'
NV_VARS3='foo:': export NV_VARS3:
NV_VARS4='': export NV_VARS4:
### opam exec -- opam env --revert | grep "NV_VARS" | ';' -> ':'
NV_VARS3='': export NV_VARS3:
NV_VARS4='': export NV_VARS4:
### NV_VARS=/another/path
### NV_VARS2=/another/different/path
### NV_VARS3=/yet/another/different/path
### NV_VARS4=ignored-value
### opam env | grep "NV_VARS" | ';' -> ':'
NV_VARS3='foo:/yet/another/different/path': export NV_VARS3:
NV_VARS4='': export NV_VARS4:
### opam exec -- opam env --revert | grep "NV_VARS" | ';' -> ':'
NV_VARS3='/yet/another/different/path': export NV_VARS3:
NV_VARS4='': export NV_VARS4:
### : root and switch with spaces :
### RT="$BASEDIR/root 2"
### SW="switch w spaces"
Expand Down

0 comments on commit 79affca

Please sign in to comment.