Skip to content

Commit 29af2fd

Browse files
committed
Replace the use of GNU Patch by the OCaml patch library
1 parent fcce0c8 commit 29af2fd

19 files changed

+202
-135
lines changed

.github/workflows/ci.ml

+2-2
Original file line numberDiff line numberDiff line change
@@ -527,8 +527,8 @@ let main oc : unit =
527527
("OPAM12CACHE", "~/.cache/opam1.2/cache");
528528
(* These should be identical to the values in appveyor.yml *)
529529
("OPAM_REPO", "https://github.com/ocaml/opam-repository.git");
530-
("OPAM_TEST_REPO_SHA", "67e940587b8aca227f511e1943bcd31eabe6b1db");
531-
("OPAM_REPO_SHA", "67e940587b8aca227f511e1943bcd31eabe6b1db");
530+
("OPAM_TEST_REPO_SHA", "0c42e982f4cf97fc698132fb2a16b49524a26ab3");
531+
("OPAM_REPO_SHA", "0c42e982f4cf97fc698132fb2a16b49524a26ab3");
532532
("SOLVER", "");
533533
(* Cygwin configuration *)
534534
("CYGWIN_MIRROR", "http://mirrors.kernel.org/sourceware/cygwin/");

.github/workflows/main.yml

+2-2
Original file line numberDiff line numberDiff line change
@@ -26,8 +26,8 @@ env:
2626
OPAMBSROOT: ~/.cache/.opam.cached
2727
OPAM12CACHE: ~/.cache/opam1.2/cache
2828
OPAM_REPO: https://github.com/ocaml/opam-repository.git
29-
OPAM_TEST_REPO_SHA: 67e940587b8aca227f511e1943bcd31eabe6b1db
30-
OPAM_REPO_SHA: 67e940587b8aca227f511e1943bcd31eabe6b1db
29+
OPAM_TEST_REPO_SHA: 0c42e982f4cf97fc698132fb2a16b49524a26ab3
30+
OPAM_REPO_SHA: 0c42e982f4cf97fc698132fb2a16b49524a26ab3
3131
SOLVER:
3232
CYGWIN_MIRROR: http://mirrors.kernel.org/sourceware/cygwin/
3333
CYGWIN_ROOT: D:\cygwin

configure

+26
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

configure.ac

+2
Original file line numberDiff line numberDiff line change
@@ -366,6 +366,7 @@ AC_CHECK_OCAML_PKG([jsonm])
366366
AC_CHECK_OCAML_PKG([uutf])
367367
AC_CHECK_OCAML_PKG([sha])
368368
AC_CHECK_OCAML_PKG([swhid_core])
369+
AC_CHECK_OCAML_PKG([patch])
369370

370371
# Optional dependencies
371372
AC_CHECK_OCAML_PKG_AT_LEAST([mccs],[1.1+17])
@@ -414,6 +415,7 @@ AS_IF([test "x${enable_checks}" != "xno" && {
414415
test "x$OCAML_PKG_uutf" = "xno" ||
415416
test "x$OCAML_PKG_sha" = "xno" ||
416417
test "x$OCAML_PKG_swhid_core" = "xno" ||
418+
test "x$OCAML_PKG_patch" = "xno" ||
417419
test "x$OCAML_PKG_mccs$MCCS_ENABLED" = "xnotrue";}],[
418420
AS_IF([test "x${with_vendored_deps}" != "xyes"],[
419421
AC_MSG_ERROR([Dependencies missing. Use --with-vendored-deps or --disable-checks])

master_changes.md

+10
Original file line numberDiff line numberDiff line change
@@ -29,6 +29,9 @@ users)
2929
## Install
3030

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

3336
## Remove
3437

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

6973
## Tree
7074

@@ -100,6 +104,7 @@ users)
100104
* 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]
101105
* Relax lookup on OpenBSD to consider all installed packages [#6362 @semarie]
102106
* Speedup the detection of available system packages with pacman and brew [#6324 @kit-ty-kate]
107+
* The system GNU Patch is no longer runtime dependency of opam [#5892 @kit-ty-kate - fix #6052]
103108

104109
## Format upgrade
105110

@@ -226,6 +231,7 @@ users)
226231

227232
# API updates
228233
## opam-client
234+
* `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]
229235
* `OpamArg.InvalidCLI`: export exception [#6150 @rjbou]
230236
* `OpamArg`: export `require_checksums` and `no_checksums`, that are shared with `build_options` [#5563 @rjbou]
231237
* `OpamArg.hash_kinds`: was added [#5960 @kit-ty-kate]
@@ -254,6 +260,8 @@ users)
254260
## opam-core
255261
* `OpamConsole`: Replace `black` text style (unused and not very readable) by `gray` [#6358 @kit-ty-kate]
256262
* `OpamConsole.pause`: Ensure the function always prints a newline character at the end [#6376 @kit-ty-kate]
263+
* `OpamFilename.patch`: now returns `exn option` instead of `exn option OpamProcess.job` and no longer calls the system GNU Patch [#5892 @kit-ty-kate]
264+
* `OpamFilename.patch`: a named-parameter `~allow_unclean` was added [#5892 @kit-ty-kate]
257265
* `OpamHash.all_kinds`: was added, which returns the list of all possible values of `OpamHash.kind` [#5960 @kit-ty-kate]
258266
* `OpamStd.List.split`: Improve performance [#6210 @kit-ty-kate]
259267
* `OpamStd.Option.equal_some`: was added, which tests equality of an option with a value [#6381 @kit-ty-kate]
@@ -265,5 +273,7 @@ users)
265273
* `OpamStubs.get_stdout_ws_col`: new Unix-only function returning the number of columns of the current terminal window [#6244 @kit-ty-kate]
266274
* `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]
267275
* `OpamSystem.remove_dir`: do not fail with an exception when directory is a symbolic link [#6276 @btjorge @rjbou - fix #6275]
276+
* `OpamSystem.patch`: now returns `exn option` instead of `exn option OpamProcess.job` and no longer calls the system GNU Patch [#5892 @kit-ty-kate]
277+
* `OpamSystem.patch`: a named-parameter `~allow_unclean` was added [#5892 @kit-ty-kate]
268278
* `OpamParallel.*.{map,reduce,iter}`: Run `Gc.compact` when the main process is waiting for the children processes for the first time [#5396 @kkeundotnet]
269279
* `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]

opam-core.opam

+1
Original file line numberDiff line numberDiff line change
@@ -30,6 +30,7 @@ depends: [
3030
"sha" {>= "1.13"}
3131
"jsonm"
3232
"swhid_core"
33+
"patch" {>= "3.0.0~alpha1"}
3334
"uutf"
3435
(("host-system-mingw" {os = "win32" & os-distribution != "cygwinports"} &
3536
"conf-mingw-w64-gcc-i686" {os = "win32" & os-distribution != "cygwinports"} &

opam-repository.opam

+1
Original file line numberDiff line numberDiff line change
@@ -30,5 +30,6 @@ build: [
3030
depends: [
3131
"ocaml" {>= "4.08.0"}
3232
"opam-format" {= version}
33+
"patch" {>= "3.0.0~alpha1"}
3334
"dune" {>= "2.8.0"}
3435
]

src/client/opamAction.ml

+55-61
Original file line numberDiff line numberDiff line change
@@ -367,18 +367,18 @@ let prepare_package_build env opam nv dir =
367367

368368
let apply_patches ?(dryrun=false) () =
369369
let patch base =
370-
if dryrun then Done None else
371-
OpamFilename.patch
370+
if dryrun then None else
371+
OpamFilename.patch ~allow_unclean:true
372372
(dir // OpamFilename.Base.to_string base) dir
373373
in
374374
let rec aux = function
375-
| [] -> Done []
375+
| [] -> []
376376
| (patchname,filter)::rest ->
377377
if OpamFilter.opt_eval_to_bool env filter then
378378
(print_apply patchname;
379-
patch patchname @@+ function
379+
match patch patchname with
380380
| None -> aux rest
381-
| Some err -> aux rest @@| fun e -> (patchname, err) :: e)
381+
| Some err -> (patchname, err) :: aux rest)
382382
else aux rest
383383
in
384384
aux patches
@@ -390,63 +390,57 @@ let prepare_package_build env opam nv dir =
390390
in
391391
if OpamStateConfig.(!r.dryrun) || OpamClientConfig.(!r.fake) then
392392
(List.iter print_subst (OpamFile.OPAM.substs opam);
393-
apply_patches ~dryrun:true ()) @@| fun _ -> None
393+
let _ : _ list = apply_patches ~dryrun:true () in
394+
None)
394395
else
395-
let subst_errs =
396-
OpamFilename.in_dir dir @@ fun () ->
397-
List.fold_left (fun errs f ->
398-
try
399-
print_subst f;
400-
OpamFilter.expand_interpolations_in_file env f;
401-
errs
402-
with e -> (f, e)::errs)
403-
[] subst_patches
404-
in
405-
406-
(* Apply the patches *)
407-
let text =
408-
OpamProcess.make_command_text (OpamPackage.Name.to_string nv.name) "patch"
409-
in
410-
OpamProcess.Job.with_text text (apply_patches ())
411-
@@+ fun patching_errors ->
412-
413-
(* Substitute the configuration files. We should be in the right
414-
directory to get the correct absolute path for the
415-
substitution files (see [OpamFilter.expand_interpolations_in_file] and
416-
[OpamFilename.of_basename]. *)
417-
let subst_errs =
418-
OpamFilename.in_dir dir @@ fun () ->
419-
List.fold_left (fun errs f ->
420-
try
421-
print_subst f;
422-
OpamFilter.expand_interpolations_in_file env f;
423-
errs
424-
with e -> (f, e)::errs)
425-
subst_errs subst_others
426-
in
427-
if patching_errors <> [] || subst_errs <> [] then
428-
let msg =
429-
(if patching_errors <> [] then
430-
Printf.sprintf "These patches didn't apply at %s:\n%s"
431-
(OpamFilename.Dir.to_string dir)
432-
(OpamStd.Format.itemize
433-
(fun (f,err) ->
434-
Printf.sprintf "%s: %s"
435-
(OpamFilename.Base.to_string f) (Printexc.to_string err))
436-
patching_errors)
437-
else "") ^
438-
(if subst_errs <> [] then
439-
Printf.sprintf "String expansion failed for these files:\n%s"
440-
(OpamStd.Format.itemize
441-
(fun (b,err) ->
442-
Printf.sprintf "%s.in: %s" (OpamFilename.Base.to_string b)
443-
(Printexc.to_string err))
444-
subst_errs)
445-
else "")
396+
let subst_errs =
397+
OpamFilename.in_dir dir @@ fun () ->
398+
List.fold_left (fun errs f ->
399+
try
400+
print_subst f;
401+
OpamFilter.expand_interpolations_in_file env f;
402+
errs
403+
with e -> (f, e)::errs)
404+
[] subst_patches
446405
in
447-
Done (Some (Failure msg))
448-
else
449-
Done None
406+
let patching_errors = apply_patches () in
407+
(* Substitute the configuration files. We should be in the right
408+
directory to get the correct absolute path for the
409+
substitution files (see [OpamFilter.expand_interpolations_in_file] and
410+
[OpamFilename.of_basename]. *)
411+
let subst_errs =
412+
OpamFilename.in_dir dir @@ fun () ->
413+
List.fold_left (fun errs f ->
414+
try
415+
print_subst f;
416+
OpamFilter.expand_interpolations_in_file env f;
417+
errs
418+
with e -> (f, e)::errs)
419+
subst_errs subst_others
420+
in
421+
if patching_errors <> [] || subst_errs <> [] then
422+
let msg =
423+
(if patching_errors <> [] then
424+
Printf.sprintf "These patches didn't apply at %s:\n%s"
425+
(OpamFilename.Dir.to_string dir)
426+
(OpamStd.Format.itemize
427+
(fun (f,err) ->
428+
Printf.sprintf "%s: %s"
429+
(OpamFilename.Base.to_string f) (Printexc.to_string err))
430+
patching_errors)
431+
else "") ^
432+
(if subst_errs <> [] then
433+
Printf.sprintf "String expansion failed for these files:\n%s"
434+
(OpamStd.Format.itemize
435+
(fun (b,err) ->
436+
Printf.sprintf "%s.in: %s" (OpamFilename.Base.to_string b)
437+
(Printexc.to_string err))
438+
subst_errs)
439+
else "")
440+
in
441+
Some (Failure msg)
442+
else
443+
None
450444

451445
let prepare_package_source st nv dir =
452446
log "prepare_package_source: %a at %a"
@@ -517,7 +511,7 @@ let prepare_package_source st nv dir =
517511
get_extra_sources_job @@+ function Some _ as err -> Done err | None ->
518512
check_extra_files |> function Some _ as err -> Done err | None ->
519513
let opam = OpamSwitchState.opam st nv in
520-
prepare_package_build (OpamPackageVar.resolve ~opam st) opam nv dir
514+
Done (prepare_package_build (OpamPackageVar.resolve ~opam st) opam nv dir)
521515

522516
let compilation_env t opam =
523517
let build_env =

src/client/opamAction.mli

+1-1
Original file line numberDiff line numberDiff line change
@@ -40,7 +40,7 @@ val prepare_package_source:
4040
of `prepare_package_source`, without requiring a switch and
4141
without handling extra downloads. *)
4242
val prepare_package_build:
43-
OpamFilter.env -> OpamFile.OPAM.t -> package -> dirname -> exn option OpamProcess.job
43+
OpamFilter.env -> OpamFile.OPAM.t -> package -> dirname -> exn option
4444

4545
(** [build_package t build_dir pkg] builds the package [pkg] within [build_dir].
4646
Returns [None] on success, [Some exn] on error.

src/client/opamInitDefaults.ml

-8
Original file line numberDiff line numberDiff line change
@@ -52,11 +52,6 @@ let not_win32_filter =
5252
FOp (FIdent ([], OpamVariable.of_string "os", None), `Neq, FString "win32")
5353
let sandbox_filter = FOr (linux_filter, macos_filter)
5454

55-
let gpatch_filter =
56-
FOr (FOr (openbsd_filter, netbsd_filter),
57-
FOr (freebsd_filter, FOr (dragonflybsd_filter, macos_filter)))
58-
let patch_filter = FNot gpatch_filter
59-
6055
let gtar_filter = openbsd_filter
6156
let tar_filter = FNot gtar_filter
6257

@@ -132,8 +127,6 @@ let required_tools ~sandboxing () =
132127
req_dl_tools () @
133128
[
134129
["diff"], None, None;
135-
["patch"], None, Some patch_filter;
136-
["gpatch"], None, Some gpatch_filter;
137130
["tar"], None, Some tar_filter;
138131
["gtar"], None, Some gtar_filter;
139132
["unzip"], None, None;
@@ -148,7 +141,6 @@ let required_packages_for_cygwin =
148141
[
149142
"diffutils";
150143
"make";
151-
"patch";
152144
"tar";
153145
"unzip";
154146
"rsync";

src/core/dune

+1-1
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,7 @@
33
(public_name opam-core)
44
(synopsis "OCaml Package Manager core internal stdlib")
55
; TODO: Remove (re_export ...) when CI uses the OCaml version that includes https://github.com/ocaml/ocaml/pull/11989
6-
(libraries re (re_export ocamlgraph) unix sha jsonm swhid_core uutf)
6+
(libraries re (re_export ocamlgraph) unix sha jsonm swhid_core uutf patch)
77
(flags (:standard
88
(:include ../ocaml-flags-standard.sexp)
99
(:include ../ocaml-flags-configure.sexp)

src/core/opamFilename.ml

+3-2
Original file line numberDiff line numberDiff line change
@@ -445,8 +445,9 @@ let link ?(relative=false) ~target ~link =
445445
OpamSystem.link target (to_string link)
446446
[@@ocaml.warning "-16"]
447447

448-
let patch ?preprocess filename dirname =
449-
OpamSystem.patch ?preprocess ~dir:(Dir.to_string dirname) (to_string filename)
448+
let patch ?preprocess ~allow_unclean filename dirname =
449+
OpamSystem.patch ?preprocess ~allow_unclean ~dir:(Dir.to_string dirname)
450+
(to_string filename)
450451

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

src/core/opamFilename.mli

+6-2
Original file line numberDiff line numberDiff line change
@@ -271,8 +271,12 @@ val remove_prefix_dir: Dir.t -> Dir.t -> string
271271
val remove_suffix: Base.t -> t -> string
272272

273273
(** Apply a patch in a directory. If [preprocess] is set to false, there is no
274-
CRLF translation. Returns [None] on success, the process error otherwise *)
275-
val patch: ?preprocess:bool -> t -> Dir.t -> exn option OpamProcess.job
274+
CRLF translation. Returns [None] on success, the process error otherwise.
275+
276+
@param allow_unclean decides if applying a patch on a directory which
277+
differs slightly from the one described in the patch file is allowed.
278+
Allowing unclean applications imitates the default behaviour of GNU Patch. *)
279+
val patch: ?preprocess:bool -> allow_unclean:bool -> t -> Dir.t -> exn option
276280

277281
(** Create an empty file *)
278282
val touch: t -> unit

0 commit comments

Comments
 (0)