Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension


Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
4 changes: 2 additions & 2 deletions .github/workflows/ci.ml
Original file line number Diff line number Diff line change
Expand Up @@ -527,8 +527,8 @@ let main oc : unit =
("OPAM12CACHE", "~/.cache/opam1.2/cache");
(* These should be identical to the values in appveyor.yml *)
("OPAM_REPO", "https://github.com/ocaml/opam-repository.git");
("OPAM_TEST_REPO_SHA", "67e940587b8aca227f511e1943bcd31eabe6b1db");
("OPAM_REPO_SHA", "67e940587b8aca227f511e1943bcd31eabe6b1db");
("OPAM_TEST_REPO_SHA", "0c42e982f4cf97fc698132fb2a16b49524a26ab3");
("OPAM_REPO_SHA", "0c42e982f4cf97fc698132fb2a16b49524a26ab3");
("SOLVER", "");
(* Cygwin configuration *)
("CYGWIN_MIRROR", "http://mirrors.kernel.org/sourceware/cygwin/");
Expand Down
4 changes: 2 additions & 2 deletions .github/workflows/main.yml
Original file line number Diff line number Diff line change
Expand Up @@ -26,8 +26,8 @@ env:
OPAMBSROOT: ~/.cache/.opam.cached
OPAM12CACHE: ~/.cache/opam1.2/cache
OPAM_REPO: https://github.com/ocaml/opam-repository.git
OPAM_TEST_REPO_SHA: 67e940587b8aca227f511e1943bcd31eabe6b1db
OPAM_REPO_SHA: 67e940587b8aca227f511e1943bcd31eabe6b1db
OPAM_TEST_REPO_SHA: 0c42e982f4cf97fc698132fb2a16b49524a26ab3
OPAM_REPO_SHA: 0c42e982f4cf97fc698132fb2a16b49524a26ab3
SOLVER:
CYGWIN_MIRROR: http://mirrors.kernel.org/sourceware/cygwin/
CYGWIN_ROOT: D:\cygwin
Expand Down
26 changes: 26 additions & 0 deletions configure

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

2 changes: 2 additions & 0 deletions configure.ac
Original file line number Diff line number Diff line change
Expand Up @@ -366,6 +366,7 @@ AC_CHECK_OCAML_PKG([jsonm])
AC_CHECK_OCAML_PKG([uutf])
AC_CHECK_OCAML_PKG([sha])
AC_CHECK_OCAML_PKG([swhid_core])
AC_CHECK_OCAML_PKG([patch])

# Optional dependencies
AC_CHECK_OCAML_PKG_AT_LEAST([mccs],[1.1+17])
Expand Down Expand Up @@ -414,6 +415,7 @@ AS_IF([test "x${enable_checks}" != "xno" && {
test "x$OCAML_PKG_uutf" = "xno" ||
test "x$OCAML_PKG_sha" = "xno" ||
test "x$OCAML_PKG_swhid_core" = "xno" ||
test "x$OCAML_PKG_patch" = "xno" ||
test "x$OCAML_PKG_mccs$MCCS_ENABLED" = "xnotrue";}],[
AS_IF([test "x${with_vendored_deps}" != "xyes"],[
AC_MSG_ERROR([Dependencies missing. Use --with-vendored-deps or --disable-checks])
Expand Down
16 changes: 16 additions & 0 deletions master_changes.md
Original file line number Diff line number Diff line change
Expand Up @@ -29,6 +29,9 @@ users)
## Install

## Build (package)
* Patches are now applied using the `patch` OCaml library instead of GNU Patch [#5892 @kit-ty-kate - fix #6019 #6052]
* ✘ Patches: Context diffs are not supported anymore, only Unified diffs are (including its git extensions) [#5892 @kit-ty-kate]
* ✘ Patches: Stop support of file permission changes via git extension to the unified diff specification [#5892 @kit-ty-kate - fix #3782]

## Remove

Expand Down Expand Up @@ -65,6 +68,7 @@ users)
* [BUG] Do not show the not-up-to-date message with packages tagged with avoid-version [#6273 @kit-ty-kate - fix #6271]
* [BUG] Fix a regression on `opam upgrade <package>` upgrading unrelated packages [#6373 @AltGr]
* [BUG] Fix a regression on `opam upgrade --all <uninstalled-pkg>` not upgrading the whole switch [#6373 @kit-ty-kate]
* Updates are now applied using the `patch` OCaml library instead of the system GNU Patch and diff utilities [#5892 @kit-ty-kate - fix ocaml/setup-ocaml#933 #6052]

## Tree

Expand All @@ -83,6 +87,7 @@ users)
* Update SWH API request [#6036 @rjbou]
* Rework SWH fallback to have a more correct archive retrieval and more fine grained error handling [#6036 @rjbou - fix #5721]
* Check that the repositories given to `opam repository remove` actually exist [#5014 @kit-ty-kate - fixes #5012]
* ✘ Symlinks in repositories are no longer supported [#5892 @kit-ty-kate]

## Lock
* [BUG] Fix `pin-depends` for `with-*` dependencies [#5471 @rjbou - fix #5428]
Expand All @@ -100,6 +105,7 @@ users)
* Lookup at `gpatch` before `patch` on macOS now that both homebrew and macports expose `gpatch` as `gpatch` since Homebrew/homebrew-core#174687 [#6255 @kit-ty-kate]
* Relax lookup on OpenBSD to consider all installed packages [#6362 @semarie]
* Speedup the detection of available system packages with pacman and brew [#6324 @kit-ty-kate]
* The system GNU Patch and diff are no longer runtime dependencies of opam [#5892 @kit-ty-kate - fix #6052]

## Format upgrade

Expand Down Expand Up @@ -168,6 +174,7 @@ users)
## Internal: Windows

## Test
* Add a library test for the new OCaml implementation of patch and diff [#5892 @rjbou]

## Benchmarks
* Add benchmarks for `opam show` [#6212 @kit-ty-kate]
Expand Down Expand Up @@ -226,6 +233,7 @@ users)

# API updates
## opam-client
* `OpamAction.prepare_package_build`: now returns `exn option` instead of `exn option OpamProcess.job` and no longer calls the system GNU Patch [#5892 @kit-ty-kate]
* `OpamArg.InvalidCLI`: export exception [#6150 @rjbou]
* `OpamArg`: export `require_checksums` and `no_checksums`, that are shared with `build_options` [#5563 @rjbou]
* `OpamArg.hash_kinds`: was added [#5960 @kit-ty-kate]
Expand All @@ -239,6 +247,8 @@ users)
* `OpamDownload.download`: more fine grained HTTP request error code detection for curl [#6036 @rjbou]
* `OpamRepository.revision`: now returns a `string` instead of a `version` [#6409 @kit-ty-kate]
* `OpamRepositoryBackend.S.revision`: now returns a `string` instead of a `version` [#6409 @kit-ty-kate]
* `OpamRepositoryBackend.get_diff`: now returns `exn option` instead of `exn option OpamProcess.job` and no longer calls the system `diff` utility [#5892 @kit-ty-kate]
* `OpamRepositoryBackend.get_diff`: now raises `Stdlib.Failure` if an unsupported file type or comparison is detected [#5892 @kit-ty-kate]

## opam-state
* `OpamStateConfig`: Make the `?lock_kind` parameters non-optional to avoid breaking the library users after they upgrade their opam root [#5488 @kit-ty-kate]
Expand All @@ -254,6 +264,8 @@ users)
## opam-core
* `OpamConsole`: Replace `black` text style (unused and not very readable) by `gray` [#6358 @kit-ty-kate]
* `OpamConsole.pause`: Ensure the function always prints a newline character at the end [#6376 @kit-ty-kate]
* `OpamFilename.patch`: now returns `exn option` instead of `exn option OpamProcess.job` and no longer calls the system GNU Patch [#5892 @kit-ty-kate]
* `OpamFilename.patch`: a named-parameter `~allow_unclean` was added [#5892 @kit-ty-kate]
* `OpamHash.all_kinds`: was added, which returns the list of all possible values of `OpamHash.kind` [#5960 @kit-ty-kate]
* `OpamStd.List.split`: Improve performance [#6210 @kit-ty-kate]
* `OpamStd.Option.equal_some`: was added, which tests equality of an option with a value [#6381 @kit-ty-kate]
Expand All @@ -264,6 +276,10 @@ users)
* `OpamStd.Sys.get_freebsd_version`: was added, which returns the output of the `uname -U` command [#6217 @kit-ty-kate]
* `OpamStubs.get_stdout_ws_col`: new Unix-only function returning the number of columns of the current terminal window [#6244 @kit-ty-kate]
* `OpamSystem`: add `is_archive_from_string` that does the same than `is_archive` but without looking at the file, only analysing the string (extension) [#6219 @rjbou]
* `OpamSystem.get_files`: was exposed which returns the list of files (without prefix) inside the given directory [#5892 @kit-ty-kate]
* `OpamSystem.remove_dir`: do not fail with an exception when directory is a symbolic link [#6276 @btjorge @rjbou - fix #6275]
* `OpamSystem.patch`: now returns `exn option` instead of `exn option OpamProcess.job` and no longer calls the system GNU Patch [#5892 @kit-ty-kate]
* `OpamSystem.patch`: a named-parameter `~allow_unclean` was added [#5892 @kit-ty-kate]
* `OpamSystem.patch`: do not remove the original patch file if called with `~preprocess:false` [#5892 @kit-ty-kate]
* `OpamParallel.*.{map,reduce,iter}`: Run `Gc.compact` when the main process is waiting for the children processes for the first time [#5396 @kkeundotnet]
* `OpamSystem`, `OpamFilename`: add `with_tmp_file` and `with_tmp_file_job` function, that create a file name in temporary directory and removes it at the end of the call [#6036 @rjbou]
1 change: 1 addition & 0 deletions opam-core.opam
Original file line number Diff line number Diff line change
Expand Up @@ -30,6 +30,7 @@ depends: [
"sha" {>= "1.13"}
"jsonm"
"swhid_core"
"patch" {>= "3.0.0~alpha1"}
"uutf"
(("host-system-mingw" {os = "win32" & os-distribution != "cygwinports"} &
"conf-mingw-w64-gcc-i686" {os = "win32" & os-distribution != "cygwinports"} &
Expand Down
1 change: 1 addition & 0 deletions opam-repository.opam
Original file line number Diff line number Diff line change
Expand Up @@ -30,5 +30,6 @@ build: [
depends: [
"ocaml" {>= "4.08.0"}
"opam-format" {= version}
"patch" {>= "3.0.0~alpha1"}
"dune" {>= "2.8.0"}
]
116 changes: 55 additions & 61 deletions src/client/opamAction.ml
Original file line number Diff line number Diff line change
Expand Up @@ -367,18 +367,18 @@ let prepare_package_build env opam nv dir =

let apply_patches ?(dryrun=false) () =
let patch base =
if dryrun then Done None else
OpamFilename.patch
if dryrun then None else
OpamFilename.patch ~allow_unclean:true
(dir // OpamFilename.Base.to_string base) dir
in
let rec aux = function
| [] -> Done []
| [] -> []
| (patchname,filter)::rest ->
if OpamFilter.opt_eval_to_bool env filter then
(print_apply patchname;
patch patchname @@+ function
match patch patchname with
| None -> aux rest
| Some err -> aux rest @@| fun e -> (patchname, err) :: e)
| Some err -> (patchname, err) :: aux rest)
else aux rest
in
aux patches
Expand All @@ -390,63 +390,57 @@ let prepare_package_build env opam nv dir =
in
if OpamStateConfig.(!r.dryrun) || OpamClientConfig.(!r.fake) then
(List.iter print_subst (OpamFile.OPAM.substs opam);
apply_patches ~dryrun:true ()) @@| fun _ -> None
let _ : _ list = apply_patches ~dryrun:true () in
None)
else
let subst_errs =
OpamFilename.in_dir dir @@ fun () ->
List.fold_left (fun errs f ->
try
print_subst f;
OpamFilter.expand_interpolations_in_file env f;
errs
with e -> (f, e)::errs)
[] subst_patches
in

(* Apply the patches *)
let text =
OpamProcess.make_command_text (OpamPackage.Name.to_string nv.name) "patch"
in
OpamProcess.Job.with_text text (apply_patches ())
@@+ fun patching_errors ->

(* Substitute the configuration files. We should be in the right
directory to get the correct absolute path for the
substitution files (see [OpamFilter.expand_interpolations_in_file] and
[OpamFilename.of_basename]. *)
let subst_errs =
OpamFilename.in_dir dir @@ fun () ->
List.fold_left (fun errs f ->
try
print_subst f;
OpamFilter.expand_interpolations_in_file env f;
errs
with e -> (f, e)::errs)
subst_errs subst_others
in
if patching_errors <> [] || subst_errs <> [] then
let msg =
(if patching_errors <> [] then
Printf.sprintf "These patches didn't apply at %s:\n%s"
(OpamFilename.Dir.to_string dir)
(OpamStd.Format.itemize
(fun (f,err) ->
Printf.sprintf "%s: %s"
(OpamFilename.Base.to_string f) (Printexc.to_string err))
patching_errors)
else "") ^
(if subst_errs <> [] then
Printf.sprintf "String expansion failed for these files:\n%s"
(OpamStd.Format.itemize
(fun (b,err) ->
Printf.sprintf "%s.in: %s" (OpamFilename.Base.to_string b)
(Printexc.to_string err))
subst_errs)
else "")
let subst_errs =
OpamFilename.in_dir dir @@ fun () ->
List.fold_left (fun errs f ->
try
print_subst f;
OpamFilter.expand_interpolations_in_file env f;
errs
with e -> (f, e)::errs)
[] subst_patches
in
Done (Some (Failure msg))
else
Done None
let patching_errors = apply_patches () in
(* Substitute the configuration files. We should be in the right
directory to get the correct absolute path for the
substitution files (see [OpamFilter.expand_interpolations_in_file] and
[OpamFilename.of_basename]. *)
let subst_errs =
OpamFilename.in_dir dir @@ fun () ->
List.fold_left (fun errs f ->
try
print_subst f;
OpamFilter.expand_interpolations_in_file env f;
errs
with e -> (f, e)::errs)
subst_errs subst_others
in
if patching_errors <> [] || subst_errs <> [] then
let msg =
(if patching_errors <> [] then
Printf.sprintf "These patches didn't apply at %s:\n%s"
(OpamFilename.Dir.to_string dir)
(OpamStd.Format.itemize
(fun (f,err) ->
Printf.sprintf "%s: %s"
(OpamFilename.Base.to_string f) (Printexc.to_string err))
patching_errors)
else "") ^
(if subst_errs <> [] then
Printf.sprintf "String expansion failed for these files:\n%s"
(OpamStd.Format.itemize
(fun (b,err) ->
Printf.sprintf "%s.in: %s" (OpamFilename.Base.to_string b)
(Printexc.to_string err))
subst_errs)
else "")
in
Some (Failure msg)
else
None

let prepare_package_source st nv dir =
log "prepare_package_source: %a at %a"
Expand Down Expand Up @@ -517,7 +511,7 @@ let prepare_package_source st nv dir =
get_extra_sources_job @@+ function Some _ as err -> Done err | None ->
check_extra_files |> function Some _ as err -> Done err | None ->
let opam = OpamSwitchState.opam st nv in
prepare_package_build (OpamPackageVar.resolve ~opam st) opam nv dir
Done (prepare_package_build (OpamPackageVar.resolve ~opam st) opam nv dir)

let compilation_env t opam =
let build_env =
Expand Down
2 changes: 1 addition & 1 deletion src/client/opamAction.mli
Original file line number Diff line number Diff line change
Expand Up @@ -40,7 +40,7 @@ val prepare_package_source:
of `prepare_package_source`, without requiring a switch and
without handling extra downloads. *)
val prepare_package_build:
OpamFilter.env -> OpamFile.OPAM.t -> package -> dirname -> exn option OpamProcess.job
OpamFilter.env -> OpamFile.OPAM.t -> package -> dirname -> exn option

(** [build_package t build_dir pkg] builds the package [pkg] within [build_dir].
Returns [None] on success, [Some exn] on error.
Expand Down
10 changes: 0 additions & 10 deletions src/client/opamInitDefaults.ml
Original file line number Diff line number Diff line change
Expand Up @@ -52,11 +52,6 @@ let not_win32_filter =
FOp (FIdent ([], OpamVariable.of_string "os", None), `Neq, FString "win32")
let sandbox_filter = FOr (linux_filter, macos_filter)

let gpatch_filter =
FOr (FOr (openbsd_filter, netbsd_filter),
FOr (freebsd_filter, FOr (dragonflybsd_filter, macos_filter)))
let patch_filter = FNot gpatch_filter

let gtar_filter = openbsd_filter
let tar_filter = FNot gtar_filter

Expand Down Expand Up @@ -131,9 +126,6 @@ let recommended_tools () =
let required_tools ~sandboxing () =
req_dl_tools () @
[
["diff"], None, None;
["patch"], None, Some patch_filter;
["gpatch"], None, Some gpatch_filter;
["tar"], None, Some tar_filter;
["gtar"], None, Some gtar_filter;
["unzip"], None, None;
Expand All @@ -146,9 +138,7 @@ let required_tools ~sandboxing () =

let required_packages_for_cygwin =
[
"diffutils";
"make";
"patch";
"tar";
"unzip";
"rsync";
Expand Down
2 changes: 1 addition & 1 deletion src/core/dune
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@
(public_name opam-core)
(synopsis "OCaml Package Manager core internal stdlib")
; TODO: Remove (re_export ...) when CI uses the OCaml version that includes https://github.com/ocaml/ocaml/pull/11989
(libraries re (re_export ocamlgraph) unix sha jsonm swhid_core uutf)
(libraries re (re_export ocamlgraph) unix sha jsonm swhid_core uutf patch)
(flags (:standard
(:include ../ocaml-flags-standard.sexp)
(:include ../ocaml-flags-configure.sexp)
Expand Down
5 changes: 3 additions & 2 deletions src/core/opamFilename.ml
Original file line number Diff line number Diff line change
Expand Up @@ -445,8 +445,9 @@ let link ?(relative=false) ~target ~link =
OpamSystem.link target (to_string link)
[@@ocaml.warning "-16"]

let patch ?preprocess filename dirname =
OpamSystem.patch ?preprocess ~dir:(Dir.to_string dirname) (to_string filename)
let patch ?preprocess ~allow_unclean filename dirname =
OpamSystem.patch ?preprocess ~allow_unclean ~dir:(Dir.to_string dirname)
(to_string filename)

let flock flag ?dontblock file = OpamSystem.flock flag ?dontblock (to_string file)

Expand Down
Loading