Skip to content

Commit

Permalink
Merge pull request #5444 from kit-ty-kate/2.1.5-backport
Browse files Browse the repository at this point in the history
2.1.5 backport commits
  • Loading branch information
rjbou committed May 12, 2023
2 parents 3dd624a + 387d97f commit 93f47ec
Show file tree
Hide file tree
Showing 27 changed files with 679 additions and 57 deletions.
13 changes: 8 additions & 5 deletions .github/scripts/hygiene.sh
Expand Up @@ -67,12 +67,15 @@ case $GITHUB_EVENT_NAME in
CheckConfigure "$GITHUB_SHA"
;;
pull_request)
for commit in $(git rev-list $BASE_REF_SHA...$PR_REF_SHA --reverse)
do
echo "check configure for $commit"
CheckConfigure "$commit"
done
CheckConfigure "$PR_REF_SHA"
;;
#git rev-list $BASE_REF_SHA...$PR_REF_SHA --reverse
#for commit in $(git rev-list $BASE_REF_SHA...$PR_REF_SHA --reverse)
#do
# echo "check configure for $commit"
# CheckConfigure "$commit"
#done
#;;
*)
echo "no configure to check for unknown event"
;;
Expand Down
11 changes: 11 additions & 0 deletions CHANGES
Expand Up @@ -3,6 +3,17 @@ repositories (changes that are automatically handled by the format upgrade tools
are not marked). Those prefixed with "(+)" are new command/option (since
2.1.0~alpha2).

2.1.5:
* [BUG] Variables are now expanded in build-env (as for setenv) [#5352 @dra27]
* Correctly handle empty environment variable additions [#5350 @dra27]
* Skip empty environment variable additions [#5350 @dra27]
* [BUG] Fix passing `archive-mirrors` field from init config file to config
[#5315 @hannesm]
* git, hg: Use the full SHA1 revision instead of just the 8 first characters
[#5342 @reynir]
* [BUG] Fix opam installing packages without checking their checksum when the
local cache is corrupted in some case [#5538 @kit-ty-kate]

2.1.4:
* Add support for OCaml 5.0. Dose3 >= 6.1 and base64 >= 3.1.0 are now required [#5357 @kit-ty-kate @dra27 - fix #5354]
* [BUG] Fix all empty conflict explanation messages [#5378 @kit-ty-kate - partial fix #4373]
Expand Down
18 changes: 9 additions & 9 deletions configure

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

2 changes: 1 addition & 1 deletion configure.ac
@@ -1,5 +1,5 @@
dnl The line below must be formatted AC_INIT(opam,VERSION) with no extra spaces
AC_INIT(opam,2.1.4)
AC_INIT(opam,2.1.5)
AC_COPYRIGHT(Copyright 2012-2019 OcamlPro SAS)

AC_CONFIG_MACRO_DIR([m4])
Expand Down
4 changes: 4 additions & 0 deletions doc/pages/Manual.md
Expand Up @@ -644,6 +644,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
2 changes: 1 addition & 1 deletion opam-client.opam
@@ -1,5 +1,5 @@
opam-version: "2.0"
version: "2.1.4"
version: "2.1.5"
synopsis: "Client library for opam 2.1"
description: """
Actions on the opam root, switches, installations, and front-end.
Expand Down
2 changes: 1 addition & 1 deletion opam-core.opam
@@ -1,5 +1,5 @@
opam-version: "2.0"
version: "2.1.4"
version: "2.1.5"
synopsis: "Core library for opam 2.1"
description: """
Small standard library extensions, and generic system interaction modules used by opam.
Expand Down
2 changes: 1 addition & 1 deletion opam-devel.opam
@@ -1,5 +1,5 @@
opam-version: "2.0"
version: "2.1.4"
version: "2.1.5"
synopsis: "Bootstrapped development binary for opam 2.1"
description: """
This package compiles (bootstraps) opam. For consistency and safety of the installation, the binaries are not installed into the PATH, but into lib/opam-devel, from where the user can manually install them system-wide.
Expand Down
2 changes: 1 addition & 1 deletion opam-format.opam
@@ -1,5 +1,5 @@
opam-version: "2.0"
version: "2.1.4"
version: "2.1.5"
synopsis: "Format library for opam 2.1"
description: """
Definition of opam datastructures and its file interface.
Expand Down
2 changes: 1 addition & 1 deletion opam-installer.opam
@@ -1,5 +1,5 @@
opam-version: "2.0"
version: "2.1.4"
version: "2.1.5"
synopsis: "Installation of files to a prefix, following opam conventions"
description: """
opam-installer is a small tool that can read *.install files, as defined by opam [1], and execute them to install or remove package files without going through opam.
Expand Down
2 changes: 1 addition & 1 deletion opam-repository.opam
@@ -1,5 +1,5 @@
opam-version: "2.0"
version: "2.1.4"
version: "2.1.5"
synopsis: "Repository library for opam 2.1"
description: """
This library includes repository and remote sources handling, including curl/wget, rsync, git, mercurial, darcs backends.
Expand Down
2 changes: 1 addition & 1 deletion opam-solver.opam
@@ -1,5 +1,5 @@
opam-version: "2.0"
version: "2.1.4"
version: "2.1.5"
synopsis: "Solver library for opam 2.1"
description: """
Solver and Cudf interaction. This library is based on the Cudf and Dose libraries, and handles calls to the external solver from opam.
Expand Down
2 changes: 1 addition & 1 deletion opam-state.opam
@@ -1,5 +1,5 @@
opam-version: "2.0"
version: "2.1.4"
version: "2.1.5"
synopsis: "State library for opam 2.1"
description: """
Handling of the ~/.opam hierarchy, repository and switch states.
Expand Down
2 changes: 1 addition & 1 deletion opam.opam
@@ -1,5 +1,5 @@
opam-version: "2.0"
version: "2.1.4"
version: "2.1.5"
synopsis: "Meta-package for Dune"
maintainer: "opam-devel@lists.ocaml.org"
authors: [
Expand Down
5 changes: 4 additions & 1 deletion src/client/opamAction.ml
Expand Up @@ -479,6 +479,9 @@ let prepare_package_source st nv dir =

let compilation_env t opam =
let open OpamParserTypes in
let build_env =
List.map (OpamEnv.env_expansion ~opam t) (OpamFile.OPAM.build_env opam)
in
let scrub = OpamClientConfig.(!r.scrubbed_environment_variables) in
OpamEnv.get_full ~scrub ~set_opamroot:true ~set_opamswitch:true
~force_path:true t ~updates:([
Expand All @@ -493,7 +496,7 @@ let compilation_env t opam =
Some "build environment definition";
"OPAMCLI", Eq, "2.0", Some "opam CLI version";
] @
OpamFile.OPAM.build_env opam)
build_env)

let installed_opam_opt st nv =
OpamStd.Option.Op.(
Expand Down
1 change: 1 addition & 0 deletions src/client/opamClient.ml
Expand Up @@ -756,6 +756,7 @@ let update_with_init_config ?(overwrite=false) config init_config =
| Some j -> setifnew C.jobs C.with_jobs j
| None -> fun c -> c) |>
setifnew C.dl_tool C.with_dl_tool_opt (I.dl_tool init_config) |>
setifnew C.dl_cache C.with_dl_cache (I.dl_cache init_config) |>
setifnew C.dl_jobs C.with_dl_jobs
(OpamStd.Option.default OpamStateConfig.(default.dl_jobs)
(I.dl_jobs init_config)) |>
Expand Down
5 changes: 1 addition & 4 deletions src/repository/opamGit.ml
Expand Up @@ -157,10 +157,7 @@ module VCS : OpamVCS.VCS = struct
match r.OpamProcess.r_stdout with
| [] -> Done None
| full::_ ->
if String.length full > 8 then
Done (Some (String.sub full 0 8))
else
Done (Some full))
Done (Some full))

let clean repo_root =
git repo_root [ "clean"; "-fdx" ]
Expand Down
3 changes: 1 addition & 2 deletions src/repository/opamHg.ml
Expand Up @@ -53,8 +53,7 @@ module VCS = struct
match r.OpamProcess.r_stdout with
| [] -> Done None
| full::_ ->
if String.length full > 8 then Done (Some (String.sub full 0 8))
else Done (Some full)
Done (Some full)

let clean repo_root =
hg repo_root ["revert"; "--all"; "--no-backup"]
Expand Down
7 changes: 3 additions & 4 deletions src/repository/opamRepository.ml
Expand Up @@ -93,15 +93,14 @@ let fetch_from_cache =
failwith "Version control not allowed as cache URL"
in
try
let hit_checksum, hit_file =
let hit_file =
OpamStd.List.find_map (fun ck ->
let f = cache_file cache_dir ck in
if OpamFilename.exists f then Some (ck, f) else None)
if OpamFilename.exists f then Some f else None)
checksums
in
if List.for_all
(fun ck -> ck = hit_checksum ||
OpamHash.check_file (OpamFilename.to_string hit_file) ck)
(fun ck -> OpamHash.check_file (OpamFilename.to_string hit_file) ck)
checksums
then Done (Up_to_date (hit_file, OpamUrl.empty))
else mismatch hit_file
Expand Down
45 changes: 25 additions & 20 deletions src/state/opamEnv.ml
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 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 (x : string) = 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 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 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 All @@ -185,18 +190,22 @@ let add (env: env) (updates: env_update list) =
in
env @ expand updates

let env_expansion ?opam st (name, op, str, cmt) =
let fenv v =
try OpamPackageVar.resolve st ?opam v
with Not_found ->
log "Undefined variable: %s" (OpamVariable.Full.to_string v);
None
in
let s = OpamFilter.expand_string ~default:(fun _ -> "") fenv str in
name, op, s, cmt

let compute_updates ?(force_path=false) st =
(* Todo: put these back into their packages!
let perl5 = OpamPackage.Name.of_string "perl5" in
let add_to_perl5lib = OpamPath.Switch.lib t.root t.switch t.switch_config perl5 in
let new_perl5lib = "PERL5LIB", "+=", OpamFilename.Dir.to_string add_to_perl5lib in
*)
let fenv ?opam v =
try OpamPackageVar.resolve st ?opam v
with Not_found ->
log "Undefined variable: %s" (OpamVariable.Full.to_string v);
None
in
let bindir =
OpamPath.Switch.bin st.switch_global.root st.switch st.switch_config
in
Expand All @@ -218,21 +227,17 @@ let compute_updates ?(force_path=false) st =
st.switch_global.root st.switch st.switch_config),
Some "Current opam switch man dir"]
in
let env_expansion ?opam (name,op,str,cmt) =
let s = OpamFilter.expand_string ~default:(fun _ -> "") (fenv ?opam) str in
name, op, s, cmt
in
let switch_env =
("OPAM_SWITCH_PREFIX", Eq,
OpamFilename.Dir.to_string
(OpamPath.Switch.root st.switch_global.root st.switch),
Some "Prefix of the current opam switch") ::
List.map env_expansion st.switch_config.OpamFile.Switch_config.env
List.map (env_expansion st) st.switch_config.OpamFile.Switch_config.env
in
let pkg_env = (* XXX: Does this need a (costly) topological sort? *)
OpamPackage.Set.fold (fun nv acc ->
match OpamPackage.Map.find_opt nv st.opams with
| Some opam -> List.map (env_expansion ~opam) (OpamFile.OPAM.env opam) @ acc
| Some opam -> List.map (env_expansion ~opam st) (OpamFile.OPAM.env opam) @ acc
| None -> acc)
st.installed []
in
Expand Down
3 changes: 3 additions & 0 deletions src/state/opamEnv.mli
Expand Up @@ -94,6 +94,9 @@ val path: force_path:bool -> dirname -> switch -> string
val full_with_path:
force_path:bool -> ?updates:env_update list -> dirname -> switch -> env

(** Performs variable expansion on the strings in an environment update *)
val env_expansion: ?opam:OpamFile.OPAM.t -> 'a switch_state -> env_update -> env_update

(** {2 Shell and initialisation support} *)

(** Sets the opam configuration in the user shell, after detailing the process
Expand Down
17 changes: 17 additions & 0 deletions tests/reftests/dune.inc
Expand Up @@ -376,6 +376,23 @@
%{targets}
(run ./run.exe %{bin:opam} %{dep:list.unix.test} %{read-lines:testing-env}))))

(alias
(name reftest-local-cache)
(action
(diff local-cache.test local-cache.out)))

(alias
(name reftest)
(deps (alias reftest-local-cache)))

(rule
(targets local-cache.out)
(deps root-N0REP0)
(action
(with-stdout-to
%{targets}
(run ./run.exe %{bin:opam} %{dep:local-cache.test} %{read-lines:testing-env}))))

(alias
(name reftest-opamroot-versions)
(action
Expand Down

0 comments on commit 93f47ec

Please sign in to comment.