commit d147496cdb46d56aea67ea0728c77a7281859b0d Author: MSVSphere Packaging Team Date: Fri Oct 25 17:21:26 2024 +0300 import ocaml-5.2.0-3.el10 diff --git a/.gitignore b/.gitignore new file mode 100644 index 0000000..518ef2a --- /dev/null +++ b/.gitignore @@ -0,0 +1 @@ +SOURCES/ocaml-5.2.0.tar.gz diff --git a/.ocaml.metadata b/.ocaml.metadata new file mode 100644 index 0000000..e01cc33 --- /dev/null +++ b/.ocaml.metadata @@ -0,0 +1 @@ +b404edd5d605b271a1b094a00bdff011a2d5ac17 SOURCES/ocaml-5.2.0.tar.gz diff --git a/SOURCES/0001-Changes-synchronisation-and-consistency-with-trunk.patch b/SOURCES/0001-Changes-synchronisation-and-consistency-with-trunk.patch new file mode 100644 index 0000000..a1f33b7 --- /dev/null +++ b/SOURCES/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/7] 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/SOURCES/0002-Changes-copy-editing.patch b/SOURCES/0002-Changes-copy-editing.patch new file mode 100644 index 0000000..7633e01 --- /dev/null +++ b/SOURCES/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/7] 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/SOURCES/0003-Don-t-add-rpaths-to-libraries.patch b/SOURCES/0003-Don-t-add-rpaths-to-libraries.patch new file mode 100644 index 0000000..3b3e9f9 --- /dev/null +++ b/SOURCES/0003-Don-t-add-rpaths-to-libraries.patch @@ -0,0 +1,25 @@ +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 3/7] Don't add rpaths to libraries. + +--- + configure.ac | 2 -- + 1 file changed, 2 deletions(-) + +diff --git a/configure.ac b/configure.ac +index 0c9d63859a..48aa9f0a29 100644 +--- a/configure.ac ++++ b/configure.ac +@@ -1221,8 +1221,6 @@ AS_IF([test x"$enable_shared" != "xno"], + [[*-*-openbsd7.[3-9]|*-*-openbsd[89].*]], + [mkdll_flags="${mkdll_flags} -Wl,--no-execute-only"]) + oc_ldflags="$oc_ldflags -Wl,-E" +- rpath="-Wl,-rpath," +- mksharedlibrpath="-Wl,-rpath," + natdynlinkopts="-Wl,-E" + supports_shared_libraries=true], + [mkdll='shared-libs-not-available']) +-- +2.44.0 + diff --git a/SOURCES/0004-configure-Allow-user-defined-C-compiler-flags.patch b/SOURCES/0004-configure-Allow-user-defined-C-compiler-flags.patch new file mode 100644 index 0000000..3c14867 --- /dev/null +++ b/SOURCES/0004-configure-Allow-user-defined-C-compiler-flags.patch @@ -0,0 +1,45 @@ +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 4/7] 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 48aa9f0a29..fc29c88f50 100644 +--- a/configure.ac ++++ b/configure.ac +@@ -869,6 +869,10 @@ AS_CASE([$ocaml_cc_vendor], + internal_cflags="$cc_warnings"], + [common_cflags="-O"]) + ++# Allow CFLAGS and LDFLAGS to be added. ++common_cflags="$common_cflags $CFLAGS" ++cclibs="$cclibs $LDFLAGS" ++ + # Enable SSE2 on x86 mingw to avoid using 80-bit registers. + AS_CASE([$host], + [i686-*-mingw32*], +@@ -2648,7 +2652,7 @@ AC_CONFIG_COMMANDS_PRE([ + [mkexedebugflag="${mkexe_ldflags_prefix}${mkexedebugflag}"]) + mkdll_ldflags="" + AS_IF([test -n "${LDFLAGS}"], +- [for flag in ${LDFLAGS}; do ++ [for flag in "${LDFLAGS}"; do + mkdll_ldflags="${mkdll_ldflags} ${mkexe_ldflags_prefix}${flag}" + done + mkdll_ldflags_exp="$mkdll_ldflags"]) +@@ -2674,7 +2678,7 @@ ${mkdll_ldflags}" + ],[ + mkdll_ldflags='$(OC_DLL_LDFLAGS) $(LDFLAGS)' + mkdll_ldflags_exp="${oc_dll_ldflags}" +- AS_IF([test -n ${LDFLAGS}], ++ AS_IF([test -n "${LDFLAGS}"], + [mkdll_ldflags_exp="$mkdll_ldflags_exp $LDFLAGS"]) + mkexe_ldflags="\$(OC_LDFLAGS) \$(LDFLAGS)" + mkexe_ldflags_exp="${oc_ldflags} ${LDFLAGS}" +-- +2.44.0 + diff --git a/SOURCES/0005-flambda-Improve-transitive-closure-in-invariant_para.patch b/SOURCES/0005-flambda-Improve-transitive-closure-in-invariant_para.patch new file mode 100644 index 0000000..b0b347c --- /dev/null +++ b/SOURCES/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/7] 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/SOURCES/0006-Reload-exception-pointer-register-in-caml_c_call.patch b/SOURCES/0006-Reload-exception-pointer-register-in-caml_c_call.patch new file mode 100644 index 0000000..4c20a85 --- /dev/null +++ b/SOURCES/0006-Reload-exception-pointer-register-in-caml_c_call.patch @@ -0,0 +1,165 @@ +From 8637cac022907501c3c0d941e07e436b70c9d4ac Mon Sep 17 00:00:00 2001 +From: Miod Vallat <118974489+dustanddreams@users.noreply.github.com> +Date: Thu, 30 May 2024 09:57:41 +0000 +Subject: [PATCH 6/7] Reload exception pointer register in caml_c_call* + +The invoked code may end up causing caml_try_realloc_stack() to be invoked, +which in turn may replace the stack TRAP_PTR points to, leading to +either crashes with the debug runtime (thanks to the old stack contents +being overwritten) or all kinds of memory or control flow corruption otherwise. + +Added test for stack reallocation in callback followed by exception raising. + +(cherry picked from commit 6964d3a90f84402ed6066fb1821679435e063067) +(cherry picked from commit 1e8a91d305f1fa4668444fb1cce97952dbc39810) +--- + Changes | 9 +++++++++ + runtime/arm64.S | 6 ++++-- + runtime/power.S | 6 ++++-- + runtime/riscv.S | 6 ++++-- + runtime/s390x.S | 5 +++-- + testsuite/tests/callback/test1.ml | 5 +++++ + 6 files changed, 29 insertions(+), 8 deletions(-) + +diff --git a/Changes b/Changes +index d26512067d..53bb5369b9 100644 +--- a/Changes ++++ b/Changes +@@ -1,3 +1,12 @@ ++OCaml 5.2 maintenance version ++----------------------------- ++ ++- #13207: Be sure to reload the register caching the exception handler in ++ caml_c_call and caml_c_call_stack_args, as its value may have been changed ++ if the OCaml stack is expanded during a callback. ++ (Miod Vallat, report by Vesa Karvonen, review by Gabriel Scherer and ++ Xavier Leroy) ++ + OCaml 5.2.0 (13 May 2024) + ------------------------- + +diff --git a/runtime/arm64.S b/runtime/arm64.S +index e71f25ebba..6c6495a0a8 100644 +--- a/runtime/arm64.S ++++ b/runtime/arm64.S +@@ -569,8 +569,9 @@ FUNCTION(caml_c_call) + str TRAP_PTR, Caml_state(exn_handler) + /* Call the function */ + blr ADDITIONAL_ARG +- /* Reload alloc ptr */ ++ /* Reload new allocation pointer & exn handler */ + ldr ALLOC_PTR, Caml_state(young_ptr) ++ ldr TRAP_PTR, Caml_state(exn_handler) + /* Load ocaml stack */ + SWITCH_C_TO_OCAML + #if defined(WITH_THREAD_SANITIZER) +@@ -625,8 +626,9 @@ FUNCTION(caml_c_call_stack_args) + blr ADDITIONAL_ARG + /* Restore stack */ + mov sp, x19 +- /* Reload alloc ptr */ ++ /* Reload new allocation pointer & exn handler */ + ldr ALLOC_PTR, Caml_state(young_ptr) ++ ldr TRAP_PTR, Caml_state(exn_handler) + /* Switch from C to OCaml */ + SWITCH_C_TO_OCAML + /* Return */ +diff --git a/runtime/power.S b/runtime/power.S +index bfb37fa989..257678100e 100644 +--- a/runtime/power.S ++++ b/runtime/power.S +@@ -445,8 +445,9 @@ FUNCTION caml_c_call + mr 2, C_CALL_TOC /* restore current TOC */ + /* Restore return address (in register C_CALL_RET_ADDR, preserved by C) */ + mtlr C_CALL_RET_ADDR +- /* Reload allocation pointer*/ ++ /* Reload new allocation pointer and exception pointer */ + ld ALLOC_PTR, Caml_state(young_ptr) ++ ld TRAP_PTR, Caml_state(exn_handler) + #if defined(WITH_THREAD_SANITIZER) + TSAN_SETUP_C_CALL 16 + /* Save return value registers. Since the called function could be anything, +@@ -497,8 +498,9 @@ FUNCTION caml_c_call_stack_args + add SP, SP, STACK_ARG_BYTES + /* Restore return address (in register C_CALL_RET_ADDR, preserved by C) */ + mtlr C_CALL_RET_ADDR +- /* Reload allocation pointer*/ ++ /* Reload new allocation pointer and exception pointer */ + ld ALLOC_PTR, Caml_state(young_ptr) ++ ld TRAP_PTR, Caml_state(exn_handler) + /* Switch from C to OCaml */ + SWITCH_C_TO_OCAML + /* Return to caller */ +diff --git a/runtime/riscv.S b/runtime/riscv.S +index a2eca7a315..8934db0bb3 100644 +--- a/runtime/riscv.S ++++ b/runtime/riscv.S +@@ -516,8 +516,9 @@ L(caml_c_call): + sd TRAP_PTR, Caml_state(exn_handler) + /* Call the function */ + jalr ADDITIONAL_ARG +- /* Reload alloc ptr */ ++ /* Reload new allocation pointer & exn handler */ + ld ALLOC_PTR, Caml_state(young_ptr) ++ ld TRAP_PTR, Caml_state(exn_handler) + /* Load ocaml stack */ + SWITCH_C_TO_OCAML + #if defined(WITH_THREAD_SANITIZER) +@@ -575,8 +576,9 @@ FUNCTION(caml_c_call_stack_args) + jalr ADDITIONAL_ARG + /* Restore stack */ + mv sp, s2 +- /* Reload alloc ptr */ ++ /* Reload new allocation pointer & exn handler */ + ld ALLOC_PTR, Caml_state(young_ptr) ++ ld TRAP_PTR, Caml_state(exn_handler) + /* Switch from C to OCaml */ + SWITCH_C_TO_OCAML + /* Return */ +diff --git a/runtime/s390x.S b/runtime/s390x.S +index b59822ce57..113831a376 100644 +--- a/runtime/s390x.S ++++ b/runtime/s390x.S +@@ -515,7 +515,7 @@ LBL(caml_c_call): + #endif + basr %r14, ADDITIONAL_ARG + CLEANUP_AFTER_C_CALL +- /* Reload alloc ptr */ ++ /* Reload new allocation pointer & exn handler */ + lg ALLOC_PTR, Caml_state(young_ptr) + lg TRAP_PTR, Caml_state(exn_handler) + /* Load ocaml stack and restore global variables */ +@@ -584,8 +584,9 @@ LBL(106): + CLEANUP_AFTER_C_CALL + /* Restore stack */ + lgr %r15, %r12 +- /* Reload alloc ptr */ ++ /* Reload new allocation pointer & exn handler */ + lg ALLOC_PTR, Caml_state(young_ptr) ++ lg TRAP_PTR, Caml_state(exn_handler) + /* Switch from C to OCaml */ + SWITCH_C_TO_OCAML + /* Return */ +diff --git a/testsuite/tests/callback/test1.ml b/testsuite/tests/callback/test1.ml +index c39be0c586..f6ad4356cf 100644 +--- a/testsuite/tests/callback/test1.ml ++++ b/testsuite/tests/callback/test1.ml +@@ -11,6 +11,9 @@ external mycallback3 : ('a -> 'b -> 'c -> 'd) -> 'a -> 'b -> 'c -> 'd + external mycallback4 : + ('a -> 'b -> 'c -> 'd -> 'e) -> 'a -> 'b -> 'c -> 'd -> 'e = "mycallback4" + ++let rec growstack n = ++ if n <= 0 then 0 else 1 + growstack (n - 1) ++ + let rec tak (x, y, z as _tuple) = + if x > y then tak(tak (x-1, y, z), tak (y-1, z, x), tak (z-1, x, y)) + else z +@@ -46,3 +49,5 @@ let _ = + print_int(trapexit ()); print_newline(); + print_string(tripwire mypushroot); print_newline(); + print_string(tripwire mycamlparam); print_newline(); ++ begin try ignore (mycallback1 growstack 1_000); raise Exit ++ with Exit -> () end +-- +2.44.0 + diff --git a/SOURCES/0007-Compute-more-accurate-instruction-sizes-for-branch-r.patch b/SOURCES/0007-Compute-more-accurate-instruction-sizes-for-branch-r.patch new file mode 100644 index 0000000..e9dd879 --- /dev/null +++ b/SOURCES/0007-Compute-more-accurate-instruction-sizes-for-branch-r.patch @@ -0,0 +1,178 @@ +From 4eb80b13779125fcd76a445ab0004ca064fab634 Mon Sep 17 00:00:00 2001 +From: Miod Vallat +Date: Fri, 7 Jun 2024 06:19:45 +0000 +Subject: [PATCH 7/7] Compute more accurate instruction sizes for branch + relaxation. + +(cherry picked from commit 114ddae2d4c85391a4f939dc6623424ae35a07aa) +--- + Changes | 4 ++ + asmcomp/power/emit.mlp | 87 ++++++++++++++++++++++++------------------ + 2 files changed, 53 insertions(+), 38 deletions(-) + +diff --git a/Changes b/Changes +index 53bb5369b9..1a81509247 100644 +--- a/Changes ++++ b/Changes +@@ -7,6 +7,10 @@ OCaml 5.2 maintenance version + (Miod Vallat, report by Vesa Karvonen, review by Gabriel Scherer and + Xavier Leroy) + ++- #13221: Compute more accurate instruction sizes for branch relocation on ++ POWER. ++ (Miod Vallat, review by Gabriel Scherer) ++ + OCaml 5.2.0 (13 May 2024) + ------------------------- + +diff --git a/asmcomp/power/emit.mlp b/asmcomp/power/emit.mlp +index 47f5419a92..fdf22996fa 100644 +--- a/asmcomp/power/emit.mlp ++++ b/asmcomp/power/emit.mlp +@@ -177,6 +177,28 @@ let emit_tocload emit_dest dest entry = + + (* Output a load or store operation *) + ++let load_mnemonic = function ++ | Byte_unsigned -> "lbz" ++ | Byte_signed -> "lbz" ++ | Sixteen_unsigned -> "lhz" ++ | Sixteen_signed -> "lha" ++ | Thirtytwo_unsigned -> "lwz" ++ | Thirtytwo_signed -> "lwa" ++ | Word_int | Word_val -> "ld" ++ | Single -> "lfs" ++ | Double -> "lfd" ++ ++let store_mnemonic = function ++ | Byte_unsigned | Byte_signed -> "stb" ++ | Sixteen_unsigned | Sixteen_signed -> "sth" ++ | Thirtytwo_unsigned | Thirtytwo_signed -> "stw" ++ | Word_int | Word_val -> "std" ++ | Single -> "stfs" ++ | Double -> "stfd" ++ ++let store_needs_lwsync chunk assignment = ++ assignment && (chunk = Word_int || chunk = Word_val) ++ + let valid_offset instr ofs = + ofs land 3 = 0 || (instr <> "ld" && instr <> "std" && instr <> "lwa") + +@@ -383,11 +405,17 @@ module BR = Branch_relaxation.Make (struct + + let tocload_size = 2 + +- let load_store_size = function ++ let load_store_size instr = function + | Ibased(_s, d) -> +- let (_lo, hi) = low_high_s d in +- tocload_size + (if hi = 0 then 1 else 2) +- | Iindexed ofs -> if is_immediate ofs then 1 else 3 ++ let (lo, hi) = low_high_s d in ++ tocload_size + ++ (if hi <> 0 then 1 else 0) + ++ (if valid_offset instr lo then 1 else 2) ++ | Iindexed ofs -> ++ if is_immediate ofs && valid_offset instr ofs then 1 else begin ++ let (lo, _hi) = low_high_u ofs in ++ if lo <> 0 then 3 else 2 ++ end + | Iindexed2 -> 1 + + let instr_size f = function +@@ -415,16 +443,16 @@ module BR = Branch_relaxation.Make (struct + else if alloc then tocload_size + 2 + else 5 + | Lop(Istackoffset _) -> 1 +- | Lop(Iload {memory_chunk; addressing_mode; _ }) -> +- if memory_chunk = Byte_signed +- then load_store_size addressing_mode + 1 +- else load_store_size addressing_mode ++ | Lop(Iload {memory_chunk; addressing_mode; is_atomic }) -> ++ let loadinstr = load_mnemonic memory_chunk in ++ (if is_atomic then 4 else 0) + ++ (if memory_chunk = Byte_signed then 1 else 0) + ++ load_store_size loadinstr addressing_mode + | Lop(Istore(chunk, addr, assignment)) -> +- (match chunk with +- | Single -> 1 +- | Word_int | Word_val when assignment -> 1 +- | _ -> 0) +- + load_store_size addr ++ let storeinstr = store_mnemonic chunk in ++ (if chunk = Single then 1 else 0) + ++ (if store_needs_lwsync chunk assignment then 1 else 0) + ++ load_store_size storeinstr addr + | Lop(Ialloc _) -> 5 + | Lop(Ispecific(Ialloc_far _)) -> 6 + | Lop(Ipoll { return_label = Some(_) }) -> 5 +@@ -442,12 +470,12 @@ module BR = Branch_relaxation.Make (struct + | Lop(Ispecific(Icheckbound_imm_far _)) -> 3 + | Lop(Iintop_imm _) -> 1 + | Lop(Inegf | Iabsf | Iaddf | Isubf | Imulf | Idivf) -> 1 +- | Lop(Ifloatofint) -> 9 +- | Lop(Iintoffloat) -> 4 ++ | Lop(Ifloatofint) -> 3 ++ | Lop(Iintoffloat) -> 3 + | Lop(Iopaque) -> 0 + | Lop(Ispecific _) -> 1 +- | Lop (Idls_get) -> 1 +- | Lop (Ireturn_addr) -> 1 ++ | Lop(Idls_get) -> 1 ++ | Lop(Ireturn_addr) -> 1 + | Lreloadretaddr -> 2 + | Lreturn -> 2 + | Llabel _ -> 0 +@@ -457,7 +485,7 @@ module BR = Branch_relaxation.Make (struct + 1 + (if lbl0 = None then 0 else 1) + + (if lbl1 = None then 0 else 1) + + (if lbl2 = None then 0 else 1) +- | Lswitch _ -> 5 + tocload_size ++ | Lswitch _ -> 7 + tocload_size + | Lentertrap -> 1 + | Ladjust_trap_depth _ -> 0 + | Lpushtrap _ -> 4 + tocload_size +@@ -705,17 +733,7 @@ let emit_instr env i = + ` addi 1, 1, {emit_int (-n)}\n`; + adjust_stack_offset env n + | Lop(Iload { memory_chunk; addressing_mode; is_atomic }) -> +- let loadinstr = +- match memory_chunk with +- | Byte_unsigned -> "lbz" +- | Byte_signed -> "lbz" +- | Sixteen_unsigned -> "lhz" +- | Sixteen_signed -> "lha" +- | Thirtytwo_unsigned -> "lwz" +- | Thirtytwo_signed -> "lwa" +- | Word_int | Word_val -> "ld" +- | Single -> "lfs" +- | Double -> "lfd" in ++ let loadinstr = load_mnemonic memory_chunk in + if is_atomic then + ` sync\n`; + emit_load_store loadinstr addressing_mode i.arg 0 i.res.(0); +@@ -731,19 +749,12 @@ let emit_instr env i = + ` frsp {emit_reg tmp}, {emit_reg i.arg.(0)}\n`; + emit_load_store "stfs" addr i.arg 1 tmp + | Lop(Istore(chunk, addr, assignment)) -> +- let storeinstr = +- match chunk with +- | Byte_unsigned | Byte_signed -> "stb" +- | Sixteen_unsigned | Sixteen_signed -> "sth" +- | Thirtytwo_unsigned | Thirtytwo_signed -> "stw" +- | Word_int | Word_val -> "std" +- | Single -> assert false +- | Double -> "stfd" in ++ let storeinstr = store_mnemonic chunk in + (* Non-initializing stores need a memory barrier to follow the + Multicore OCaml memory model. Stores of size other than + Word_int and Word_val do not follow the memory model and therefore + do not need a barrier *) +- if assignment && (chunk = Word_int || chunk = Word_val) then ++ if store_needs_lwsync chunk assignment then + ` lwsync\n`; + emit_load_store storeinstr addr i.arg 1 i.arg.(0) + | Lop(Ialloc { bytes; dbginfo }) -> +-- +2.44.0 + diff --git a/SOURCES/macros.ocaml-rpm b/SOURCES/macros.ocaml-rpm new file mode 100644 index 0000000..ac94c48 --- /dev/null +++ b/SOURCES/macros.ocaml-rpm @@ -0,0 +1,69 @@ +# Make %files lists from an installed tree of files. +# Options: +# -s: separate packaging; every subdirectory of %%{ocamldir}, except stublibs, +# is placed in its own package. This option requires the existence of opam +# *.install files in the build tree. +# -n: suppress creation of a devel subpackage. +%ocaml_files(sn) %{python3} /usr/lib/rpm/redhat/ocaml_files.py %{-s} %{-n} %{buildroot} %{ocamldir} + +# Internal macro holding the common parts of ocaml_install and dune_install +%ocaml_install_common(sn) %{expand: +rm -rf %{buildroot}%{_prefix}/doc +mlis=$(find %{buildroot}%{_libdir}/ocaml -name '*.mli') +rm -f ${mlis//.mli/.ml} +%ocaml_files %{-s} %{-n}} + +# Install files listed in opam *.install files. +# Options: +# -s: separate packaging; every subdirectory of %%{ocamldir}, except stublibs, +# is placed in its own package. +# -n: suppress creation of a devel subpackage. +%ocaml_install(sn) %{expand: +%{python3} /usr/lib/rpm/redhat/ocaml_files.py -i %{-s} %{-n} %{buildroot} %{ocamldir} +%ocaml_install_common %{-s} %{-n}} + +# Add smp_mflags to arguments if no -j release option is given. +# Add --release to arguments if no -p or --release option is given. +# Add --verbose to arguments if it is not given. +%dune_add_flags(-) %{lua: + has_j = false + has_p = false + has_v = false + for _, flag in pairs(arg) do + if flag:find("^-j") then + has_j = true + elseif flag:find("^-p") or flag:find("^--release)") then + has_p = true + elseif flag:find("^--verbose") then + has_v = true + end + end + if not has_j then + table.insert(arg, 1, rpm.expand("%{?_smp_mflags}")) + end + if not has_p then + table.insert(arg, 1, "--release") + end + if not has_v then + table.insert(arg, 1, "--verbose") + end + print(table.concat(arg, " ")) +} + +# Build with dune +%dune_build(-) dune build %{dune_add_flags %*} + +# Run tests with dune +%dune_check(-) dune runtest %{dune_add_flags %*} + +# Install with dune +# Options: +# -s: separate packaging; every subdirectory of %%{ocamldir}, except stublibs, +# is placed in its own package. +# -n: suppress creation of a devel subpackage. +%dune_install(sn) %{expand: +dune install --destdir=%{buildroot} %{dune_add_flags %*} +if [ -d _build/default/_doc/_html ]; then + find _build/default/_doc/_html -name .dune-keep -delete +fi +%ocaml_install_common %{-s} %{-n}} diff --git a/SOURCES/ocaml_files.py b/SOURCES/ocaml_files.py new file mode 100644 index 0000000..cf4afd1 --- /dev/null +++ b/SOURCES/ocaml_files.py @@ -0,0 +1,451 @@ +# Copyright 2022-3, Jerry James +# +# Redistribution and use in source and binary forms, with or without +# modification, are permitted provided that the following conditions +# are met: +# +# 1. Redistributions of source code must retain the above copyright +# notice, this list of conditions and the following disclaimer. +# 2. Redistributions in binary form must reproduce the above copyright +# notice, this list of conditions and the following disclaimer in the +# documentation and/or other materials provided with the +# distribution. +# 3. Neither the name of Red Hat nor the names of its +# contributors may be used to endorse or promote products derived +# from this software without specific prior written permission. +# +# THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +# "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT +# LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR +# A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT +# OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, +# SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT +# LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, +# DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY +# THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT +# (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE +# OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. + +import argparse +import os +import shutil +import string +import sys +from collections.abc import Iterable, Iterator +from enum import Enum, auto +from typing import Callable, final + +# Version of this script +version=2 + +# +# BUILDROOT CATEGORIZATION +# + +# Directories to ignore when generating %dir entries +root_dirs: set[str] = { + '/', + '/etc', + '/usr', + '/usr/bin', + '/usr/lib', + '/usr/lib/ocaml', + '/usr/lib/ocaml/caml', + '/usr/lib/ocaml/stublibs', + '/usr/lib/ocaml/threads', + '/usr/lib64', + '/usr/lib64/ocaml', + '/usr/lib64/ocaml/caml', + '/usr/lib64/ocaml/stublibs', + '/usr/lib64/ocaml/threads', + '/usr/libexec', + '/usr/sbin', + '/usr/share', + '/usr/share/doc' +} + +def find_buildroot_toplevel(buildroot: str) -> list[str]: + """Find toplevel files and directories in the buildroot. + + :param str buildroot: path to the buildroot + :return: a list of toplevel files and directories in the buildroot + """ + bfiles: list[str] = [] + for path, dirs, files in os.walk(buildroot): + for i in range(len(dirs) - 1, -1, -1): + d = os.path.join(path, dirs[i])[len(buildroot):] + if d not in root_dirs and not d.startswith('/usr/share/man'): + bfiles.append(d) + del dirs[i] + for f in files: + realfile = os.path.join(path, f)[len(buildroot):] + if realfile.startswith('/usr/share/man'): + bfiles.append(realfile + '*') + else: + bfiles.append(realfile) + return bfiles + +# File suffixes that go into a devel subpackage +dev_suffixes: set[str] = { + 'a', 'cmo', 'cmt', 'cmti', 'cmx', 'cmxa', 'h', 'idl', 'ml', 'mli', 'o' +} + +def is_devel_file(filname: str) -> bool: + """Determine whether a file belongs to a devel subpackage. + + :param str filname: the filename to check + :return: True if the file belongs to a devel subpackage, else False + """ + return (filname == 'dune-package' or filname == 'opam' or + (os.path.splitext(filname)[1][1:] in dev_suffixes + and not filname.endswith('_top_init.ml'))) + +def find_buildroot_all(buildroot: str, devel: bool, add_star: bool) -> list[set[str]]: + """Find all files and directories in the buildroot and optionally + categorize them as 'main' or 'devel'. + + :param Namespace args: parsed command line arguments + :param bool devel: True to split into 'main' and 'devel', False otherwise + :param bool add_star: True to add a star to man page filenames + :return: a list of files and directories, in this order: main files, + main directories, devel files, and devel directories + """ + bfiles: list[set[str]] = [set(), set(), set()] + bdirs: set[str] = set() + for path, dirs, files in os.walk(buildroot): + for d in dirs: + realdir = os.path.join(path, d)[len(buildroot):] + if realdir not in root_dirs and not realdir.startswith('/usr/share/man'): + bdirs.add(realdir) + for f in files: + realfile = os.path.join(path, f)[len(buildroot):] + if devel and is_devel_file(os.path.basename(realfile)): + bfiles[2].add(realfile) + else: + if add_star and realfile.startswith('/usr/share/man'): + bfiles[0].add(realfile + '*') + else: + bfiles[0].add(realfile) + parentdir = os.path.dirname(realfile) + if parentdir in bdirs: + bfiles[1].add(parentdir) + bdirs.remove(parentdir) + # Catch intermediate directories, as in ocaml-mtime + parentdir = os.path.dirname(parentdir) + if parentdir in bdirs: + bfiles[1].add(parentdir) + bdirs.remove(parentdir) + bfiles.append(bdirs) + return bfiles + +# +# INSTALL FILE LEXER AND PARSER +# + +class TokenType(Enum): + """The types of tokens that can appear in an opam *.install file.""" + ERROR = auto() + COLON = auto() + LBRACE = auto() + RBRACE = auto() + LBRACK = auto() + RBRACK = auto() + STRING = auto() + FIELD = auto() + +@final +class InstallFileLexer(Iterator[tuple[TokenType, str]]): + """Convert an opam *.install file into a sequence of tokens.""" + __slots__ = ['index', 'text'] + + def __init__(self, filname: str) -> None: + """Create an opam *.install file lexer. + + :param str filname: the name of the file to read from + """ + self.index = 0 + with open(filname, 'r') as f: + # Limit reads to 4 MB in case this file is bogus. + # Most install files are under 4K. + self.text = f.read(4194304) + + def skip_whitespace(self) -> None: + """Skip over whitespace in the input.""" + while self.index < len(self.text) and \ + (self.text[self.index] == '#' or + self.text[self.index] in string.whitespace): + if self.text[self.index] == '#': + while (self.index < len(self.text) and + self.text[self.index] != '\n' and + self.text[self.index] != '\r'): + self.index += 1 + else: + self.index += 1 + + def __next__(self) -> tuple[TokenType, str]: + """Get the next token from the opam *.install file. + + :return: a pair containing the type and text of the next token + """ + self.skip_whitespace() + if self.index < len(self.text): + ch = self.text[self.index] + if ch == ':': + self.index += 1 + return (TokenType.COLON, ch) + if ch == '{': + self.index += 1 + return (TokenType.LBRACE, ch) + if ch == '}': + self.index += 1 + return (TokenType.RBRACE, ch) + if ch == '[': + self.index += 1 + return (TokenType.LBRACK, ch) + if ch == ']': + self.index += 1 + return (TokenType.RBRACK, ch) + if ch == '"': + start = self.index + 1 + end = start + while end < len(self.text) and self.text[end] != '"': + end += 2 if self.text[end] == '\\' else 1 + self.index = end + 1 + return (TokenType.STRING, self.text[start:end]) + if ch in string.ascii_letters: + start = self.index + end = start + 1 + while (end < len(self.text) and + (self.text[end] == '_' or + self.text[end] in string.ascii_letters)): + end += 1 + self.index = end + return (TokenType.FIELD, self.text[start:end]) + return (TokenType.ERROR, ch) + else: + raise StopIteration + +@final +class InstallFileParser(Iterable[tuple[str, bool, str, str]]): + """Parse opam *.install files.""" + + __slots__ = ['pkgname', 'lexer', 'libdir'] + + def __init__(self, filname: str, libdir: str) -> None: + """Initialize an OCaml .install file parser. + + :param str filname: name of the .install file to parse + :param str libdir: the OCaml library directory + """ + self.pkgname = os.path.splitext(os.path.basename(filname))[0] + self.lexer = InstallFileLexer(filname) + self.libdir = libdir + + def __iter__(self) -> Iterator[tuple[str, bool, str, str]]: + """Parse a .install file. + If there are any parse errors, we assume this file is not really an + opam .install file and abandon the parse. + """ + # Map opam installer names to directories + opammap: dict[str, str] = { + 'lib': os.path.join(self.libdir, self.pkgname), + 'lib_root': self.libdir, + 'libexec': os.path.join(self.libdir, self.pkgname), + 'libexec_root': self.libdir, + 'bin': '/usr/bin', + 'sbin': '/usr/sbin', + 'toplevel': os.path.join(self.libdir, 'toplevel'), + 'share': os.path.join('/usr/share', self.pkgname), + 'share_root': '/usr/share', + 'etc': os.path.join('/etc', self.pkgname), + 'doc': os.path.join('/usr/doc', self.pkgname), + 'stublibs': os.path.join(self.libdir, 'stublibs'), + 'man': '/usr/share/man' + } + + # Parse the file + try: + toktyp, token = next(self.lexer) + while toktyp == TokenType.FIELD: + libname = token + toktyp, token = next(self.lexer) + if toktyp != TokenType.COLON: + return + + toktyp, token = next(self.lexer) + if toktyp != TokenType.LBRACK: + return + + directory = opammap.get(libname) + if not directory: + return + + toktyp, token = next(self.lexer) + while toktyp == TokenType.STRING: + source = token + optional = source[0] == '?' + if optional: + source = source[1:] + nexttp, nexttk = next(self.lexer) + if nexttp == TokenType.LBRACE: + nexttp, nexttk = next(self.lexer) + if nexttp == TokenType.STRING: + filname = os.path.join(directory, nexttk) + bracetp, bractk = next(self.lexer) + if bracetp != TokenType.RBRACE: + return + nexttp, nexttk = next(self.lexer) + else: + return + elif libname == 'man': + index = token.rfind('.') + if index < 0: + return + mandir = os.path.join(directory, 'man' + token[index+1:]) + filname = os.path.join(mandir, os.path.basename(token)) + else: + filname = os.path.join(directory, os.path.basename(token)) + toktyp, token = nexttp, nexttk + yield (self.pkgname, optional, source, filname) + + if toktyp != TokenType.RBRACK: + return + toktyp, token = next(self.lexer) + except StopIteration: + return + +def install_files(buildroot: str, libdir: str) -> None: + """Install the files listed in opam .install files in the buildroot. + + For some projects, there are install files in both the project root + directory and somewhere under "_build", so be careful not to parse the same + install file twice. + + :param str buildroot: path to the buildroot + :param str libdir: the OCaml library directory + """ + install_files = set() + for path, dirs, files in os.walk('.'): + for f in files: + if f.endswith('.install') and f not in install_files: + install_files.add(f) + parser = InstallFileParser(os.path.join(path, f), libdir) + for _, optional, source, filname in parser: + if not optional or os.path.exists(source): + installpath = os.path.join(buildroot, filname[1:]) + os.makedirs(os.path.dirname(installpath), exist_ok=True) + shutil.copy2(source, installpath) + +def get_package_map(buildroot: str, libdir: str, devel: bool) -> dict[str, set[str]]: + """Create a map from package names to installed files from the opam .install + files in the buildroot. + + For some projects, there are install files in both the project root + directory and somewhere under "_build", so be careful not to parse the same + install file twice.""" + + pmap: dict[str, set[str]] = dict() + install_files = set() + + def add_pkg(pkgname: str, filname: str) -> None: + """Add a mapping from a package name to a filename. + + :param str pkgname: the package that acts as the map key + :param str filname: the filename to add to the package set + """ + if pkgname not in pmap: + pmap[pkgname] = set() + pmap[pkgname].add(filname) + + installed = find_buildroot_all(buildroot, devel, False) + for path, dirs, files in os.walk('.'): + for f in files: + if f.endswith('.install') and f not in install_files: + install_files.add(f) + parser = InstallFileParser(os.path.join(path, f), libdir) + for pkgname, _, _, filname in parser: + if filname in installed[0]: + if filname.startswith('/usr/share/man'): + add_pkg(pkgname, filname + '*') + else: + add_pkg(pkgname, filname) + dirname = os.path.dirname(filname) + if dirname in installed[1]: + add_pkg(pkgname, '%dir ' + dirname) + installed[1].remove(dirname) + elif filname in installed[2]: + if filname.startswith('/usr/share/man'): + add_pkg(pkgname + '-devel', filname + '*') + else: + add_pkg(pkgname + '-devel', filname) + dirname = os.path.dirname(filname) + if dirname in installed[3]: + add_pkg(pkgname + '-devel', '%dir ' + dirname) + installed[3].remove(dirname) + return pmap + +# +# MAIN INTERFACE +# + +def ocaml_files(no_devel: bool, separate: bool, install: bool, buildroot: str, + libdir: str) -> None: + """Generate %files lists from an installed buildroot. + + :param bool no_devel: False to split files into a main package and a devel + package + :param bool separate: True to place each OCaml module in an RPM package + :param bool install: True to install files, False to generate %files + :param str buildroot: the installed buildroot + :param str libdir: the OCaml library directory + """ + if install: + install_files(buildroot, libdir) + elif separate: + pkgmap = get_package_map(buildroot, libdir, not no_devel) + for pkg in pkgmap: + with open('.ofiles-' + pkg, 'w') as f: + for entry in pkgmap[pkg]: + f.write(entry + '\n') + elif no_devel: + with open('.ofiles', 'w') as f: + for entry in find_buildroot_toplevel(buildroot): + f.write(entry + '\n') + else: + files = find_buildroot_all(buildroot, True, True) + with open('.ofiles', 'w') as f: + for entry in files[0]: + f.write(entry + '\n') + for entry in files[1]: + f.write('%dir ' + entry + '\n') + with open('.ofiles-devel', 'w') as f: + for entry in files[2]: + f.write(entry + '\n') + for entry in files[3]: + f.write('%dir ' + entry + '\n') + +if __name__ == "__main__": + parser = argparse.ArgumentParser(description='Support for building OCaml RPM packages') + parser.add_argument('-i', '--install', + action='store_true', + default=False, + help='install files instead of generating %files') + parser.add_argument('-n', '--no-devel', + action='store_true', + default=False, + help='suppress creation of a devel subpackage') + parser.add_argument('-s', '--separate', + action='store_true', + default=False, + help='separate packaging. Each OCaml module is in a distinct RPM package. All modules are in a single RPM package by default.') + parser.add_argument('-v', '--version', + action='version', + version=f'%(prog)s {str(version)}') + parser.add_argument('buildroot', help='RPM build root') + parser.add_argument('libdir', help='OCaml library directory') + args = parser.parse_args() + ocaml_files(args.no_devel, + args.separate, + args.install, + args.buildroot, + args.libdir) diff --git a/SPECS/ocaml.spec b/SPECS/ocaml.spec new file mode 100644 index 0000000..a39102f --- /dev/null +++ b/SPECS/ocaml.spec @@ -0,0 +1,1310 @@ +# 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. This is still a problem in 5.2. +%global _lto_cflags %{nil} + +# OCaml has a bytecode backend that works on anything with a C +# compiler, and a native code backend available on a subset of +# architectures. A further subset of architectures support native +# dynamic linking. + +%ifarch %{ocaml_native_compiler} +%global native_compiler 1 +%else +%global native_compiler 0 +%endif + +%ifarch %{ocaml_natdynlink} +%global natdynlink 1 +%else +%global natdynlink 0 +%endif + +# i686 support was dropped in OCaml 5 / Fedora 39. +ExcludeArch: %{ix86} + +# These are all the architectures that the tests run on. The tests +# take a long time to run, so don't run them on slow machines. +%global test_arches aarch64 %{power64} riscv64 s390x x86_64 +# These are the architectures for which the tests must pass otherwise +# the build will fail. +#global test_arches_required aarch64 ppc64le x86_64 +%global test_arches_required NONE + +# Architectures where parallel builds fail. +#global no_parallel_build_arches aarch64 + +#global rcver +git +%global rcver %{nil} + +Name: ocaml +Version: 5.2.0 +Release: 3%{?dist} + +Summary: OCaml compiler and programming environment + +License: LGPL-2.1-or-later WITH OCaml-LGPL-linking-exception + +URL: https://www.ocaml.org +VCS: https://github.com/ocaml/ocaml + +Source0: %{vcs}/archive/%{version}%{rcver}/%{name}-%{version}%{rcver}.tar.gz +Source1: macros.ocaml-rpm +Source2: ocaml_files.py + +# IMPORTANT NOTE: +# +# These patches are generated from unpacked sources stored in a +# pagure.io git repository. If you change the patches here, they will +# be OVERWRITTEN by the next update. Instead, request commit access +# to the pagure project: +# +# https://pagure.io/fedora-ocaml +# +# 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: 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 + +# Upstream after 5.2.0: +Patch: 0006-Reload-exception-pointer-register-in-caml_c_call.patch + +# Fix for ppc64le code generation issue found after 5.2.0 was released. +# https://github.com/ocaml/ocaml/issues/13220 +# https://github.com/ocaml/ocaml/commit/114ddae2d4c85391a4f939dc6623424ae35a07aa +Patch: 0007-Compute-more-accurate-instruction-sizes-for-branch-r.patch + +BuildRequires: make +BuildRequires: git +BuildRequires: gcc +BuildRequires: autoconf +BuildRequires: gawk +BuildRequires: hardlink +BuildRequires: perl-interpreter +BuildRequires: util-linux +BuildRequires: /usr/bin/annocheck +BuildRequires: pkgconfig(libzstd) + +# Documentation requirements +BuildRequires: asciidoc +BuildRequires: python3-pygments + +# ocamlopt runs gcc to link binaries. Because Fedora includes +# hardening flags automatically, redhat-rpm-config is also required. +# Compressed marshaling requires libzstd-devel. +Requires: gcc +Requires: redhat-rpm-config +Requires: libzstd-devel%{?_isa} + +# Because we pass -c flag to ocaml-find-requires (to avoid circular +# dependencies) we also have to explicitly depend on the right version +# of ocaml-runtime. +Requires: ocaml-runtime%{?_isa} = %{version}-%{release} + +# Force ocaml-srpm-macros to be at the latest version, both for builds +# 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 + +# Bundles an MD5 implementation in runtime/caml/md5.h and runtime/md5.c +Provides: bundled(md5-plumb) + +Provides: ocaml(compiler) = %{version} + +%if %{native_compiler} +%global __ocaml_requires_opts -c -f '%{buildroot}%{_bindir}/ocamlrun %{buildroot}%{_bindir}/ocamlobjinfo.byte' +%else +%global __ocaml_requires_opts -c -f '%{buildroot}%{_bindir}/ocamlrun %{buildroot}%{_bindir}/ocamlobjinfo.byte' -i Backend_intf -i Inlining_decision_intf -i Simplify_boxed_integer_ops_intf +%endif +%global __ocaml_provides_opts -f '%{buildroot}%{_bindir}/ocamlrun %{buildroot}%{_bindir}/ocamlobjinfo.byte' + + +%description +OCaml is a high-level, strongly-typed, functional and object-oriented +programming language from the ML family of languages. + +This package comprises two batch compilers (a fast bytecode compiler +and an optimizing native-code compiler), an interactive toplevel system, +parsing tools (Lex,Yacc), a replay debugger, a documentation generator, +and a comprehensive library. + + +%package runtime +# LGPL-2.1-or-later WITH OCaml-LGPL-linking-exception: the project as a whole +# LicenseRef-Fedora-Public-Domain: the MD5 implementation in runtime/caml/md5.h +# and runtime/md5.c +License: LGPL-2.1-or-later WITH OCaml-LGPL-linking-exception AND LicenseRef-Fedora-Public-Domain +Summary: OCaml runtime environment +Requires: util-linux +Provides: ocaml(runtime) = %{version} + +%description runtime +OCaml is a high-level, strongly-typed, functional and object-oriented +programming language from the ML family of languages. + +This package contains the runtime environment needed to run OCaml +bytecode. + + +%package source +Summary: Source code for OCaml libraries +Requires: ocaml%{?_isa} = %{version}-%{release} + +%description source +Source code for OCaml libraries. + + +%package ocamldoc +# LGPL-2.1-or-later WITH OCaml-LGPL-linking-exception: the project as a whole +# LicenseRef-Fedora-Public-Domain: ocamldoc/ocamldoc.sty +License: LGPL-2.1-or-later WITH OCaml-LGPL-linking-exception AND LicenseRef-Fedora-Public-Domain +Summary: Documentation generator for OCaml +Requires: ocaml%{?_isa} = %{version}-%{release} +Provides: ocamldoc = %{version} + +%description ocamldoc +Documentation generator for OCaml. + + +%package docs +Summary: Documentation for OCaml +BuildArch: noarch +Requires: ocaml = %{version}-%{release} + + +%description docs +OCaml is a high-level, strongly-typed, functional and object-oriented +programming language from the ML family of languages. + +This package contains man pages. + + +%package compiler-libs +Summary: Compiler libraries for OCaml +Requires: ocaml%{?_isa} = %{version}-%{release} + + +%description compiler-libs +OCaml is a high-level, strongly-typed, functional and object-oriented +programming language from the ML family of languages. + +This package contains some modules used internally by the OCaml +compilers, useful for the development of some OCaml applications. +Note that this exposes internal details of the OCaml compiler which +may not be portable between versions. + + +%package rpm-macros +# LGPL-2.1-or-later WITH OCaml-LGPL-linking-exception: the project as a whole +# BSD-3-Clause: ocaml_files.py +License: LGPL-2.1-or-later WITH OCaml-LGPL-linking-exception AND BSD-3-Clause +Summary: RPM macros for building OCaml packages +BuildArch: noarch +Requires: ocaml = %{version}-%{release} +Requires: python3 + + +%description rpm-macros +This package contains macros that are useful for building OCaml RPMs. + + +%prep +%autosetup -S git -n %{name}-%{version}%{rcver} +# Patches touch configure.ac, so rebuild it: +autoconf --force + + +%build +%ifnarch %{no_parallel_build_arches} +make="%make_build" +%else +unset MAKEFLAGS +make=make +%endif + +# Set ocamlmklib default flags to include Fedora linker flags +sed -i '/ld_opts/s|\[\]|["%{build_ldflags}"]|' tools/ocamlmklib.ml + +# Expose a dependency on the math library +sed -i '/^EXTRACAMLFLAGS=/aLINKOPTS=-cclib -lm' otherlibs/unix/Makefile + +# Don't use %%configure macro because it sets --build, --host which +# breaks some incorrect assumptions made by OCaml's configure.ac +# +# See also: +# https://lists.fedoraproject.org/archives/list/devel@lists.fedoraproject.org/thread/2O4HBOK6PTQZAFAVIRDVMZGG2PYB2QHM/ +# https://github.com/ocaml/ocaml/issues/8647 +# +# We set --libdir to the unusual directory because we want OCaml to +# install its libraries and other files into a subdirectory. +# +# OC_CFLAGS/OC_LDFLAGS control what flags OCaml passes to the linker +# when doing final linking of OCaml binaries. Setting these is +# necessary to ensure that generated binaries have Fedora hardening +# features. +./configure \ + --prefix=%{_prefix} \ + --sysconfdir=%{_sysconfdir} \ + --mandir=%{_mandir} \ + --libdir=%{_libdir}/ocaml \ + --enable-flambda \ +%if %{native_compiler} + --enable-native-compiler \ + --enable-native-toplevel \ +%else + --disable-native-compiler \ + --disable-native-toplevel \ +%endif +%ifarch x86_64 +%if 0%{?_include_frame_pointers} + --enable-frame-pointers \ +%endif +%endif +%ifarch %{test_arches} + --enable-ocamltest \ +%else + --disable-ocamltest \ +%endif + OC_CFLAGS='%{build_cflags}' \ + OC_LDFLAGS='%{build_ldflags}' \ + %{nil} +$make world +%if %{native_compiler} +$make opt +$make opt.opt +%endif + +# Build the README and fix up references to other doc files +asciidoc -d book README.adoc +for fil in CONTRIBUTING.md HACKING.adoc INSTALL.adoc README.win32.adoc; do + sed -e "s,\"$fil\",\"https://github.com/ocaml/ocaml/blob/trunk/$fil\"," \ + -i README.html +done + + +%check +%ifarch %{ocaml_native_compiler} +# For information only, compile a binary and dump the annocheck data +# from it. Useful so we know if hardening is being enabled, but don't +# fail because not every hardening feature can be enabled here. +echo 'print_endline "hello, world"' > hello.ml +./ocamlopt.opt -verbose -I stdlib hello.ml -o hello ||: +annocheck -v hello ||: +%endif + +%ifarch %{test_arches} +%ifarch %{test_arches_required} +make -j1 tests +%else +make -j1 tests ||: +%endif +%endif + + +%install +%make_install +perl -pi -e "s|^$RPM_BUILD_ROOT||" $RPM_BUILD_ROOT%{_libdir}/ocaml/ld.conf + +echo %{version} > $RPM_BUILD_ROOT%{_libdir}/ocaml/fedora-ocaml-release + +# Remove the installed documentation. We will install it using %%doc +rm -rf $RPM_BUILD_ROOT%{_docdir}/ocaml + +mkdir -p $RPM_BUILD_ROOT%{rpmmacrodir} +install -m 0644 %{SOURCE1} $RPM_BUILD_ROOT%{rpmmacrodir}/macros.ocaml-rpm + +mkdir -p $RPM_BUILD_ROOT%{_rpmconfigdir}/redhat +install -m 0644 %{SOURCE2} $RPM_BUILD_ROOT%{_rpmconfigdir}/redhat + +# Link, rather than copy, identical binaries +hardlink -t $RPM_BUILD_ROOT%{_libdir}/ocaml/stublibs + + +%files +%license LICENSE +%{_bindir}/ocaml + +%{_bindir}/ocamlcmt +%{_bindir}/ocamlcp +%{_bindir}/ocamldebug +%{_bindir}/ocamlmklib +%{_bindir}/ocamlmktop +%{_bindir}/ocamlprof +%{_bindir}/ocamlyacc + +# symlink to either .byte or .opt version +%{_bindir}/ocamlc +%{_bindir}/ocamldep +%{_bindir}/ocamllex +%{_bindir}/ocamlobjinfo + +# bytecode versions +%{_bindir}/ocamlc.byte +%{_bindir}/ocamldep.byte +%{_bindir}/ocamllex.byte +%{_bindir}/ocamlobjinfo.byte + +%if %{native_compiler} +# native code versions +%{_bindir}/ocamlc.opt +%{_bindir}/ocamldep.opt +%{_bindir}/ocamllex.opt +%{_bindir}/ocamlobjinfo.opt +%endif + +%if %{native_compiler} +%{_bindir}/ocamlnat +%{_bindir}/ocamlopt +%{_bindir}/ocamlopt.byte +%{_bindir}/ocamlopt.opt +%{_bindir}/ocamloptp +%endif + +%{_libdir}/ocaml/expunge +%{_libdir}/ocaml/ld.conf +%{_libdir}/ocaml/Makefile.config + +%{_libdir}/ocaml/*.a +%if %{native_compiler} +%{_libdir}/ocaml/*.cmxa +%{_libdir}/ocaml/*.cmx +%{_libdir}/ocaml/*.o +%{_libdir}/ocaml/libasmrun_shared.so +%endif +%{_libdir}/ocaml/*.mli +%{_libdir}/ocaml/sys.ml.in +%{_libdir}/ocaml/libcamlrun_shared.so + +%{_libdir}/ocaml/{dynlink,runtime_events,str,threads,unix}/*.mli +%if %{native_compiler} +%{_libdir}/ocaml/{dynlink,runtime_events,str,threads,unix}/*.a +%{_libdir}/ocaml/{dynlink,runtime_events,str,threads,unix}/*.cmxa +%{_libdir}/ocaml/{dynlink,profiling,runtime_events,str,threads,unix}/*.cmx +%{_libdir}/ocaml/profiling/*.o +%endif +%if %{natdynlink} +%{_libdir}/ocaml/{runtime_events,str,unix}/*.cmxs +%endif + +# headers +%{_libdir}/ocaml/caml + + +%files runtime +%doc README.html Changes +%license LICENSE +%{_bindir}/ocamlrun +%{_bindir}/ocamlrund +%{_bindir}/ocamlruni +%dir %{_libdir}/ocaml +%{_libdir}/ocaml/*.cmo +%{_libdir}/ocaml/*.cmi +%{_libdir}/ocaml/*.cma +%{_libdir}/ocaml/stublibs +%dir %{_libdir}/ocaml/dynlink +%{_libdir}/ocaml/dynlink/META +%{_libdir}/ocaml/dynlink/*.cmi +%{_libdir}/ocaml/dynlink/*.cma +%dir %{_libdir}/ocaml/profiling +%{_libdir}/ocaml/profiling/*.cmo +%{_libdir}/ocaml/profiling/*.cmi +%dir %{_libdir}/ocaml/runtime_events +%{_libdir}/ocaml/runtime_events/META +%{_libdir}/ocaml/runtime_events/*.cmi +%{_libdir}/ocaml/runtime_events/*.cma +%{_libdir}/ocaml/runtime-launch-info +%{_libdir}/ocaml/stdlib +%dir %{_libdir}/ocaml/str +%{_libdir}/ocaml/str/META +%{_libdir}/ocaml/str/*.cmi +%{_libdir}/ocaml/str/*.cma +%dir %{_libdir}/ocaml/threads +%{_libdir}/ocaml/threads/META +%{_libdir}/ocaml/threads/*.cmi +%{_libdir}/ocaml/threads/*.cma +%dir %{_libdir}/ocaml/unix +%{_libdir}/ocaml/unix/META +%{_libdir}/ocaml/unix/*.cmi +%{_libdir}/ocaml/unix/*.cma +%{_libdir}/ocaml/fedora-ocaml-release + + +%files source +%license LICENSE +%{_libdir}/ocaml/*.ml +%{_libdir}/ocaml/*.cmt* +%{_libdir}/ocaml/*/*.cmt* + + +%files ocamldoc +%license LICENSE +%doc ocamldoc/Changes.txt +%{_bindir}/ocamldoc* +%{_libdir}/ocaml/ocamldoc + + +%files docs +%{_mandir}/man1/* +%{_mandir}/man3/* + + +%files compiler-libs +%license LICENSE +%{_libdir}/ocaml/compiler-libs + + +%files rpm-macros +%{rpmmacrodir}/macros.ocaml-rpm +%{_rpmconfigdir}/redhat/ocaml_files.py + + +%changelog +* Fri Oct 25 2024 MSVSphere Packaging Team - 5.2.0-3 +- Rebuilt for MSVSphere 10 + +* Mon Jun 24 2024 Troy Dawson - 5.2.0-3 +- Bump release for June 2024 mass rebuild + +* Wed Jun 19 2024 Richard W.M. Jones - 5.2.0-2 +- Add fix for ppc64le code generation issue found after 5.2.0 was released + +* Thu May 23 2024 Jerry James - 5.2.0-1 +- 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 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_40_Mass_Rebuild + +* Sun Jan 21 2024 Fedora Release Engineering - 5.1.1-3 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_40_Mass_Rebuild + +* Mon Dec 18 2023 Richard W.M. Jones - 5.1.1-2 +- Add s390x code generation fix + https://github.com/ocaml/ocaml/issues/12829 + +* Mon Dec 11 2023 Richard W.M. Jones - 5.1.1-1 +- New upstream version 5.1.1 (RHBZ#2239227) + +* Tue Nov 14 2023 Yaakov Selkowitz - 5.1.0-5 +- Drop unused BR parallel + +* Fri Oct 06 2023 Richard W.M. Jones - 5.1.0-4 +- Use BR ocaml-srpm-macros to force latest to be built against + +* Thu Oct 05 2023 Richard W.M. Jones - 5.1.0-3 +- Rebuild against updated ocaml-srpm-macros + +* Thu Oct 5 2023 Richard W.M. Jones - 5.1.0-2 +- Add upstream patch added after 5.1.0 + +* Wed Oct 4 2023 Jerry James - 5.1.0-1 +- Version 5.1.0 +- Add LicenseRef-Fedora-Public-Domain to the runtime License field +- New ocaml-rpm-macros subpackage +- Depend on libzstd-devel for compressed marshaling +- Disable LTO + +* Thu Jul 20 2023 Fedora Release Engineering - 5.0.0-4 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_39_Mass_Rebuild + +* Wed Jul 12 2023 Richard W.M. Jones - 5.0.0-3 +- Force ocaml-srpm-macros to be the latest version. + +* Wed Jun 14 2023 Jerry James - 5.0.0-2 +- Version 5.0.0 +- Convert License tag to SPDX +- Ship HTML documentation instead of asciidoc source +- Set ocamlmklib default flags to the Fedora linker flags +- Enable frame pointers on x86_64 + +* Mon Jan 23 2023 Richard W.M. Jones - 4.14.0-5 +- Rebuild OCaml packages for F38 + +* Thu Jan 19 2023 Fedora Release Engineering - 4.14.0-4 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_38_Mass_Rebuild + +* Mon Sep 5 2022 Richard W.M. Jones - 4.14.0-3 +- Include more upstream patches from 4.14 branch + +* Fri Jul 22 2022 Fedora Release Engineering - 4.14.0-2 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_37_Mass_Rebuild + +* Sat Jun 18 2022 Richard W.M. Jones - 4.14.0-1 +- New upstream version 4.14.0 + +* Thu Jun 9 2022 Jerry James - 4.13.1-4 +- Fix the Source0 URL +- chrpath is no longer needed +- Use the %%license macro +- Build the test binaries so the tests will run + +* Fri Feb 04 2022 Richard W.M. Jones - 4.13.1-4 +- Rebuild 4.13.1 to remove package notes + +* Wed Jan 26 2022 Richard W.M. Jones - 4.13.1-3 +- Disable package note misfeature +- Remove duplicate flags from mkexe + +* Thu Jan 20 2022 Fedora Release Engineering - 4.13.1-2 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_36_Mass_Rebuild + +* Mon Oct 04 2021 Richard W.M. Jones - 4.13.1-1 +- New upstream version 4.13.1 + +* Thu Jul 22 2021 Fedora Release Engineering - 4.12.0-3 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_35_Mass_Rebuild + +* Wed Jun 23 2021 Richard W.M. Jones - 4.12.0-2 +- Move to final version of upstream patch for non-constant SIGSTKSZ + +* Sun Feb 28 2021 Richard W.M. Jones - 4.12.0-1 +- OCaml 4.12.0 release (RHBZ#1893381). +- Workaround for glibc non-constant SIGSTKSZ + (https://github.com/ocaml/ocaml/issues/10250) +- Package *.cmt and *.cmti files. +- Remove objinfo_helper since it is no longer built. + +* Tue Jan 26 2021 Fedora Release Engineering - 4.11.1-2 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_34_Mass_Rebuild + +* Tue Sep 01 2020 Richard W.M. Jones - 4.11.1-1 +- OCaml 4.11.1 release (RHBZ#1870368#c26). + +* Fri Aug 21 2020 Richard W.M. Jones - 4.11.0-1 +- OCaml 4.11.0 release (RHBZ#1870368). + +* Tue Aug 04 2020 Richard W.M. Jones - 4.11.0-0.9.dev2 +- Bump and rebuild to fix DWARF versioning issues. +- Enable LTO again. + +* Tue Jul 28 2020 Fedora Release Engineering - 4.11.0-0.7.dev2 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_33_Mass_Rebuild + +* Tue Jul 14 2020 Tom Stellard - 4.11.0-0.6.dev2 +- Use make macros +- https://fedoraproject.org/wiki/Changes/UseMakeBuildInstallMacro + +* Wed Jul 01 2020 Jeff Law - 4.11.0-0.5.dev2.fc33 +- Disable LTO + +* Mon May 04 2020 Richard W.M. Jones - 4.11.0-0.4.dev2.fc33 +- Move to OCaml 4.11.0+dev2-2020-04-22. +- Backport upstream RISC-V backend from 4.12 + fixes. +- Enable tests on riscv64. +- Disable ocaml-instr-* tools on riscv64. + +* Tue Apr 21 2020 Richard W.M. Jones - 4.11.0-0.3.pre.fc33 +- Add fixes for various issues found in the previous build. + +* Fri Apr 17 2020 Richard W.M. Jones - 4.11.0-0.2.pre.fc33 +- Move to OCaml 4.11.0 pre-release with support for RISC-V. + +* Sat Apr 11 2020 Richard W.M. Jones - 4.10.0-4.fc33 +- Fix RISC-V backend. + +* Thu Apr 02 2020 Richard W.M. Jones - 4.10.0-3.fc33 +- Update all OCaml dependencies for RPM 4.16. + +* Thu Feb 27 2020 Richard W.M. Jones - 4.10.0-2.fc33 +- Add dist tag. + +* Tue Feb 25 2020 Richard W.M. Jones - 4.10.0-1 +- OCaml 4.10.0 final. + +* Wed Jan 29 2020 Fedora Release Engineering - 4.10.0-0.beta1.0.1 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_32_Mass_Rebuild + +* Sat Jan 18 2020 Richard W.M. Jones - 4.10.0-0.beta1 +- OCaml 4.10.0+beta1. + +* Tue Jan 07 2020 Richard W.M. Jones - 4.09.0-13 +- Bump release and rebuild. + +* Tue Jan 07 2020 Richard W.M. Jones - 4.09.0-4 +- OCaml 4.09.0 for riscv64 + +* Tue Dec 10 2019 Richard W.M. Jones - 4.09.0-3 +- Require redhat-rpm-config to get hardening flags when linking. + +* Thu Dec 05 2019 Richard W.M. Jones - 4.09.0-2 +- OCaml 4.09.0 final. +- Use autosetup, remove old setup line. +- Remove ocamloptp binaries. +- Rename target_camlheader[di] -> camlheader[di] files. +- Remove vmthreads - old threading library which is no longer built. +- Remove x11 subpackage which is obsolete. +- Further fixes to CFLAGS and annobin. + +* Fri Aug 16 2019 Richard W.M. Jones - 4.08.1-1 +- OCaml 4.08.1 final. + +* Tue Jul 30 2019 Richard W.M. Jones - 4.08.1-0.rc2.1 +- OCaml 4.08.1+rc2. +- Include fix for miscompilation of off_t on 32 bit architectures. + +* Thu Jul 25 2019 Fedora Release Engineering - 4.08.0-2 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_31_Mass_Rebuild + +* Thu Jun 27 2019 Richard W.M. Jones - 4.08.0-1 +- OCaml 4.08.0 (RHBZ#1673688). + +* Fri Apr 26 2019 Richard W.M. Jones - 4.08.0-0.beta3.1 +- OCaml 4.08.0 beta 3 (RHBZ#1673688). +- emacs subpackage has been dropped (from upstream): + https://github.com/ocaml/ocaml/pull/2078#issuecomment-443322613 + https://github.com/Chris00/caml-mode +- Remove ocamlbyteinfo and ocamlpluginfo, neither can be compiled. +- Disable tests on all architectures, temporarily hopefully. +- Package threads/*.mli files. + +* Fri Feb 01 2019 Fedora Release Engineering - 4.07.0-4 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_30_Mass_Rebuild + +* Fri Aug 17 2018 Richard W.M. Jones - 4.07.0-3 +- Bootstrap from previously build Fedora compiler by default. + +* Fri Jul 13 2018 Fedora Release Engineering - 4.07.0-2 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_29_Mass_Rebuild + +* Wed Jul 11 2018 Richard W.M. Jones - 4.07.0-1 +- OCaml 4.07.0 (RHBZ#1536734). + +* Tue Jun 26 2018 Richard W.M. Jones - 4.07.0-0.rc1.3 +- Enable emacs again on riscv64. + +* Tue Jun 19 2018 Richard W.M. Jones - 4.07.0-0.rc1.2 +- OCaml 4.07.0-rc1 (RHBZ#1536734). + +* Tue Jun 5 2018 Richard W.M. Jones - 4.07.0-0.beta2.1 +- Add RISC-V patch to add debuginfo (DWARF) generation. + +* Thu Apr 26 2018 Richard W.M. Jones - 4.07.0-0.beta2.0 +- OCaml 4.07.0-beta2 (RHBZ#1536734). + +* Sun Feb 25 2018 Richard W.M. Jones - 4.06.0-5 +- Add another couple of RISC-V patches from nojb branch. + +* Sat Feb 24 2018 Richard W.M. Jones - 4.06.0-4 +- Remove mesa* dependencies which are not needed. + +* Thu Feb 08 2018 Fedora Release Engineering - 4.06.0-3 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_28_Mass_Rebuild + +* Wed Jan 10 2018 Richard W.M. Jones - 4.06.0-2 +- Drop non-free documentation (RHBZ#1530647). + +* Mon Nov 06 2017 Richard W.M. Jones - 4.06.0-1 +- New upstream version 4.06.0. +- Enable parallel builds again. +- Rebase patches. +- New binary ocamlcmt. + +* Wed Sep 13 2017 Richard W.M. Jones - 4.05.0-4 +- Add final upstream fix for aarch64/binutils relocation problems. + https://github.com/ocaml/ocaml/pull/1330 + +* Wed Sep 06 2017 Richard W.M. Jones - 4.05.0-3 +- Include interim fix for aarch64/binutils relocation problems. + +* Sat Aug 05 2017 Richard W.M. Jones - 4.05.0-2 +- New upstream version 4.05.0. +- Disable parallel builds for now. +- *.mli files are now included in ocaml-compiler-libs. +- Add possible fix for aarch64 with new binutils. + +* Sat Aug 05 2017 Richard W.M. Jones - 4.04.2-4 +- Disable tests on aarch64 (https://caml.inria.fr/mantis/view.php?id=7602) + +* Thu Aug 03 2017 Fedora Release Engineering - 4.04.2-3 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_27_Binutils_Mass_Rebuild + +* Thu Jul 27 2017 Fedora Release Engineering - 4.04.2-2 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_27_Mass_Rebuild + +* Mon Jun 26 2017 Richard W.M. Jones - 4.04.2-1 +- New upstream version 4.04.2. +- Fix: ocaml: Insufficient sanitisation allows privilege escalation for + setuid binaries (CVE-2017-9772) (RHBZ#1464920). + +* Wed May 10 2017 Richard W.M. Jones - 4.04.1-1 +- New upstream version 4.04.1. + +* Sat Feb 11 2017 Fedora Release Engineering - 4.04.0-9 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_26_Mass_Rebuild + +* Thu Jan 12 2017 Igor Gnatenko - 4.04.0-8 +- Rebuild for readline 7.x + +* Wed Nov 23 2016 Richard W.M. Jones - 4.04.0-7 +- riscv: Further fixes for https://github.com/nojb/riscv-ocaml/issues/2 + +* Tue Nov 22 2016 Richard W.M. Jones - 4.04.0-5 +- Update RISC-V support to fix + https://github.com/nojb/riscv-ocaml/issues/2 + +* Fri Nov 11 2016 Richard W.M. Jones - 4.04.0-4 +- riscv64: Fix intermediate operands. + (https://github.com/nojb/riscv-ocaml/issues/1) +- Temporarily disable emacs subpackage on riscv64. + +* Wed Nov 09 2016 Richard W.M. Jones - 4.04.0-3 +- s390x: Fix address of caml_raise_exn in native dynlink modules. + (https://caml.inria.fr/mantis/view.php?id=7405) + +* Tue Nov 08 2016 Richard W.M. Jones - 4.04.0-2 +- Add support for RISC-V using out of tree support from: + https://github.com/nojb/riscv-ocaml + +* Fri Nov 04 2016 Richard W.M. Jones - 4.04.0-1 +- New upstream version 4.04.0. + +* Thu Nov 03 2016 Richard W.M. Jones - 4.04.0-0.1.beta2 +- New upstream version 4.04.0+beta2. +- Remove our downstream ppc64 backends, and switch to upstream power backend. +- Use autopatch instead of git for patching. +- Allow parallel builds again. +- Restore ppc stack limits. +- Remove ocamlbuild. +- Add *.byte bytecode binaries. + +* Wed May 04 2016 Richard W.M. Jones - 4.02.3-3 +- CVE-2015-8869 ocaml: sizes arguments are sign-extended from + 32 to 64 bits (RHBZ#1332090) + +* Thu Feb 04 2016 Fedora Release Engineering - 4.02.3-2 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_24_Mass_Rebuild + +* Tue Jul 28 2015 Richard W.M. Jones - 4.02.3-1 +- New upstream version: 4.02.3. + +* Mon Jun 29 2015 Richard W.M. Jones - 4.02.2-4 +- Couple of minor build fixes for ppc64 and ppc64le. +- ppc64/ppc64le: Fix behaviour of Int64.max_int ÷ -1 (RHBZ#1236615). + +* Fri Jun 26 2015 Richard W.M. Jones - 4.02.2-2 +- Enable the test suite during the build. Currently the results are + only advisory. + +* Tue Jun 23 2015 Richard W.M. Jones - 4.02.2-1 +- New upstream version: 4.02.2. +- No need for a mass rebuild, since this version is identical to RC1. + +* Tue Jun 16 2015 Richard W.M. Jones - 4.02.2-0.rc1.1 +- New upstream version: 4.02.2+rc1. +- Dropped two aarch64 patches which are now included upstream. +- Includes libasmrun_shared.so (RHBZ#1195025). + +* Wed Jun 10 2015 Richard W.M. Jones - 4.02.1-7 +- aarch64: Use upstream version of patch that fixes RHBZ#1224815. + +* Tue Jun 09 2015 Richard W.M. Jones - 4.02.1-6 +- aarch64: AArch64 backend generates invalid asm: conditional branch + out of range (RHBZ#1224815). + +* Thu May 28 2015 Richard W.M. Jones - 4.02.1-5 +- ppc64le: Fix calling convention of external functions with > 8 parameters + (RHBZ#1225995). + +* Wed May 6 2015 Richard W.M. Jones - 4.02.1-4 +- Fix gdb stack traces on aarch64 (upstream PR6490). Thanks: Mark Shinwell. + +* Thu Apr 23 2015 Richard W.M. Jones - 4.02.1-3 +- ppc, ppc64, ppc64le: Properly mark stack as non-executable. + The upstream fix was not applied completely. + +* Thu Feb 26 2015 Richard W.M. Jones - 4.02.1-2 +- Kill dependency on rpm-build. Added in 2009, apparently by accident. + (Thanks: Jon Ludlam) + +* Mon Feb 16 2015 Richard W.M. Jones - 4.02.1-1 +- New upstream version 4.02.1. +- Rebase patches on top. + +* Fri Oct 24 2014 Richard W.M. Jones - 4.02.0-6 +- Fixes for ppc64/ppc64le (RHBZ#1156300). + +* Mon Oct 20 2014 Richard W.M. Jones - 4.02.0-4 +- ocaml-emacs should require emacs(bin) (RHBZ#1154513). + +* Thu Sep 11 2014 Richard W.M. Jones - 4.02.0-3 +- Use -fno-strict-aliasing when building the compiler (RHBZ#990540). +- ppc, ppc64, ppc64le: Mark stack as non-executable. + +* Tue Sep 9 2014 Richard W.M. Jones - 4.02.0-2 +- Fix bug in argument parsing (RHBZ#1139790). + +* Sat Aug 30 2014 Richard W.M. Jones - 4.02.0-1 +- New upstream OCaml 4.02.0 final. +- Add patch for ocaml-camlimages + (see http://caml.inria.fr/mantis/view.php?id=6517) + +* Fri Aug 22 2014 Richard W.M. Jones - 4.02.0-0.11.gitc48fc015 +- Rebase on top of OCaml 4.02+rc1 (same as git commit c48fc015). + +* Sun Aug 17 2014 Fedora Release Engineering - 4.02.0-0.10.git10e45753 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_21_22_Mass_Rebuild + +* Fri Aug 08 2014 Richard W.M. Jones - 4.02.0-0.9 +- Add fix for Coq build issue: + http://caml.inria.fr/mantis/view.php?id=6507 + +* Fri Aug 01 2014 Richard W.M. Jones - 4.02.0-0.8 +- Rebase on top of 4.02.0 beta commit 10e45753. + +* Sat Jul 19 2014 Richard W.M. Jones - 4.02.0-0.7 +- Rebase on top of 4.02.0 beta commit c4f3a6c7. +- Remove the patch to disable CSE, since that problem is fixed upstream. +- Remove the patch fixing caml_callback2 on aarch64 since that patch is + now upstream. +- Make the compiler depend on ocaml-runtime explicitly. + +* Tue Jul 15 2014 Richard W.M. Jones - 4.02.0-0.5 +- Disable CSE optimization which is broken on armv7hl and aarch64. +- Fix broken caml_callback2 on aarch64 + http://caml.inria.fr/mantis/view.php?id=6489 + +* Sat Jul 12 2014 Richard W.M. Jones - 4.02.0-0.1 +- Update to 4.02.0-beta1 + patches from the upstream 4.02 branch. +- REMOVED labltk and camlp4 packages, since these are now packaged + separately upstream. +- Upstream includes fix for stack alignment issues on i686, so remove hack. +- Upstream now uses mkstemp where available, so patch removed. +- Upstream includes Aarch64 backend, so remove our own backport. +- Drop BR on ocaml-srpm-macros, since it is now included in Fedora. + +* Thu Jun 26 2014 Richard W.M. Jones - 4.01.0-20 +- BR binutils-devel so ocamlobjinfo supports *.cmxs files (RHBZ#1113735). + +* Sat Jun 07 2014 Fedora Release Engineering - 4.01.0-19 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_21_Mass_Rebuild + +* Wed May 21 2014 Jaroslav Škarvada - 4.01.0-18 +- Rebuilt for https://fedoraproject.org/wiki/Changes/f21tcl86 + +* Sat May 10 2014 Richard W.M. Jones - 4.01.0-17 +- Mark stack as non-executable on ARM (32 bit) and Aarch64. + +* Tue Apr 22 2014 Richard W.M. Jones - 4.01.0-16 +- Remove ocaml-srpm-macros subpackage. + This is now a separate package, see RHBZ#1087893. + +* Tue Apr 15 2014 Richard W.M. Jones - 4.01.0-15 +- Fix s390x builds (no native compiler). + +* Tue Apr 15 2014 Richard W.M. Jones - 4.01.0-14 +- Remove ExclusiveArch. +- Add ocaml-srpm-macros subpackage containing arch macros. +- See: RHBZ#1087794 + +* Mon Apr 14 2014 Richard W.M. Jones - 4.01.0-13 +- Fix aarch64 relocation problems again. + Earlier patch was dropped accidentally. + +* Wed Apr 9 2014 Richard W.M. Jones - 4.01.0-12 +- Add ppc64le support (thanks: Michel Normand) (RHBZ#1077767). + +* Tue Apr 1 2014 Richard W.M. Jones - 4.01.0-11 +- Fix --flag=arg patch (thanks: Anton Lavrik, Ignas Vyšniauskas). + +* Mon Mar 24 2014 Richard W.M. Jones - 4.01.0-10 +- Include a fix for aarch64 relocation problems + http://caml.inria.fr/mantis/view.php?id=6283 + +* Wed Jan 8 2014 Richard W.M. Jones - 4.01.0-8 +- Don't use ifarch around Patch lines, as it means the patch files + don't get included in the spec file. + +* Mon Jan 6 2014 Richard W.M. Jones - 4.01.0-7 +- Work around gcc stack alignment issues, see + http://caml.inria.fr/mantis/view.php?id=5700 + +* Tue Dec 31 2013 Richard W.M. Jones - 4.01.0-6 +- Add aarch64 (arm64) code generator. + +* Thu Nov 21 2013 Richard W.M. Jones - 4.01.0-4 +- Add bundled(md5-plumb) (thanks: Tomas Mraz). +- Add NON-upstream (but being sent upstream) patch to allow --flag=arg + as an alternative to --flag arg (RHBZ#1028650). + +* Sat Sep 14 2013 Richard W.M. Jones - 4.01.0-3 +- Disable -lcurses. This is not actually used, just linked with unnecessarily. + +* Sat Sep 14 2013 Richard W.M. Jones - 4.01.0-2 +- Fix the build on ppc64. + +* Fri Sep 13 2013 Richard W.M. Jones - 4.01.0-1 +- Update to new major version OCaml 4.01.0. +- Rebase patches. +- Remove bogus Requires 'ncurses-devel'. The base ocaml package already + pulls in the library implicitly. +- Remove bogus Requires 'gdbm-devel'. Nothing in the source mentions gdbm. +- Use mkstemp instead of mktemp in ocamlyacc. +- Add LICENSE as doc to some subpackages to keep rpmlint happy. +- Remove .ignore file from some packages. +- Remove period from end of Summary. + +* Sat Aug 03 2013 Fedora Release Engineering - 4.00.1-3 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_20_Mass_Rebuild + +* Thu Feb 14 2013 Fedora Release Engineering - 4.00.1-2 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_19_Mass_Rebuild + +* Tue Oct 16 2012 Richard W.M. Jones - 4.00.1-1 +- Update to upstream version 4.00.1. +- Clean up the spec file further. + +* Thu Aug 16 2012 Richard W.M. Jones - 4.00.0-2 +- ppc supports natdynlink. + +* Sat Jul 28 2012 Richard W.M. Jones - 4.00.0-1 +- Upgrade to OCaml 4.00.0 official release. +- Remove one patch (add -lpthread) which went upstream. + +* Fri Jul 20 2012 Fedora Release Engineering - 4.00.0-0.6.beta2 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_18_Mass_Rebuild + +* Sun Jun 10 2012 Richard W.M. Jones - 4.00.0-0.5.beta2 +- No change, just fix up changelog. + +* Thu Jun 7 2012 Richard W.M. Jones 4.00.0-0.3.beta2 +- Upgrade to OCaml 4.00.0 beta 2. +- The language is now officially called OCaml (not Objective Caml, O'Caml etc) +- Rebase patches on top: + . New ARM backend patch no longer required, since upstream. + . Replacement config.guess, config.sub no longer required, since upstream + versions are newer. +- PPC64 backend rebased and fixed. + . Increase the default size of the stack when compiling. +- New tool: ocamloptp (ocamlopt profiler). +- New VERSION file in ocaml-runtime package. +- New ocaml-compiler-libs subpackage. +- Rearrange ExclusiveArch alphanumerically. +- alpha, ia64 native backends have been removed upstream, so they are + no longer supported as native compiler targets. +- Remove defattr. +- Make OCaml dependency generator self-contained so it doesn't need + previous version of OCaml around. + +* Wed Jun 6 2012 Richard W.M. Jones 3.12.1-12 +- ppc64: Include fix for minor heap corruption because of unaligned + minor heap register (RHBZ#826649). +- Unset MAKEFLAGS before running build. + +* Wed Jun 6 2012 Richard W.M. Jones 3.12.1-11 +- ppc64: Fix position of stack arguments to external C functions + when there are more than 8 parameters. + +* Tue Jun 5 2012 Richard W.M. Jones 3.12.1-10 +- Include patch to link dllthreads.so with -lpthread explicitly, to + fix problem with 'pthread_atfork' symbol missing (statically linked) + on ppc64. + +* Sun Jun 3 2012 Richard W.M. Jones 3.12.1-9 +- Include svn rev 12548 to fix invalid generation of Thumb-2 branch + instruction TBH (upstream PR#5623, RHBZ#821153). + +* Wed May 30 2012 Richard W.M. Jones 3.12.1-8 +- Modify the ppc64 patch to reduce the delta between power64 and + upstream power backends. +- Clean up the spec file and bring it up to modern standards. + * Remove patch fuzz directive. + * Remove buildroot directive. + * Rearrange source unpacking. + * Remove chmod of GNU config.* files, since git does it. + * Don't need to remove buildroot in install section. + * Remove clean section. + * git am 3.12.1-6 +- Move patches to external git repo: + http://git.fedorahosted.org/git/?p=fedora-ocaml.git + There should be no change introduced here. + +* Tue May 15 2012 Karsten Hopp 3.12.1-4 +- ppc64 got broken by the new ARM backend, add a minor patch + +* Sat Apr 28 2012 Richard W.M. Jones 3.12.1-3 +- New ARM backend by Benedikt Meurer, backported to OCaml 3.12.1. + This has several advantages, including enabling natdynlink on ARM. +- Provide updated config.guess and config.sub (from OCaml upstream tree). + +* Thu Jan 12 2012 Richard W.M. Jones 3.12.1-2 +- add back ocaml-ppc64.patch for ppc secondary arch, drop .cmxs files + from file list on ppc (cherry picked from F16 - this should have + gone into Rawhide originally then been cherry picked back to F16) + +* Fri Jan 6 2012 Richard W.M. Jones - 3.12.1-1 +- New upstream version 3.12.1. This is a bugfix update. + +* Thu Dec 8 2011 Richard W.M. Jones - 3.12.0-7 +- Allow this package to be compiled on platforms without native + support and/or natdynlink, specifically ppc64. This updates (and + hopefully does not break) DJ's previous *.cmxs change for arm. + +* Fri Sep 23 2011 DJ Delorie - 3.12.0-6 +- Add arm type directive patch. +- Allow more arm arches. +- Don't package *.cmxs on arm. + +* Wed Mar 30 2011 Richard W.M. Jones - 3.12.0-5 +- Fix for invalid assembler generation (RHBZ#691896). + +* Tue Feb 08 2011 Fedora Release Engineering - 3.12.0-4 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_15_Mass_Rebuild + +* Wed Jan 5 2011 Richard W.M. Jones - 3.12.0-3 +- Rebuild with self. + +* Tue Jan 4 2011 Richard W.M. Jones - 3.12.0-2 +- Try depending on OCaml BR to fix: + /usr/lib/rpm/ocaml-find-provides.sh: /builddir/build/BUILDROOT/ocaml-3.12.0-1.fc15.i386/usr/bin/ocamlobjinfo: /usr/bin/ocamlrun: bad interpreter: No such file or directory + +* Tue Jan 4 2011 Richard W.M. Jones - 3.12.0-1 +- New upstream version 3.12.0. + http://fedoraproject.org/wiki/Features/OCaml3.12 +- Remove ppc64 support patch. +- Rebase rpath removal patch. +- ocamlobjinfo is now an official tool, so no need to compile it by hand. + Add objinfo_helper. +- Disable ocamlplugininfo. +- Remove addlabels, scrapelabels. +- Remove ocaml/stublibs/dlltkanim.so. + +* Fri Jan 29 2010 Richard W.M. Jones - 3.11.2-2 +- Update reference manual to latest version from website. + +* Wed Jan 20 2010 Richard W.M. Jones - 3.11.2-1 +- Update to 3.11.2 official release. + +* Tue Jan 5 2010 Richard W.M. Jones - 3.11.2-0.rc1.2 +- ocaml-labltk-devel should require tcl-devel and tk-devel. + +* Tue Dec 29 2009 Richard W.M. Jones - 3.11.2-0.rc1.1 +- Update to (release candidate) 3.11.2+rc1. + +* Wed Dec 16 2009 Richard W.M. Jones - 3.11.1-8 +- Use __ocaml_requires_opts / __ocaml_provides_opts. + +* Wed Dec 16 2009 Richard W.M. Jones - 3.11.1-7 +- Remove ocaml-find-{requires,provides}.sh from this package. These are + now in upstream RPM 4.8 (RHBZ#545116). +- define -> global in a few places. + +* Thu Nov 05 2009 Dennis Gilmore - 3.11.1-6 +- include sparcv9 in the arch list + +* Tue Oct 27 2009 Richard W.M. Jones - 3.11.1-5 +- Install ocaml.info files correctly (RHBZ#531204). + +* Fri Oct 16 2009 Richard W.M. Jones - 3.11.1-4 +- Set includes so building the *info programs works without + having OCaml already installed. + +* Fri Oct 16 2009 Richard W.M. Jones - 3.11.1-3 +- Add ocamlbyteinfo and ocamlplugininfo programs from Debian. + +* Sun Oct 4 2009 Richard W.M. Jones - 3.11.1-2 +- ocaml-find-requires.sh: Calculate runtime version using ocamlrun + -version instead of fedora-ocaml-release file. + +* Wed Sep 30 2009 Richard W.M. Jones - 3.11.1-1 +- OCaml 3.11.1 (this is virtually the same as the release candidate + that we were using for Fedora 12). + +* Sat Jul 25 2009 Fedora Release Engineering - 3.11.1-0.rc1.2.1 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_12_Mass_Rebuild + +* Wed Jun 3 2009 Richard W.M. Jones - 3.11.1-0.rc1.2 +- Remember to upload the source this time. + +* Wed Jun 3 2009 Richard W.M. Jones - 3.11.1-0.rc1.1 +- New upstream release candidate 3.11.1+rc1. +- Remove ocamlbuild -where patch (now upstream). + +* Tue Jun 2 2009 Richard W.M. Jones - 3.11.1-0.rc0.3 +- Move dllgraphics.so into runtime package (RHBZ#468506). + +* Tue May 26 2009 Richard W.M. Jones - 3.11.1-0.rc0.2 +- Backport ocamlbuild -where fix. + +* Fri May 22 2009 Richard W.M. Jones - 3.11.1-0.rc0.1 +- 3.11.1 release candidate 0. + +* Wed Feb 25 2009 Fedora Release Engineering - 3.11.0-2 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_11_Mass_Rebuild + +* Thu Dec 4 2008 Richard W.M. Jones - 3.11.0-1 +- Official release of 3.11.0. + +* Thu Dec 4 2008 Richard W.M. Jones - 3.11.0-0.6.rc1 +- Fixed sources file. + +* Thu Dec 4 2008 Richard W.M. Jones - 3.11.0-0.5.rc1 +- New upstream version 3.11.0+rc1. + +* Mon Nov 24 2008 Richard W.M. Jones - 3.11.0-0.4.beta1 +- Rebuild. + +* Thu Nov 20 2008 Rex Dieter - 3.11.0-0.3.beta1 +- fix NVR to match packaging guidelines + +* Thu Nov 20 2008 Richard W.M. Jones - 3.11.0+beta1-2 +- Fix Invalid_argument("String.index_from") with patch from upstream. + +* Tue Nov 18 2008 Richard W.M. Jones - 3.11.0+beta1-1 +- Rebuild for major new upstream release of 3.11.0 for Fedora 11. + +* Fri Aug 29 2008 Richard W.M. Jones - 3.10.2-5 +- Rebuild with patch fuzz. + +* Mon Jun 9 2008 Richard W.M. Jones - 3.10.2-4 +- Add ocaml-3.11-dev12-no-executable-stack.patch (bz #450551). + +* Wed Jun 4 2008 Richard W.M. Jones - 3.10.2-3 +- ocaml-ocamldoc provides ocamldoc (bz #449931). +- REMOVED provides of labltk, camlp4. Those are libraries and all + packages should now depend on ocaml-labltk / ocaml-camlp4 / -devel + as appropriate. + +* Thu May 8 2008 Richard W.M. Jones - 3.10.2-2 +- Pass MAP_32BIT to mmap (bz #445545). + +* Mon Apr 21 2008 Richard W.M. Jones - 3.10.2-1 +- New upstream version 3.10.2 for Fedora 10. +- Cleaned up several rpmlint errors & warnings. + +* Fri Feb 29 2008 David Woodhouse - 3.10.1-2 +- ppc64 port + +* Tue Feb 12 2008 Richard W.M. Jones - 3.10.1-1 +- new upstream version 3.10.1 + +* Fri Jan 4 2008 Gerard Milmeister - 3.10.0-8 +- patch for building with tcl/tk 8.5 + +* Thu Sep 6 2007 Richard W.M. Jones - 3.10.0-7 +- Run chrpath to delete rpaths used on some of the stublibs. +- Ignore Parsetree module in dependency calculation. +- Fixed ocaml-find-{requires,provides}.sh regexp calculation so it doesn't + over-match module names. + +* Mon Sep 3 2007 Richard W.M. Jones - 3.10.0-6 +- ocaml-runtime provides ocaml(runtime) = 3.10.0, and + ocaml-find-requires.sh modified so that it adds this requires + to other packages. Now can upgrade base ocaml packages without + needing to rebuild everything else. + +* Mon Sep 3 2007 Richard W.M. Jones - 3.10.0-5 +- Don't include the release number in fedora-ocaml-release file, so + that packages built against this won't depend on the Fedora release. + +* Wed Aug 29 2007 Gerard Milmeister - 3.10.0-4 +- added BR util-linux-ng + +* Wed Aug 29 2007 Gerard Milmeister - 3.10.0-3 +- added BR gawk + +* Tue Aug 28 2007 Fedora Release Engineering - 3.10.0-2 +- Rebuild for selinux ppc32 issue. + +* Sat Jun 2 2007 Gerard Milmeister - 3.10.0-1 +- new version 3.10.0 +- split off devel packages +- rename subpackages to use ocaml- prefix + +* Thu May 24 2007 Gerard Milmeister - 3.09.3-2 +- added ocamlobjinfo + +* Sat Dec 2 2006 Gerard Milmeister - 3.09.3-1 +- new version 3.09.3 + +* Mon Aug 28 2006 Gerard Milmeister - 3.09.2-2 +- Rebuild for FE6 + +* Sun Apr 30 2006 Gerard Milmeister - 3.09.2-1 +- new version 3.09.2 + +* Fri Feb 17 2006 Gerard Milmeister - 3.09.1-2 +- Rebuild for Fedora Extras 5 + +* Thu Jan 5 2006 Gerard Milmeister - 3.09.1-1 +- new version 3.09.1 + +* Sun Jan 1 2006 Gerard Milmeister - 3.09.0-1 +- new version 3.09.0 + +* Sun Sep 11 2005 Gerard Milmeister - 3.08.4-1 +- New Version 3.08.4 + +* Wed May 25 2005 Toshio Kuratomi - 3.08.3-5 +- Bump and re-release as last build failed due to rawhide syncing. + +* Sun May 22 2005 Toshio Kuratomi - 3.08.3-4 +- Fix for gcc4 and the 32 bit assembly in otherlibs/num. +- Fix to allow compilation with RPM_OPT_FLAG defined -O level. + +* Sun May 22 2005 Jeremy Katz - 3.08.3-3 +- rebuild on all arches + +* Fri Apr 8 2005 Michael Schwendt +- rebuilt + +* Sat Mar 26 2005 Gerard Milmeister - 3.08.3-1 +- New Version 3.08.3 + +* Sat Feb 12 2005 Gerard Milmeister - 0:3.08.2-2 +- Added patch for removing rpath from shared libs + +* Sat Feb 12 2005 Gerard Milmeister - 0:3.08.2-1 +- New Version 3.08.2 + +* Thu Dec 30 2004 Thorsten Leemhuis - 0:3.07-6 +- add -x11lib _prefix/X11R6/_lib to configure; fixes labltk build + on x86_64 + +* Tue Dec 2 2003 Gerard Milmeister - 0:3.07-0.fdr.5 +- ocamldoc -> ocaml-ocamldoc +- ocaml-doc -> ocaml-docs + +* Fri Nov 28 2003 Gerard Milmeister - 0:3.07-0.fdr.4 +- Make separate packages for labltk, camlp4, ocamldoc, emacs and documentation + +* Thu Nov 27 2003 Gerard Milmeister - 0:3.07-0.fdr.2 +- Changed license tag +- Register info files +- Honor RPM_OPT_FLAGS +- New Patch + +* Fri Oct 31 2003 Gerard Milmeister - 0:3.07-0.fdr.1 +- First Fedora release + +* Mon Oct 13 2003 Axel Thimm +- Updated to 3.07. + +* Wed Apr 9 2003 Axel Thimm +- Rebuilt for Red Hat 9. + +* Tue Nov 26 2002 Axel Thimm +- Added _mandir/mano/* entry