From 7f5edb92c01292a25db532cf468fbc8894fdcd9e Mon Sep 17 00:00:00 2001 From: "Richard W.M. Jones" Date: Wed, 29 May 2024 10:48:49 +0100 Subject: [PATCH] New upstream version 5.2.0 (RHBZ#2269805) --- ...onisation-and-consistency-with-trunk.patch | 90 +++ 0002-Changes-copy-editing.patch | 515 ++++++++++++++++++ ...> 0003-Don-t-add-rpaths-to-libraries.patch | 8 +- ...-Allow-user-defined-C-compiler-flags.patch | 8 +- ...transitive-closure-in-invariant_para.patch | 114 ++++ ocaml.spec | 29 +- 6 files changed, 747 insertions(+), 17 deletions(-) create mode 100644 0001-Changes-synchronisation-and-consistency-with-trunk.patch create mode 100644 0002-Changes-copy-editing.patch rename 0001-Don-t-add-rpaths-to-libraries.patch => 0003-Don-t-add-rpaths-to-libraries.patch (79%) rename 0002-configure-Allow-user-defined-C-compiler-flags.patch => 0004-configure-Allow-user-defined-C-compiler-flags.patch (88%) create mode 100644 0005-flambda-Improve-transitive-closure-in-invariant_para.patch diff --git a/0001-Changes-synchronisation-and-consistency-with-trunk.patch b/0001-Changes-synchronisation-and-consistency-with-trunk.patch new file mode 100644 index 0000000..5f865d0 --- /dev/null +++ b/0001-Changes-synchronisation-and-consistency-with-trunk.patch @@ -0,0 +1,90 @@ +From 5538fa66e94fad3d2b4f110d23bef3b4d2d6342c Mon Sep 17 00:00:00 2001 +From: Florian Angeletti +Date: Mon, 13 May 2024 11:39:37 +0200 +Subject: [PATCH 1/5] Changes: synchronisation and consistency with trunk + +--- + Changes | 25 ++++++++++++++----------- + 1 file changed, 14 insertions(+), 11 deletions(-) + +diff --git a/Changes b/Changes +index 208d5e8697..1af198ba77 100644 +--- a/Changes ++++ b/Changes +@@ -140,9 +140,6 @@ OCaml 5.2.0 + (Guillaume Munch-Maccagnoni, bug reports and suggestion by Mark + Shinwell, review by Nick Barnes and Stephen Dolan) + +-- #12876: Port ThreadSanitizer support to Linux on POWER +- (Miod Vallat, review by Tim McGilchrist) +- + - #12408: `Domain.spawn` no longer leaks its functional argument for + the whole duration of the children domain lifetime. + (Guillaume Munch-Maccagnoni, review by Gabriel Scherer) +@@ -156,8 +153,10 @@ OCaml 5.2.0 + review by Damien Doligez, Sébastien Hinderer, Jacques-Henri Jourdan, Luc + Maranget, Guillaume Munch-Maccagnoni, Gabriel Scherer) + +-- #11911, #12381: Restore statmemprof functionality in part +- (API changes in Gc.Memprof). (Nick Barnes) ++- #11911, #12381: Restore statmemprof functionality in part, with ++ some API changes in Gc.Memprof. ++ (Nick Barnes, review by Jacques-Henri Jourdan ++ and Guillaume Munch-Maccagnoni). + + - #12430: Simplify dynamic bytecode loading in Meta.reify_bytecode + (Stephen Dolan, review by Sébastien Hinderer, Vincent Laviron and Xavier +@@ -216,9 +215,10 @@ OCaml 5.2.0 + Ojeda Bar) + + - #11911, #12382, #12383: Restore statmemprof functionality in part +- (backtrace buffers, per-thread and per-domain data structures). +- (Nick Barnes, review by Gabriel Scherer, Fabrice Buoro, Sadiq +- Jaffer, and Guillaume Munch-Maccagnoni). ++ (backtrace buffers, per-thread and per-domain data structures, ++ GC/allocation interface). (Nick Barnes, review by Gabriel Scherer, ++ Fabrice Buoro, Sadiq Jaffer, Guillaume Munch-Maccagnoni, and ++ Jacques-Henri Jourdan). + + - #12735: Store both ends of the stack chain in continuations + (Leo White, review by Miod Vallat and KC Sivaramakrishnan) +@@ -248,6 +248,9 @@ OCaml 5.2.0 + Hari Hara Naveen S, reviewed by Fabrice Buoro, Gabriel Scherer and + Miod Vallat) + ++- #12876: Port ThreadSanitizer support to Linux on POWER ++ (Miod Vallat, review by Tim McGilchrist) ++ + - #12886: Reinitialize IO mutexes after fork + (Max Slater, review by Guillaume Munch-Maccagnoni and Xavier Leroy) + +@@ -990,7 +993,7 @@ OCaml 5.1.0 (14 September 2023) + `Seq.find_mapi`, `Seq.find_index`, `Array.find_mapi`, `Array.find_index`, + `Float.Array.find_opt`, `Float.Array.find_index`, `Float.Array.find_map`, + `Float.Array.find_mapi`. +- (Sima Kinsart, review by Daniel Bünzli and Nicolás Ojeda Bär) ++ (Tima Kinsart, review by Daniel Bünzli and Nicolás Ojeda Bär) + + - #11410: Add Set.to_list, Map.to_list, Map.of_list, + `Map.add_to_list: key -> 'a -> 'a list t -> 'a list t`. +@@ -1771,7 +1774,7 @@ Some of those changes will benefit all OCaml packages. + + - #11846: Mark rbx as destroyed at C call for Win64 (mingw-w64 and Cygwin64). + Reserve the shadow store for the ABI in the c_stack_link struct instead of +- explictly when calling C functions. This simultaneously reduces the number of ++ explicitly when calling C functions. This simultaneously reduces the number of + stack pointer manipulations and also fixes a bug when calling noalloc + functions where the shadow store was not being reserved. + (David Allsopp, report by Vesa Karvonen, review by Xavier Leroy and +@@ -2791,7 +2794,7 @@ OCaml 4.14.0 (28 March 2022) + - #8516: Change representation of class signatures + (Leo White, review by Thomas Refis) + +-- #9444: -dtypedtree, print more explictly extra nodes in pattern ast. ++- #9444: -dtypedtree, print more explicitly extra nodes in pattern ast. + (Frédéric Bour, review by Gabriel Scherer) + + - #10337: Normalize type_expr nodes on access +-- +2.44.0 + diff --git a/0002-Changes-copy-editing.patch b/0002-Changes-copy-editing.patch new file mode 100644 index 0000000..05f48ac --- /dev/null +++ b/0002-Changes-copy-editing.patch @@ -0,0 +1,515 @@ +From 7a20c9322f827923baa6a9907998f670463ce447 Mon Sep 17 00:00:00 2001 +From: Florian Angeletti +Date: Mon, 13 May 2024 14:28:08 +0200 +Subject: [PATCH 2/5] Changes copy-editing + +--- + Changes | 398 ++++++++++++++++++++++++++++---------------------------- + 1 file changed, 201 insertions(+), 197 deletions(-) + +diff --git a/Changes b/Changes +index 1af198ba77..75842fc216 100644 +--- a/Changes ++++ b/Changes +@@ -1,5 +1,5 @@ +-OCaml 5.2.0 +------------- ++OCaml 5.2.0 (13 May 2024) ++------------------------- + + (Changes that can break existing programs are marked with a "*") + +@@ -12,60 +12,6 @@ OCaml 5.2.0 + - #12667: extend the latter to POWER 64 bits, big-endian, ELFv2 ABI + (A. Wilcox, review by Xavier Leroy) + +-### Language features: +- +-- #12295, #12568: Give `while true' a polymorphic type, similarly to +- `assert false' +- (Jeremy Yallop, review by Nicolás Ojeda Bär and Gabriel Scherer, +- suggestion by Rodolphe Lepigre and John Whitington) +- +-- #12315: Use type annotations from arguments in let rec +- (Stephen Dolan, review by Gabriel Scherer) +- +-- #11252, RFC 27: Support raw identifier syntax \#foo +- (Stephen Dolan, review by David Allsopp, Gabriel Scherer and Olivier Nicole) +- +-- #12044: Add local module open syntax for types. +- ``` +- module A = struct +- type t = int +- type r = unit +- type s = string +- end +- +- type example = A.(t * r * s) +- ``` +- (Alistair O'Brien, review by Gabriel Scherer, Nicolás Ojeda Bär +- and Florian Angeletti) +- +-- #12456: Document the incompatibility between effects on the one +- hand, and `caml_callback` and asynchronous callbacks (signal +- handlers, finalisers, memprof callbacks...) on the other hand. +- (Guillaume Munch-Maccagnoni, review by KC Sivaramakrishnan) +- +-- #12375: allow use of [@untagged] for all immediate types like char, bool, +- and variant with only constant constructors. +- (Christophe Raffalli, review by Gabriel Scherer) +- +-* #12502: the compiler now normalizes the newline sequence \r\n to +- a single \n character during lexing, to guarantee that the semantics +- of newlines in string literals is not modified by Windows tools +- transforming \n into \r\n in source files. +- Warning 29 [eol-in-string] is not emitted anymore, as the normalization +- gives a more robust semantics to newlines in string literals. +- (Gabriel Scherer and Damien Doligez, review by Daniel Bünzli, David +- Allsopp, Andreas Rossberg, Xavier Leroy, report by Andreas Rossberg) +- +-- #13130: minor fixes to pprintast for raw identifiers and local module open +- syntax for types. +- (Chet Murthy, review by Gabriel Scherer) +- +-### Type system: +- +-- #12313, #11799: Do not re-build as-pattern type when a ground type annotation +- is given. This allows to work around problems with GADTs in as-patterns. +- (Jacques Garrigue, report by Leo White, review by Gabriel Scherer) +- + ### Runtime system: + + - #12193: Re-introduce GC compaction for shared pools +@@ -76,6 +22,12 @@ OCaml 5.2.0 + David Allsopp, Miod Vallat, Artem Pianykh, Stephen Dolan, Mark Shinwell + and KC Sivaramakrishnan) + ++- #12114: Add ThreadSanitizer support ++ (Fabrice Buoro and Olivier Nicole, based on an initial work by Anmol Sahoo, ++ review by Damien Doligez, Sébastien Hinderer, Jacques-Henri Jourdan, Luc ++ Maranget, Guillaume Munch-Maccagnoni, Gabriel Scherer) ++ ++ + - #12850: Update Gc.quick_stat data at the end of major cycles and compaction + This PR adds an additional caml_collect_gc_stats_sample_stw to the major heap + cycling stw. This means that Gc.quick_stat now actually reflects the state of +@@ -148,11 +100,6 @@ OCaml 5.2.0 + arise at specific locations during domain creation and shutdown. + (Guillaume Munch-Maccagnoni, review by Gabriel Scherer) + +-- #12114: Add ThreadSanitizer support +- (Fabrice Buoro and Olivier Nicole, based on an initial work by Anmol Sahoo, +- review by Damien Doligez, Sébastien Hinderer, Jacques-Henri Jourdan, Luc +- Maranget, Guillaume Munch-Maccagnoni, Gabriel Scherer) +- + - #11911, #12381: Restore statmemprof functionality in part, with + some API changes in Gc.Memprof. + (Nick Barnes, review by Jacques-Henri Jourdan +@@ -264,34 +211,48 @@ OCaml 5.2.0 + (Olivier Nicole, suggested by Stephen Dolan, review by Gabriel Scherer, + Miod Vallat and Damien Doligez) + +-### Code generation and optimizations: ++### Language features: + +-- #11239: on x86-64 and RISC-V, reduce alignment of OCaml stacks from 16 to 8. +- This reduces stack usage. It's only C stacks that require 16-alignment. +- (Xavier Leroy, review by Gabriel Scherer and Stephen Dolan) ++- #12295, #12568: Give `while true' a polymorphic type, similarly to ++ `assert false' ++ (Jeremy Yallop, review by Nicolás Ojeda Bär and Gabriel Scherer, ++ suggestion by Rodolphe Lepigre and John Whitington) + +-- #12311: on POWER, 32-bit FP numbers stored in memory (e.g. in bigarrays) +- were not correctly rounded sometimes. +- (Xavier Leroy, review by Anil Madhavapeddy and Tim McGilchrist) ++- #12044: Add local module open syntax for types. ++ ``` ++ module A = struct ++ type t = int ++ type r = unit ++ type s = string ++ end + +-- #12551, #12608, #12782, #12596: Overhaul of recursive value compilation. +- Non-function recursive bindings are now forbidden from Lambda onwards, +- and compiled using a new Value_rec_compiler module. +- (Vincent Laviron and Lunia Ayanides, review by Gabriel Scherer, +- Stefan Muenzel and Nathanaëlle Courant) ++ type example = A.(t * r * s) ++ ``` ++ (Alistair O'Brien, review by Gabriel Scherer, Nicolás Ojeda Bär ++ and Florian Angeletti) + +-- #1809, #12181: rewrite `compare x y op 0` to `x op y` when values are integers +- (Xavier Clerc, Stefan Muenzel, review by Gabriel Scherer and Vincent Laviron) ++- #11252, RFC 27: Support raw identifier syntax \#foo ++ (Stephen Dolan, review by David Allsopp, Gabriel Scherer and Olivier Nicole) + +-- #12825: disable common subexpression elimination for atomic loads... again. +- (Gabriel Scherer, review by KC Sivaramakrishnan, Xavier Leroy +- and Vincent Laviron, report by Vesa Karvonen) ++ ++- #12315: Use type annotations from arguments in let rec ++ (Stephen Dolan, review by Gabriel Scherer) ++ ++- #12375: allow use of [@untagged] for all immediate types like char, bool, ++ and variant with only constant constructors. ++ (Christophe Raffalli, review by Gabriel Scherer) ++ ++* #12502: the compiler now normalizes the newline sequence \r\n to ++ a single \n character during lexing, to guarantee that the semantics ++ of newlines in string literals is not modified by Windows tools ++ transforming \n into \r\n in source files. ++ Warning 29 [eol-in-string] is not emitted anymore, as the normalization ++ gives a more robust semantics to newlines in string literals. ++ (Gabriel Scherer and Damien Doligez, review by Daniel Bünzli, David ++ Allsopp, Andreas Rossberg, Xavier Leroy, report by Andreas Rossberg) + + ### Standard library: + +-- #12716: Add `Format.pp_print_nothing` function. +- (Léo Andrès, review by Gabriel Scherer and Nicolás Ojeda Bär) +- + - #11563: Add the Dynarray module to the stdlib. Dynamic arrays are + arrays whose length can be changed by adding or removing elements at + the end, similar to 'vectors' in C++ or Rust. +@@ -299,6 +260,10 @@ OCaml 5.2.0 + Daniel Bünzli, Guillaume Munch-Maccagnoni, Clément Allain, + Damien Doligez, Wiktor Kuchta and Pieter Goetschalckx) + ++ ++- #12716: Add `Format.pp_print_nothing` function. ++ (Léo Andrès, review by Gabriel Scherer and Nicolás Ojeda Bär) ++ + * #6732, #12423: Make Buffer.add_substitute surjective and fix its + documentation. + (Damien Doligez, review by Antonin Décimo) +@@ -380,6 +345,35 @@ OCaml 5.2.0 + C API. + (David Allsopp, review by Nicolás Ojeda Bär and Xavier Leroy) + ++### Type system: ++ ++- #12313, #11799: Do not re-build as-pattern type when a ground type annotation ++ is given. This allows to work around problems with GADTs in as-patterns. ++ (Jacques Garrigue, report by Leo White, review by Gabriel Scherer) ++ ++### Code generation and optimizations: ++ ++- #11239: on x86-64 and RISC-V, reduce alignment of OCaml stacks from 16 to 8. ++ This reduces stack usage. It's only C stacks that require 16-alignment. ++ (Xavier Leroy, review by Gabriel Scherer and Stephen Dolan) ++ ++- #12311: on POWER, 32-bit FP numbers stored in memory (e.g. in bigarrays) ++ were not correctly rounded sometimes. ++ (Xavier Leroy, review by Anil Madhavapeddy and Tim McGilchrist) ++ ++- #12551, #12608, #12782, #12596: Overhaul of recursive value compilation. ++ Non-function recursive bindings are now forbidden from Lambda onwards, ++ and compiled using a new Value_rec_compiler module. ++ (Vincent Laviron and Lunia Ayanides, review by Gabriel Scherer, ++ Stefan Muenzel and Nathanaëlle Courant) ++ ++- #1809, #12181: rewrite `compare x y op 0` to `x op y` when values are integers ++ (Xavier Clerc, Stefan Muenzel, review by Gabriel Scherer and Vincent Laviron) ++ ++- #12825: disable common subexpression elimination for atomic loads... again. ++ (Gabriel Scherer, review by KC Sivaramakrishnan, Xavier Leroy ++ and Vincent Laviron, report by Vesa Karvonen) ++ + ### Other libraries: + + - #12213: Dynlink library, improve legibility of error messages +@@ -390,98 +384,14 @@ OCaml 5.2.0 + instead of `value`. + (Xavier Leroy, review by David Allsopp) + +-### Tools: +- +-- #12340: testsuite: collect known issues with current -short-paths +- implementation for existential types +- (Florian Angeletti, Samuel Hym, review by Florian Angeletti and Thomas Refis) +- +-- #12147: ocamllex: Allow carriage returns at the end of line directives. +- (SeungCheol Jung, review by Nicolás Ojeda Bär) +- +-- #12260: Fix invalid_argument on some external or module aliases in ocamlnat +- (Fabian Hemmer, review by Vincent Laviron) +- +-- #12185: New script language for ocamltest. +- (Damien Doligez with Florian Angeletti, Sébastien Hinderer, Gabriel Scherer, +- review by Sébastien Hinderer and Gabriel Scherer) +- +-- #12371: ocamltest: fix recursive expansion of variables. +- (Antonin Décimo, Damien Doligez, review by Sébastien Hinderer, +- Damien Doligez, Gabriel Scherer, and Xavier Leroy) +- +-* #12497, #12613: Make ocamlc/ocamlopt fail with an error when no +- input files are specified to build an executable. +- (Antonin Décimo, review by Sébastien Hinderer) +- +-- #12576: ocamldep: various refactors. +- (Antonin Décimo, review by Florian Angeletti, Gabriel Scherer, and Léo Andrès) +- +-- #12615: ocamldoc: get rid of the odoc_literate and odoc_todo generators. +- (Sébaistien Hinderer, review by Gabriel Scherer and Florian Angeletti) +- +-- #12624: Use $XDG_CONFIG_DIRS in addition to $XDG_CONFIG_HOME when searching +- for init.ml and use this to extend init.ml support to the toplevel when +- running on Windows. +- (David Allsopp, report by Jonah Beckford, review by Nicolás Ojeda Bär and +- Antonin Décimo) +- +-- #12688: Setting the env variable `NO_COLOR` with an empty value no longer +- has effects. Previously, setting `NO_COLOR` with any value, including +- the empty value, would disable colors (unless `OCAML_COLOR` is also set). +- After this change, the user must set `NO_COLOR` with an non-empty value +- to disable colors. This reflects a specification clarification/change +- from the upstream website at https://no-color.org. +- (Favonia, review by Gabriel Scherer) +- +-- #12744: ocamltest: run tests in recursive subdirs more eagerly +- (Nick Roberts, review by Nicolás Ojeda Bär) +- +-- #12901, 12908: ocamllex: add overflow checks to prevent generating incorrect +- lexers; use unsigned numbers in the table encoding when possible. +- (Vincent Laviron, report by Edwin Török, review by Xavier Leroy) +- +-### Manual and documentation: +- +-- #12338: clarification of the documentation of process related function in +- the unix module regarding the first element of args and shell's pid. +- (Christophe Raffalli, review by Florian Angeletti) +- +-- #12473: Document in runtime/memory.c our current understanding of +- accesses to the OCaml heap from the C runtime code -- the problem +- of hybrid programs mixing two memory models. +- (Gabriel Scherer and Guillaume Munch-Maccagnoni, review by Olivier +- Nicole and Xavier Leroy) +- +-- #12694: Document in runtime/tsan.c the TSan instrumentation choices and the +- consequences with regard to the memory model. +- (Olivier Nicole, review by Miod Vallat, Gabriel Scherer, Guillaume +- Munch-Maccagnoni and Fabrice Buoro) +- +-- #12802: Add manual chapter about ThreadSanitizer support +- (Olivier Nicole, review by Miod Vallat, Sebastien Hinderer, Fabrice Buoro, +- Gabriel Scherer and KC Sivaramakrishnan) +- +-- #12819: Clarify which runtime interactions are allowed in custom ops +- (Basile Clément, review by Guillaume Munch-Maccagnoni and Xavier Leroy) +- +-- #12840: manual: update runtime tracing chapter for custom events (ex #12335) +- (Lucas Pluvinage, Sadiq Jaffer and Olivier Nicole, review by Gabriel Scherer, +- David Allsopp, Tim McGilchrist and Thomas Leonard) +- +-- #13066, update OCAMLRUNPARAM documentation for the stack size parameter l +- (Florian Angeletti, review by Nicolás Ojeda Bär, Tim McGilchrist, and +- Miod Vallat) +- +-- #13078: update Format tutorial on structural boxes to mention alignment +- questions. +- (Edwin Török, review by Florian Angeletti) +- +-- #13092: document the existence of the `[@@poll error]` built-in attribute +- (Florian Angeletti, review by Gabriel Scherer) +- + ### Compiler user-interface and warnings: + ++- #11989, #12246, RFC 31: New flag, -H, to allow for transitive dependencies ++ without including them in the initial environment. ++ (Chris Casinghino, François Bobot, and Gabriel Scherer, review by Leo White ++ and Stefan Muenzel, RFC by François Bobot) ++ ++ + * #10613, #12405: Simplify the values used for the system variable (`system:` in + `ocamlopt -config` or the `Config.system` constant). In particular, s390x and + ppc64 now report "linux" instead of "elf"; all variants of 32-bit ARM on Linux +@@ -493,11 +403,6 @@ OCaml 5.2.0 + (David Allsopp, request by Kate Deplaix, review by Sébastien Hinderer and + Xavier Leroy) + +-- #11989, #12246, RFC 31: New flag, -H, to allow for transitive dependencies +- without including them in the initial environment. +- (Chris Casinghino, François Bobot, and Gabriel Scherer, review by Leo White +- and Stefan Muenzel, RFC by François Bobot) +- + - #12247: configure: --disable-ocamldebug can now be used instead + of --disable-debugger (which remains available for compatibility) + (Gabriel Scherer, review by Damien Doligez and Sébastien Hinderer) +@@ -546,9 +451,125 @@ OCaml 5.2.0 + + * #12942: Fix an line ordering in some module inclusion error messages + (Nick Roberts, review by Florian Angeletti, report by Carl Eastlund) ++### Manual and documentation: ++ ++- #12338: clarification of the documentation of process related function in ++ the unix module regarding the first element of args and shell's pid. ++ (Christophe Raffalli, review by Florian Angeletti) ++ ++- #12473: Document in runtime/memory.c our current understanding of ++ accesses to the OCaml heap from the C runtime code -- the problem ++ of hybrid programs mixing two memory models. ++ (Gabriel Scherer and Guillaume Munch-Maccagnoni, review by Olivier ++ Nicole and Xavier Leroy) ++ ++- #12456: Document the incompatibility between effects on the one ++ hand, and `caml_callback` and asynchronous callbacks (signal ++ handlers, finalisers, memprof callbacks...) on the other hand. ++ (Guillaume Munch-Maccagnoni, review by KC Sivaramakrishnan) ++ ++- #12694: Document in runtime/tsan.c the TSan instrumentation choices and the ++ consequences with regard to the memory model. ++ (Olivier Nicole, review by Miod Vallat, Gabriel Scherer, Guillaume ++ Munch-Maccagnoni and Fabrice Buoro) ++ ++- #12802: Add manual chapter about ThreadSanitizer support ++ (Olivier Nicole, review by Miod Vallat, Sebastien Hinderer, Fabrice Buoro, ++ Gabriel Scherer and KC Sivaramakrishnan) ++ ++- #12819: Clarify which runtime interactions are allowed in custom ops ++ (Basile Clément, review by Guillaume Munch-Maccagnoni and Xavier Leroy) ++ ++- #12840: manual: update runtime tracing chapter for custom events (ex #12335) ++ (Lucas Pluvinage, Sadiq Jaffer and Olivier Nicole, review by Gabriel Scherer, ++ David Allsopp, Tim McGilchrist and Thomas Leonard) ++ ++- #13066, update OCAMLRUNPARAM documentation for the stack size parameter l ++ (Florian Angeletti, review by Nicolás Ojeda Bär, Tim McGilchrist, and ++ Miod Vallat) ++ ++- #13078: update Format tutorial on structural boxes to mention alignment ++ questions. ++ (Edwin Török, review by Florian Angeletti) ++ ++- #13092: document the existence of the `[@@poll error]` built-in attribute ++ (Florian Angeletti, review by Gabriel Scherer) ++ ++### Tools: ++ ++- #12340: testsuite: collect known issues with current -short-paths ++ implementation for existential types ++ (Florian Angeletti, Samuel Hym, review by Florian Angeletti and Thomas Refis) ++ ++- #12147: ocamllex: Allow carriage returns at the end of line directives. ++ (SeungCheol Jung, review by Nicolás Ojeda Bär) ++ ++- #12260: Fix invalid_argument on some external or module aliases in ocamlnat ++ (Fabian Hemmer, review by Vincent Laviron) ++ ++- #12185: New script language for ocamltest. ++ (Damien Doligez with Florian Angeletti, Sébastien Hinderer, Gabriel Scherer, ++ review by Sébastien Hinderer and Gabriel Scherer) ++ ++- #12371: ocamltest: fix recursive expansion of variables. ++ (Antonin Décimo, Damien Doligez, review by Sébastien Hinderer, ++ Damien Doligez, Gabriel Scherer, and Xavier Leroy) ++ ++* #12497, #12613: Make ocamlc/ocamlopt fail with an error when no ++ input files are specified to build an executable. ++ (Antonin Décimo, review by Sébastien Hinderer) ++ ++- #12576: ocamldep: various refactors. ++ (Antonin Décimo, review by Florian Angeletti, Gabriel Scherer, and Léo Andrès) ++ ++- #12615: ocamldoc: get rid of the odoc_literate and odoc_todo generators. ++ (Sébaistien Hinderer, review by Gabriel Scherer and Florian Angeletti) ++ ++- #12624: Use $XDG_CONFIG_DIRS in addition to $XDG_CONFIG_HOME when searching ++ for init.ml and use this to extend init.ml support to the toplevel when ++ running on Windows. ++ (David Allsopp, report by Jonah Beckford, review by Nicolás Ojeda Bär and ++ Antonin Décimo) ++ ++- #12688: Setting the env variable `NO_COLOR` with an empty value no longer ++ has effects. Previously, setting `NO_COLOR` with any value, including ++ the empty value, would disable colors (unless `OCAML_COLOR` is also set). ++ After this change, the user must set `NO_COLOR` with an non-empty value ++ to disable colors. This reflects a specification clarification/change ++ from the upstream website at https://no-color.org. ++ (Favonia, review by Gabriel Scherer) ++ ++- #12744: ocamltest: run tests in recursive subdirs more eagerly ++ (Nick Roberts, review by Nicolás Ojeda Bär) ++ ++- #12901, 12908: ocamllex: add overflow checks to prevent generating incorrect ++ lexers; use unsigned numbers in the table encoding when possible. ++ (Vincent Laviron, report by Edwin Török, review by Xavier Leroy) + + ### Internal/compiler-libs changes: + ++- #12508 : Add compiler-side support for project-wide occurrences in Merlin, by ++ generating index tables of all identifier occurrences. This extra data in .cmt ++ files is only added when the new flag -bin-annot-occurrences is passed. ++ (Ulysse Gérard, Nathanaëlle Courant, suggestions by Gabriel Scherer and Thomas ++ Refis, review by Florian Angeletti, Gabriel Scherer and Thomas Refis) ++ ++- #12236, #12386, #12391, #12496, #12673: Use syntax as sole determiner of arity ++ This changes function arity to be based solely on the source program's ++ parsetree. Previously, the heuristic for arity had more subtle heuristics ++ that involved type information about patterns. Function arity is important ++ because it determines when a pattern match's effects run and is an input ++ into the fast path for function application. ++ ++ This change affects tooling: it changes the function constructs in parsetree ++ and typedtree. ++ ++ See https://github.com/ocaml/RFCs/pull/32 for the original RFC. ++ ++ (Nick Roberts; review by Richard Eisenberg, Leo White, and Gabriel Scherer; ++ RFC by Stephen Dolan) ++ ++ + - #12639: parsing: Attach a location to the RHS of Ptyp_alias + and improve the 'alias type mismatch' error message. + (Jules Aguillon, review by Florian Angeletti) +@@ -583,21 +604,6 @@ OCaml 5.2.0 + in Typecore in favor of local mutable state. + (Nick Roberts, review by Takafumi Saikawa) + +-- #12236, #12386, #12391, #12496, #12673: Use syntax as sole determiner of arity +- This changes function arity to be based solely on the source program's +- parsetree. Previously, the heuristic for arity had more subtle heuristics +- that involved type information about patterns. Function arity is important +- because it determines when a pattern match's effects run and is an input +- into the fast path for function application. +- +- This change affects tooling: it changes the function constructs in parsetree +- and typedtree. +- +- See https://github.com/ocaml/RFCs/pull/32 for the original RFC. +- +- (Nick Roberts; review by Richard Eisenberg, Leo White, and Gabriel Scherer; +- RFC by Stephen Dolan) +- + - #12542: Minor bugfix to #12236: restore dropped call to `instance` + (Nick Roberts, review by Jacques Garrigue) + +@@ -650,12 +656,6 @@ OCaml 5.2.0 + - #12764: Move all installable headers in `caml/` sub-directories. + (Antonin Décimo, review by Gabriel Scherer and David Allsopp) + +-- #12508 : Add compiler-side support for project-wide occurrences in Merlin, by +- generating index tables of all identifier occurrences. This extra data in .cmt +- files is only added when the new flag -bin-annot-occurrences is passed. +- (Ulysse Gérard, Nathanaëlle Courant, suggestions by Gabriel Scherer and Thomas +- Refis, review by Florian Angeletti, Gabriel Scherer and Thomas Refis) +- + - #12914: Slightly change the s390x assembly dialect in order to build with + Clang's integrated assembler. + (Miod Vallat, review by Gabriel Scherer) +@@ -888,6 +888,10 @@ OCaml 5.2.0 + - #13094: Fix undefined behavior of left-shifting a negative number. + (Antonin Décimo, review by Miod Vallat and Nicolás Ojeda Bär) + ++- #13130: minor fixes to pprintast for raw identifiers and local module open ++ syntax for types. ++ (Chet Murthy, review by Gabriel Scherer) ++ + OCaml 5.1.1 (8 December 2023) + ---------------------------- + +-- +2.44.0 + diff --git a/0001-Don-t-add-rpaths-to-libraries.patch b/0003-Don-t-add-rpaths-to-libraries.patch similarity index 79% rename from 0001-Don-t-add-rpaths-to-libraries.patch rename to 0003-Don-t-add-rpaths-to-libraries.patch index 04773ec..c3c1373 100644 --- a/0001-Don-t-add-rpaths-to-libraries.patch +++ b/0003-Don-t-add-rpaths-to-libraries.patch @@ -1,14 +1,14 @@ -From 799bf9088c131fc71626a48e9987e4d44a2f0194 Mon Sep 17 00:00:00 2001 +From 507a1382cb82160c2a6cfc0ea5bcb3e33ece7307 Mon Sep 17 00:00:00 2001 From: "Richard W.M. Jones" Date: Tue, 24 Jun 2014 10:00:15 +0100 -Subject: [PATCH 1/2] Don't add rpaths to libraries. +Subject: [PATCH 3/5] Don't add rpaths to libraries. --- configure.ac | 2 -- 1 file changed, 2 deletions(-) diff --git a/configure.ac b/configure.ac -index b81da53c42..892a2a894f 100644 +index 0c9d63859a..48aa9f0a29 100644 --- a/configure.ac +++ b/configure.ac @@ -1221,8 +1221,6 @@ AS_IF([test x"$enable_shared" != "xno"], @@ -21,5 +21,5 @@ index b81da53c42..892a2a894f 100644 supports_shared_libraries=true], [mkdll='shared-libs-not-available']) -- -2.43.0 +2.44.0 diff --git a/0002-configure-Allow-user-defined-C-compiler-flags.patch b/0004-configure-Allow-user-defined-C-compiler-flags.patch similarity index 88% rename from 0002-configure-Allow-user-defined-C-compiler-flags.patch rename to 0004-configure-Allow-user-defined-C-compiler-flags.patch index 569b4a1..7c447ff 100644 --- a/0002-configure-Allow-user-defined-C-compiler-flags.patch +++ b/0004-configure-Allow-user-defined-C-compiler-flags.patch @@ -1,14 +1,14 @@ -From f2b875e8201efed22267136096b1e5df97f99f84 Mon Sep 17 00:00:00 2001 +From edd903fc73b98eb784b307a47110985967cb1d09 Mon Sep 17 00:00:00 2001 From: "Richard W.M. Jones" Date: Tue, 29 May 2012 20:44:18 +0100 -Subject: [PATCH 2/2] configure: Allow user defined C compiler flags. +Subject: [PATCH 4/5] configure: Allow user defined C compiler flags. --- configure.ac | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/configure.ac b/configure.ac -index 892a2a894f..e8f6cbc863 100644 +index 48aa9f0a29..fc29c88f50 100644 --- a/configure.ac +++ b/configure.ac @@ -869,6 +869,10 @@ AS_CASE([$ocaml_cc_vendor], @@ -41,5 +41,5 @@ index 892a2a894f..e8f6cbc863 100644 mkexe_ldflags="\$(OC_LDFLAGS) \$(LDFLAGS)" mkexe_ldflags_exp="${oc_ldflags} ${LDFLAGS}" -- -2.43.0 +2.44.0 diff --git a/0005-flambda-Improve-transitive-closure-in-invariant_para.patch b/0005-flambda-Improve-transitive-closure-in-invariant_para.patch new file mode 100644 index 0000000..808a96c --- /dev/null +++ b/0005-flambda-Improve-transitive-closure-in-invariant_para.patch @@ -0,0 +1,114 @@ +From acdc441ff1acb5390467e649bc9a9bfddd7df774 Mon Sep 17 00:00:00 2001 +From: Florian Weimer +Date: Thu, 9 May 2024 10:03:23 +0200 +Subject: [PATCH 5/5] flambda: Improve transitive closure in + invariant_params_in_recursion (#13150) + +The old implementation did not really exploit the sparseness of the +graph because it used newly discovered edges in later iterations. +The new implementation processes each original relation only once +per starting node, and does not re-process newly discovered relations. + +(cherry picked from commit 787b4fbb5aaf3728de54ca240ba9ca0bf56ace60) +--- + Changes | 5 ++ + middle_end/flambda/invariant_params.ml | 66 ++++++++++---------------- + 2 files changed, 31 insertions(+), 40 deletions(-) + +diff --git a/Changes b/Changes +index 75842fc216..d26512067d 100644 +--- a/Changes ++++ b/Changes +@@ -1,6 +1,11 @@ + OCaml 5.2.0 (13 May 2024) + ------------------------- + ++- #13150: improve a transitive-closure computation algorithm in the flambda ++ middle-end to avoid a compilation time blowup on Menhir-generated code ++ (Florian Weimer, review by Gabriel Scherer and Pierre Chambart, ++ report by Richard Jones) ++ + (Changes that can break existing programs are marked with a "*") + + ### Restored and new backends: +diff --git a/middle_end/flambda/invariant_params.ml b/middle_end/flambda/invariant_params.ml +index 414d39310a..dba63970fd 100644 +--- a/middle_end/flambda/invariant_params.ml ++++ b/middle_end/flambda/invariant_params.ml +@@ -65,47 +65,33 @@ let implies relation from to_ = + relation + + let transitive_closure state = +- let union s1 s2 = +- match s1, s2 with +- | Top, _ | _, Top -> Top +- | Implication s1, Implication s2 -> +- Implication (Variable.Pair.Set.union s1 s2) ++ (* Depth-first search for all implications for one argument. ++ Arguments are moved from candidate to frontier, assuming ++ they are newly added to the result. *) ++ let rec loop candidate frontier result = ++ match (candidate, frontier) with ++ | ([], []) -> Implication result ++ | ([], frontier::fs) -> ++ (* Obtain fresh candidate for the frontier argument. *) ++ (match Variable.Pair.Map.find frontier state with ++ | exception Not_found -> loop [] fs result ++ | Top -> Top ++ | Implication candidate -> ++ loop (Variable.Pair.Set.elements candidate) fs result) ++ | (candidate::cs, frontier) -> ++ let result' = Variable.Pair.Set.add candidate result in ++ if result' != result then ++ (* Result change means candidate becomes part of frontier. *) ++ loop cs (candidate :: frontier) result' ++ else ++ loop cs frontier result + in +- let equal s1 s2 = +- match s1, s2 with +- | Top, Implication _ | Implication _, Top -> false +- | Top, Top -> true +- | Implication s1, Implication s2 -> Variable.Pair.Set.equal s1 s2 +- in +- let update arg state = +- let original_set = +- try Variable.Pair.Map.find arg state with +- | Not_found -> Implication Variable.Pair.Set.empty +- in +- match original_set with +- | Top -> state +- | Implication arguments -> +- let set = +- Variable.Pair.Set.fold +- (fun orig acc-> +- let set = +- try Variable.Pair.Map.find orig state with +- | Not_found -> Implication Variable.Pair.Set.empty in +- union set acc) +- arguments original_set +- in +- Variable.Pair.Map.add arg set state +- in +- let once state = +- Variable.Pair.Map.fold (fun arg _ state -> update arg state) state state +- in +- let rec fp state = +- let state' = once state in +- if Variable.Pair.Map.equal equal state state' +- then state +- else fp state' +- in +- fp state ++ Variable.Pair.Map.map ++ (fun set -> ++ match set with ++ | Top -> Top ++ | Implication set -> loop [] (Variable.Pair.Set.elements set) set) ++ state + + (* CR-soon pchambart: to move to Flambda_utils and document + mshinwell: I think this calculation is basically the same as +-- +2.44.0 + diff --git a/ocaml.spec b/ocaml.spec index 64db332..991fcc3 100644 --- a/ocaml.spec +++ b/ocaml.spec @@ -1,10 +1,11 @@ # Don't add -Wl,-dT, %undefine _package_note_flags -# OCaml 5.1 broke building with LTO. A file prims.c is generated with primitive -# function declarations, all with "void" for their parameter list. This does -# not match the real definitions, leading to lots of -Wlto-type-mismatch -# warnings. These change the output of the tests, leading to many failed tests. +# OCaml 5.1 broke building with LTO. A file prims.c is generated with +# primitive function declarations, all with "void" for their parameter +# list. This does not match the real definitions, leading to lots of +# -Wlto-type-mismatch warnings. These change the output of the tests, +# leading to many failed tests. This is still a problem in 5.2. %global _lto_cflags %{nil} # OCaml has a bytecode backend that works on anything with a C @@ -65,15 +66,25 @@ Source2: ocaml_files.py # # https://pagure.io/fedora-ocaml # -# Current branch: fedora-40-5.1.1 +# Current branch: fedora-41-5.2.0 # # ALTERNATIVELY add a patch to the end of the list (leaving the # existing patches unchanged) adding a comment to note that it should # be incorporated into the git repo at a later time. +# Upstream after 5.2.0: +Patch: 0001-Changes-synchronisation-and-consistency-with-trunk.patch +Patch: 0002-Changes-copy-editing.patch + # Fedora-specific patches -Patch: 0001-Don-t-add-rpaths-to-libraries.patch -Patch: 0002-configure-Allow-user-defined-C-compiler-flags.patch +Patch: 0003-Don-t-add-rpaths-to-libraries.patch +Patch: 0004-configure-Allow-user-defined-C-compiler-flags.patch + +# Improve performance of flambda optimizer in some cases. Required to +# compiler blow-up in coccinelle package. Upstream, but not included +# in 5.2 branch. +# https://github.com/ocaml/ocaml/pull/13150 +Patch: 0005-flambda-Improve-transitive-closure-in-invariant_para.patch BuildRequires: make BuildRequires: git @@ -103,7 +114,7 @@ Requires: libzstd-devel%{?_isa} Requires: ocaml-runtime%{?_isa} = %{version}-%{release} # Force ocaml-srpm-macros to be at the latest version, both for builds -# and installs, since OCaml 5.1 has a different set of native code +# and installs, since OCaml 5.2 has a different set of native code # generators than previous versions. BuildRequires: ocaml-srpm-macros >= 10 Requires: ocaml-srpm-macros >= 10 @@ -462,7 +473,7 @@ hardlink -t $RPM_BUILD_ROOT%{_libdir}/ocaml/stublibs %changelog * Thu May 23 2024 Jerry James - 5.2.0-1 -- Version 5.2.0 +- New upstream version 5.2.0 (RHBZ#2269805) - Drop upstreamed frame pointer and s390x patches * Thu Jan 25 2024 Fedora Release Engineering - 5.1.1-4