From ce1fbe7113182361feef1b6f9d1be609f5aba99c Mon Sep 17 00:00:00 2001 From: Florian Angeletti Date: Thu, 14 Sep 2023 21:31:30 +0200 Subject: [PATCH] OCaml 5.1.0 announce and release page (#1470) * WIP: OCaml 5.1.0 announce * One latest release only * typo * Review: highlights * set OCaml 5.1.0 release date * review * minor grammar fixes * Minor grammar formatting fixes * OCaml 5.1.0: add missing changelog * minor formatting / grammar fixes * minor formatting change --------- Co-authored-by: Christine Rose --- .../changelog/ocaml/2023-09-14-ocaml-5.1.0.md | 995 ++++++++++++++++ data/releases/5.0.0.md | 60 +- data/releases/5.1.0.md | 1043 +++++++++++++++++ 3 files changed, 2068 insertions(+), 30 deletions(-) create mode 100644 data/changelog/ocaml/2023-09-14-ocaml-5.1.0.md create mode 100644 data/releases/5.1.0.md diff --git a/data/changelog/ocaml/2023-09-14-ocaml-5.1.0.md b/data/changelog/ocaml/2023-09-14-ocaml-5.1.0.md new file mode 100644 index 0000000000..1885d522a1 --- /dev/null +++ b/data/changelog/ocaml/2023-09-14-ocaml-5.1.0.md @@ -0,0 +1,995 @@ +--- +title: Release of OCaml 5.1.0 +description: Release of OCaml 5.1.0 +date: "2023-09-14" +tags: [ocaml, release] +changelog: | + ### Restored backends + + - [#11418](https://github.com/ocaml/ocaml/issues/11418), [#11708](https://github.com/ocaml/ocaml/issues/11708): RISC-V multicore support. + (Nicolás Ojeda Bär, review by KC Sivaramakrishnan) + + - [#11712](https://github.com/ocaml/ocaml/issues/11712), [#12258](https://github.com/ocaml/ocaml/issues/12258), [#12261](https://github.com/ocaml/ocaml/issues/12261): s390x / IBM Z multicore support: + OCaml & C stack separation; dynamic stack size checks; fiber and + effects support. + (Aleksei Nikiforov, with help from Vincent Laviron and Xavier Leroy, + additional suggestions by Luc Maranget, + review by the same and KC Sivaramakrishnan) + + - [#11642](https://github.com/ocaml/ocaml/issues/11642): Restore Cygwin port. Add GC messages for address space reservations + when OCAMLRUNPARAM option v includes 0x1000. + (David Allsopp, review by Xavier Leroy, Guillaume Munch-Maccagnoni + and Gabriel Scherer) + + ### Standard library: + + - [#12006](https://github.com/ocaml/ocaml/issues/12006), [#12064](https://github.com/ocaml/ocaml/issues/12064): Add `Marshal.Compression` flag to `Marshal.to_*` functions. + When this flag is explicitly set, marshaled data is compressed using ZSTD. + On some practical examples, the marshalled output became three times smaller + at no noticeable cost on the marshalling time. + (Xavier Leroy, review by Edwin Török and Gabriel Scherer, fix by Damien + Doligez) + + - [#10464](https://github.com/ocaml/ocaml/issues/10464): Add List.is_empty. + (Craig Ferguson, review by David Allsopp) + + - [#11848](https://github.com/ocaml/ocaml/issues/11848): Add `List.find_mapi`, + `List.find_index: ('a -> bool) -> 'a list -> int option`, + `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) + + - [#11410](https://github.com/ocaml/ocaml/issues/11410): Add Set.to_list, Map.to_list, Map.of_list, + `Map.add_to_list: key -> 'a -> 'a list t -> 'a list t`. + (Daniel Bünzli, review by Nicolás Ojeda Bär and Gabriel Scherer) + + - [#11836](https://github.com/ocaml/ocaml/issues/11836), [#11837](https://github.com/ocaml/ocaml/issues/11837): Add `Array.map_inplace`, `Array.mapi_inplace`, + `Float.Array.mapi_inplace` and `Float.Array.mapi_inplace`. + (Léo Andrès, review by Gabriel Scherer, KC Sivaramakrishnan and + Nicolás Ojeda Bär) + + - [#10967](https://github.com/ocaml/ocaml/issues/10967): Add Filename.temp_dir. + (David Turner, review by Anil Madhavapeddy, Valentin Gatien-Baron, Nicolás + Ojeda Bär, Gabriel Scherer, and Daniel Bünzli) + + - [#11246](https://github.com/ocaml/ocaml/issues/11246): Add "hash" and "seeded_hash" functions to Bool, Int, Char, Float, + Int32, Int64, and Nativeint. + (Nicolás Ojeda Bär, review by Xavier Leroy and Gabriel Scherer) + + - [#11488](https://github.com/ocaml/ocaml/issues/11488): Add `Mutex.protect: Mutex.t -> (unit -> 'a) -> 'a` + for resource-safe critical sections protected by a mutex. + (Simon Cruanes, review by Gabriel Scherer, Xavier Leroy, + Guillaume Munch-Maccagnoni) + + - [#11581](https://github.com/ocaml/ocaml/issues/11581): Add type equality witness + `type (_, _) eq = Equal: ('a, 'a) eq` + in a new module Stdlib.Type. + (Nicolás Ojeda Bär, review by Daniel Bünzli, Jacques Garrigue, Florian + Angeletti, Alain Frisch, Gabriel Scherer, Jeremy Yallop and Xavier Leroy) + + - [#11843](https://github.com/ocaml/ocaml/issues/11843): Add `In_channel.input_lines` and `In_channel.fold_lines`. + (Xavier Leroy, review by Nicolás Ojeda Bär and Wiktor Kuchta). + + - [#11856](https://github.com/ocaml/ocaml/issues/11856), [#11859](https://github.com/ocaml/ocaml/issues/11859): Using TRMC, the following `Stdlib` functions are now + tail-recursive: + Stdlib.(@), List.append, + List.concat_map. + (Jeremy Yallop, review by Daniel Bünzli, Anil Madhavapeddy, Nicolás Ojeda Bär, + Gabriel Scherer, and Bannerets) + + - [#11362](https://github.com/ocaml/ocaml/issues/11362), [#11402](https://github.com/ocaml/ocaml/issues/11402): Using TRMC, the following `Stdlib` functions are now + tail-recursive: + List.map, List.mapi, List.map2, + List.filter, List.filteri, List.filter_map, + List.init, + List.of_seq. + (Nicolás Ojeda Bär, review by Xavier Leroy and Gabriel Scherer) + + + - [#11878](https://github.com/ocaml/ocaml/issues/11878), [#11965](https://github.com/ocaml/ocaml/issues/11965): Prevent seek_in from marking buffer data as valid after + closing the channel. This could lead to inputting uninitialized bytes. + (Samuel Hym, review by Xavier Leroy and Olivier Nicole) + + - [#11128](https://github.com/ocaml/ocaml/issues/11128): Add In_channel.isatty, Out_channel.isatty. + (Nicolás Ojeda Bär, review by Gabriel Scherer and Florian Angeletti) + + - [#10859](https://github.com/ocaml/ocaml/issues/10859): Add `Format.pp_print_iter` and `Format.pp_print_array`. + (Léo Andrès and Daniel Bünzli, review by David Allsopp and Hugo Heuzard) + + - [#10789](https://github.com/ocaml/ocaml/issues/10789): Add `Stack.drop` + (Léo Andrès, review by Gabriel Scherer) + + * (*breaking change*) [#10899](https://github.com/ocaml/ocaml/issues/10899): Change Stdlib.nan from signaling NaN to quiet NaN. + (Greta Yorsh, review by Xavier Leroy, Guillaume Melquiond and + Gabriel Scherer) + + - [#11026](https://github.com/ocaml/ocaml/issues/11026), [#11667](https://github.com/ocaml/ocaml/issues/11667), [#11858](https://github.com/ocaml/ocaml/issues/11858): Rename the type of the accumulator + of fold functions to 'acc: + fold_left : ('acc -> 'a -> 'acc) -> 'acc -> 'a list -> 'acc + fold_right : ('a -> 'acc -> 'acc) -> 'a list -> 'acc -> 'acc + fold_left_map : ('acc -> 'a -> 'acc * 'b) -> 'acc -> 'a list -> 'acc * 'b list + ... + (Valentin Gatien-Baron and Francois Berenger, + review by Gabriel Scherer and Nicolás Ojeda Bär) + + - [#11354](https://github.com/ocaml/ocaml/issues/11354): Hashtbl.find_all is now tail-recursive. + (Fermín Reig, review by Gabriel Scherer) + + - [#11500](https://github.com/ocaml/ocaml/issues/11500): Make Hashtbl.mem non-allocating. + (Simmo Saan, review by Nicolás Ojeda Bär) + + - [#11412](https://github.com/ocaml/ocaml/issues/11412): Add Sys.is_regular_file + (Xavier Leroy, review by Anil Madhavapeddy, Nicolás Ojeda Bär, David Allsopp) + + - [#11322](https://github.com/ocaml/ocaml/issues/11322), [#11329](https://github.com/ocaml/ocaml/issues/11329): serialization functions Random.State.{of,to}_binary_string + between Random.State.t and string + (Gabriel Scherer, report by Yotam Barnoy, + review by Daniel Bünzli, Damien Doligez, Hugo Heuzard and Xavier Leroy) + + - [#11830](https://github.com/ocaml/ocaml/issues/11830): Add Type.Id with + `val provably_equal : 'a Type.Id.t -> 'b Type.Id.t -> ('a, 'b) Type.eq option` + (Daniel Bünzli, review by Jeremy Yallop, Gabriel Scherer, Wiktor Kuchta, + Nicolás Ojeda Bär) + + - [#12184](https://github.com/ocaml/ocaml/issues/12184), [#12320](https://github.com/ocaml/ocaml/issues/12320): Sys.rename Windows fixes on directory corner cases. + (Jan Midtgaard, review by Anil Madhavapeddy) + + * (*breaking change*) [#11565](https://github.com/ocaml/ocaml/issues/11565): Enable -strict-formats by default. Some incorrect format + specifications (for `printf`) where silently ignored and now fail. + Those new failures occur at compile-time, except if you use advanced + format features like `%(...%)` that parse format strings dynamically. + Pass -no-strict-formats to revert to the previous lenient behavior. + (Nicolás Ojeda Bär, review by David Allsopp) + + ### Installation size + + Specific efforts have been made during this release to reduce the filesystem + size of installed artifacts of the compiler distribution. + The installation size of 5.1 is 272 MiB compared to 521 MiB for 5.0. + Some of those changes will benefit all OCaml packages. + + - ocaml/RFCs[#23](https://github.com/ocaml/ocaml/issues/23), [#12006](https://github.com/ocaml/ocaml/issues/12006): use compressed marshaled format from [#12006](https://github.com/ocaml/ocaml/issues/12006) for .cmi, + .cmt, .cmti files, and for debug info in .cmo and .cma files, resulting in + major reduction in size. + (Xavier Leroy, review by Edwin Török and Gabriel Scherer, + RFC by Simon Cruanes) + + - [#11981](https://github.com/ocaml/ocaml/issues/11981): Reduce size of OCaml installations by removing debugging information + from installed bytecode executables. It is no longer possible to + run ocamldebug over these installed bytecode executables, nor to get + exception backtraces for them. + (Xavier Leroy, review by David Allsopp, report by Fabrice Le Fessant) + + * (*breaking change*) [#11993](https://github.com/ocaml/ocaml/issues/11993): install only bytecode executables for the `ocamlmklib`, `ocamlcmt`, + `ocamlprof`, `ocamlcp`, `ocamloptp`, and `ocamlmktop` tools, but no + native-code executables. A tool like `ocamlmklib` for example is now + installed directly to `$BINDIR/ocamlmklib`; `ocamlmklib.byte` and + `ocamlmklib.opt` are no longer installed to `$BINDIR`. + (Xavier Leroy, review by Gabriel Scherer) + + ### Runtime system: + + - [#11589](https://github.com/ocaml/ocaml/issues/11589), [#11903](https://github.com/ocaml/ocaml/issues/11903): Modify the GC pacing code to make sure the GC keeps + up with allocations in the presence of idle domains. + (Damien Doligez and Stephen Dolan, report by Florian Angeletti, + review by KC Sivaramakrishnan and Sadiq Jaffer) + + - [#11743](https://github.com/ocaml/ocaml/issues/11743): Speed up weak array operations + (KC Sivaramakrishnan, review by François Bobot and Sadiq Jaffer) + + - [#12131](https://github.com/ocaml/ocaml/issues/12131): Simplify implementation of weak hash sets, fixing a + performance regression. (Nick Barnes, review by François Bobot, + Alain Frisch and Damien Doligez). + + - [#11474](https://github.com/ocaml/ocaml/issues/11474), [#11998](https://github.com/ocaml/ocaml/issues/11998), [#12065](https://github.com/ocaml/ocaml/issues/12065): Add support for user-defined events in the runtime + event tracing system. + (Lucas Pluvinage, review by Sadiq Jaffer, Guillaume Munch-Maccagnoni, + Enguerrand Decorne, Gabriel Scherer and Anil Madhavapeddy) + + - [#11827](https://github.com/ocaml/ocaml/issues/11827), [#12249](https://github.com/ocaml/ocaml/issues/12249): Restore prefetching for GC marking + (Fabrice Buoro and Stephen Dolan, review by Gabriel Scherer and Sadiq Jaffer) + + - [#11144](https://github.com/ocaml/ocaml/issues/11144): Restore frame-pointers support for amd64 + (Fabrice Buoro, review by Frederic Bour and KC Sivaramakrishnan) + + - [#11935](https://github.com/ocaml/ocaml/issues/11935): Load frametables of dynlink'd modules in batch + (Stephen Dolan, review by David Allsopp and Guillaume Munch-Maccagnoni) + + - [#11284](https://github.com/ocaml/ocaml/issues/11284), [#12525](https://github.com/ocaml/ocaml/issues/12525): Use compression of entries scheme when pruning mark stack. + Can decrease memory usage for some workloads, otherwise should be + unobservable. + (Tom Kelly, review by Sabine Schmaltz, Sadiq Jaffer and Damien Doligez) + + * (*breaking change*) [#11865](https://github.com/ocaml/ocaml/issues/11865), [#11868](https://github.com/ocaml/ocaml/issues/11868), [#11876](https://github.com/ocaml/ocaml/issues/11876): Clarify that the operations of a custom + block must never access the OCaml runtime. The previous + documentation only mentioned the main illicit usages. In particular, + since OCaml 5.0, it is no longer safe to call + `caml_remove_global_root` or `caml_remove_generational_global_root` + from within the C finalizer of a custom block, or within the + finalization function passed to `caml_alloc_final`. As a workaround, + such a finalization operation can be registered with `Gc.finalize` + instead, which guarantees to run the finalizer at a safe point. + (Report by Timothy Bourke, discussion by Yotam Barnoy, Timothy + Bourke, Sadiq Jaffer, Xavier Leroy, Guillaume Munch-Maccagnoni, and + Gabriel Scherer) + + - [#12130](https://github.com/ocaml/ocaml/issues/12130): Fix multicore crashes with weak hash sets. Fixes [#11934](https://github.com/ocaml/ocaml/issues/11934). + (Nick Barnes, review by François Bobot) + + - [#12099](https://github.com/ocaml/ocaml/issues/12099): Add ocamlrund option, -events, to produce a trace of + debug events during bytecode interpretation. Fixes [#12098](https://github.com/ocaml/ocaml/issues/12098). + (Richard L Ford, review by Gabriel Scherer) + + - [#12001](https://github.com/ocaml/ocaml/issues/12001): Fix book keeping for last finalisers during the minor cycle + (KC Sivaramakrishnan and Enguerrand Decorne, report by Guillaume Bury + and Vincent Laviron, review by Sadiq Jaffer and KC Sivaramakrishnan) + + - [#11919](https://github.com/ocaml/ocaml/issues/11919): New runtime events counters for major heap stats and minor heap + resizing. + (Sadiq Jaffer, review by Gabriel Scherer and David Allsopp) + + - [#11287](https://github.com/ocaml/ocaml/issues/11287), [#11872](https://github.com/ocaml/ocaml/issues/11872), [#11955](https://github.com/ocaml/ocaml/issues/11955): Clean up reserved header bits (once used for + Spacetime profiling). + (Nick Barnes, review by Gabriel Scherer and Damien Doligez) + + - [#11750](https://github.com/ocaml/ocaml/issues/11750): Decouple major slice from minor GC. + (KC Sivaramakrishnan, review by Sadiq Jaffer, Guillaume Munch-Maccagnoni and + Damien Doligez) + + - [#11796](https://github.com/ocaml/ocaml/issues/11796): protect lazy computation of code fragment digest by a mutex. + This makes the thread sanitizer happier, and avoids duplicating + the hashing work. + (Gabriel Scherer, review by Xavier Leroy, report by Olivier Nicole) + + - [#11137](https://github.com/ocaml/ocaml/issues/11137): new `Unsafe_store_tag(val, new_tag)` macro to stop using + `Tag_val(val)` as lvalue. + (Gabriel Scherer, review by Xavier Leroy, Guillaume Munch-Maccagnoni + and Nicolás Ojeda Bär) + + - [#11880](https://github.com/ocaml/ocaml/issues/11880): Restore the correct sigmask in systhreads. + (Christiano Haesbaert, review by Guillaume Munch-Maccagnoni and + Sébastien Hinderer) + + - [#11881](https://github.com/ocaml/ocaml/issues/11881): Fix thread-unsafety of registration of operations for "custom" + values. + (Guillaume Munch-Maccagnoni, review by Gabriel Scherer and KC + Sivaramakrishnan) + + - [#11980](https://github.com/ocaml/ocaml/issues/11980): fix quadratic behavior in natdynlink by using a STW section + for frame-descriptor updates. + (Gabriel Scherer, review by Sadiq Jaffer, report by André Maroneze + for Frama-C and Guillaume Melquiond for Coq) + + - [#12121](https://github.com/ocaml/ocaml/issues/12121): unrooted implementations of caml_callback*_exn + (Gabriel Scherer, review by KC Sivaramakrishnan and Xavier Leroy) + + - [#3921](https://github.com/ocaml/ocaml/issues/3921), [#12039](https://github.com/ocaml/ocaml/issues/12039), [#12128](https://github.com/ocaml/ocaml/issues/12128): poll for signals in long-running polymorphic + comparisons. + (B. Szilvasy, Gabriel Scherer and Xavier Leroy, review by + Stefan Muenzel, Guillaume Munch-Maccagnoni and Damien Doligez) + + - [#12231](https://github.com/ocaml/ocaml/issues/12231): Support MinGW-w64 11.0 winpthreads library, where the macro + to set up to get flexdll working changed + (David Allsopp and Samuel Hym, light review by Xavier Leroy) + + ### Language features: + + * (*breaking change*) [#11694](https://github.com/ocaml/ocaml/issues/11694): Add short syntax for generative functor types `() -> ...` + (Jeremy Yallop, review by Gabriel Scherer, Nicolás Ojeda Bär, + Jacques Garrigue) + + + * (*breaking change*) [#11457](https://github.com/ocaml/ocaml/issues/11457): Remove old polymorphic variant syntax. + With ``type t = [ `A | `B ]``, one could use the syntax `#t` in types, + where it means the same thing as `[< t]`, and in patterns, where it means + ``(`A | `B)``. The use of `#t` in types for polymorphic variants + was deprecated since 2001, and is now removed. The syntax remains available + in patterns, or for objects -- when `t` is a class type. + (Stefan Muenzel, review by Gabriel Scherer and Jacques Garrigue) + + * (*breaking change*) [#11984](https://github.com/ocaml/ocaml/issues/11984): Add dedicated syntax for generative functor application. + Previously, OCaml did not distinguish between `F ()` and + `F (struct end)`, even though the latter looks applicative. Instead, + the decision between generative and applicative functor application + was made based on the type of `F`. With this patch, we now distinguish + these two application forms; writing `F (struct end)` for a generative + functor leads to new warning 73. + (Frederic Bour and Richard Eisenberg, review by Florian Angeletti) + + + - [#9975](https://github.com/ocaml/ocaml/issues/9975), [#11365](https://github.com/ocaml/ocaml/issues/11365): Make empty types (`type t = |`) immediate. + (Antal Spector-Zabusky, review by Gabriel Scherer) + + ### Type system: + + * (*breaking change*) [#6941](https://github.com/ocaml/ocaml/issues/6941), [#11187](https://github.com/ocaml/ocaml/issues/11187), [#12483](https://github.com/ocaml/ocaml/issues/12483): prohibit using classes through recursive modules + inheriting or including a class belonging to a mutually-recursive module + would previous behave incorrectly, and now results in a clean error. + (Leo White, review by Gabriel Scherer and Florian Angeletti) + + * (*breaking change*) [#12189](https://github.com/ocaml/ocaml/issues/12189), [#12211](https://github.com/ocaml/ocaml/issues/12211): anonymous row variables in explicitly polymorphic type + annotation, e.g. `'a. [< X of 'a ] -> 'a`, are now implicitly + universally quantified (in other words, the example above is now read + as `'a 'r. ([< X of 'a ] as 'r) -> 'a`). + (Florian Angeletti and Gabriel Scherer, review by Jacques Garrigue) + + ### Code generation and optimizations: + + - [#11967](https://github.com/ocaml/ocaml/issues/11967): Remove traces of Obj.truncate, which allows some mutable + loads to become immutable. + (Nick Barnes, review by Vincent Laviron and KC Sivaramakrishnan) + + - [#9945](https://github.com/ocaml/ocaml/issues/9945), [#10883](https://github.com/ocaml/ocaml/issues/10883): Turn boolean-result float comparisons into primitive operations + Uses the architecture's elementary operations for float comparisons, + when available, rather than branching and then setting the return value. + (Stefan Muenzel, review by Stephen Dolan, Alain Frisch and Vincent Laviron) + + - [#8998](https://github.com/ocaml/ocaml/issues/8998), [#11321](https://github.com/ocaml/ocaml/issues/11321), [#11430](https://github.com/ocaml/ocaml/issues/11430): change mangling of OCaml long identifiers + from `camlModule__name_NNN` to `camlModule.name_NNN`. The previous + mangling schema, using `__`, was ambiguous. + (Xavier Leroy, report by sliquister and Michael Bacarella, + review by Gabriel Scherer) + + - [#10834](https://github.com/ocaml/ocaml/issues/10834): The -safer-matching option disables type-based optimizations of + pattern-matching compilation. This allows to produce a match failure if + a pattern-matching was wrongly assumed to be exhaustive. Since the + exhaustiveness check for GADTs has had bugs in the past, it may be + useful if you need extra security with GADTs. + (Jacques Garrigue, review by Gabriel Scherer) + + - [#11102](https://github.com/ocaml/ocaml/issues/11102): Speed up register allocation by permanently spilling registers + (Stephen Dolan, review by Xavier Leroy) + + - [#11383](https://github.com/ocaml/ocaml/issues/11383): Restrict the local function optimisation to forbid moving code + inside a sub-function + (Vincent Laviron, review by Gabriel Scherer) + + - [#11686](https://github.com/ocaml/ocaml/issues/11686): Better spilling heuristic for the Linear Scan allocator for more + efficient stack usage. + (Nicolás Ojeda Bär, Gabriel Scherer, Alain Frisch, review by Gabriel Scherer, + Alain Frisch and Nathanaëlle Courant) + + - [#11904](https://github.com/ocaml/ocaml/issues/11904): Remove arm, i386 native-code backends that were already + disabled at configuration time. + (Nicolás Ojeda Bär, review by Stephen Dolan, Anil Madhavapeddy, and Xavier + Leroy) + + - [#11134](https://github.com/ocaml/ocaml/issues/11134): Optimise 'include struct' in more cases + (Stephen Dolan, review by Leo White and Vincent Laviron) + + ### Other libraries: + + - [#11374](https://github.com/ocaml/ocaml/issues/11374): Remove pointer cast to a type with stricter alignment requirements + in Windows implementation of Unix.gettimeofday. Windows implementations of + caml_unix_map_file, caml_unix_lseek and caml_unix_lseek_64 now release the + runtime lock. Windows implementation of caml_unix_lockf modernised and + simplified. Where possible, 64 bit integers are used instead of LARGE_INTEGER + structs. + (David Allsopp, review by Jonah Beckford and Xavier Leroy) + + - [#11475](https://github.com/ocaml/ocaml/issues/11475): Make Unix terminal interface bindings domain-safe + (Olivier Nicole and Xavier Leroy, review by Xavier Leroy) + + - [#11775](https://github.com/ocaml/ocaml/issues/11775): Unix.write on a non-blocking socket under Windows will return normally + if the write blocks after some data has already been written (as otherwise + there is no way of knowing how much data has been written before + blocking). The same behaviour was already present under Unix. + (Nicolás Ojeda Bär, review by David Allsopp) + + * (*breaking change*) [#11991](https://github.com/ocaml/ocaml/issues/11991): Unix on Windows: map ERROR_TOO_MANY_LINKS to EMLINK. + (Nicolás Ojeda Bär) + + - [#12067](https://github.com/ocaml/ocaml/issues/12067): Document Windows specific meanings of `Unix.process_status` + type + (Samuel Hym, review by David Allsopp) + + - [#12072](https://github.com/ocaml/ocaml/issues/12072): Document and test that Sys.rename works over directories too + (Jan Midtgaard, review by Anil Madhavapeddy and Xavier Leroy) + + ### Tools: + + - [#11889](https://github.com/ocaml/ocaml/issues/11889), [#11978](https://github.com/ocaml/ocaml/issues/11978): ocamldoc: handle injectivity annotations and wildcards in type + parameters. + (Florian Angeletti, report by Wiktor Kuchta, review by Jules Aguillon) + + - [#11787](https://github.com/ocaml/ocaml/issues/11787): Fix GDB scripts to work with OCaml 5's heap layout. (Nick + Barnes) + + - [#11772](https://github.com/ocaml/ocaml/issues/11772): fix ocamlyacc's handling of raw string literals + (Demi Marie Obenour) + + - [#9290](https://github.com/ocaml/ocaml/issues/9290): Add a directive to switch off debugging in toplevel. + This allows to see optimized bytecode with -dlambda. + (Jacques Garrigue, review by Gabriel Scherer) + + - [#11166](https://github.com/ocaml/ocaml/issues/11166): ocamllex: the union of two character sets "cset1 | cset2" can now be + used in any context where a character set is expected. + (Nicolás Ojeda Bär, Martin Jambon, review by Sébastien Hinderer) + + - [#11718](https://github.com/ocaml/ocaml/issues/11718): ocamlyacc: OCaml-style comments are now supported, in addition to + the C-style comments already supported. The syntax is the same as that used + in OCaml code. + (Demi Marie Obenour, review by Damien Doligez) + + - [#11728](https://github.com/ocaml/ocaml/issues/11728): ocamlyacc: generate line directives for %type declarations + (Demi Marie Obenour, review by Damien Doligez) + + - [#11773](https://github.com/ocaml/ocaml/issues/11773): ocamlyacc: Do not allow quoted literals (such as 'a' or "bc") + in a token name or %type declaration. Previously such literals were + accepted by ocamlyacc, but produced malformed OCaml that was rejected + by the compiler. + (Demi Marie Obenour, review by Gabriel Scherer) + + - [#11774](https://github.com/ocaml/ocaml/issues/11774): ocamlyacc: fail if there is an I/O error + (Demi Marie Obenour, review by Gabriel Scherer) + + - [#11973](https://github.com/ocaml/ocaml/issues/11973): Add support for postfixed mingw host triplets + (Romain Beauxis) + + - [#12165](https://github.com/ocaml/ocaml/issues/12165): ocamldoc, use standard doctype to avoid quirk mode. + (Florian Angeletti, review by Gabriel Scherer) + + ### Manual and documentation: + + - [#11476](https://github.com/ocaml/ocaml/issues/11476): Add examples in documentation of Hashtbl, Queue, Atomic, Format + (Simon Cruanes, review by Yotam Barnoy, Gabriel Scherer, Daniel Bünzli, + Ulugbek Abdullaev, and Nicolás Ojeda Bär) + + - [#11883](https://github.com/ocaml/ocaml/issues/11883), [#11884](https://github.com/ocaml/ocaml/issues/11884): Update documentation for In_channel and Out_channel + with examples and sections to group related functions. + (Kiran Gopinathan, review by Daniel Bünzli and Xavier Leroy) + + + - [#12095](https://github.com/ocaml/ocaml/issues/12095), [#12097](https://github.com/ocaml/ocaml/issues/12097): Put the sample code of the user's manual and reference + documentation of the standard library under the CC0 1.0 Universal + (CC0 1.0) Public Domain Dedication license. + + - [#11892](https://github.com/ocaml/ocaml/issues/11892): Document the semantic differences of Unix.exec* between Unix and + Windows. + (Boris Yakobowski, review by Daniel Bünzli, Gabriel Scherer and Nicolás Ojeda + Bär) + + - [#9430](https://github.com/ocaml/ocaml/issues/9430), [#11291](https://github.com/ocaml/ocaml/issues/11291): Document the general desugaring rules for binding operators. + (Gabriel Scherer, review by Nicolás Ojeda Bär) + + - [#11481](https://github.com/ocaml/ocaml/issues/11481): Fix the type of Unix.umask to Unix.file_perm -> Unix.file_perm + (Favonia, review by Sébastien Hinderer) + + - [#11514](https://github.com/ocaml/ocaml/issues/11514): Document ocamltest builtin variables and actions + (Olivier Nicole, review by Sébastien Hinderer) + + - [#11676](https://github.com/ocaml/ocaml/issues/11676): Fix missing since annotation in the `Sys` and `Format` modules + (Github user Bukolab99, review by Florian Angeletti) + + - [#12028](https://github.com/ocaml/ocaml/issues/12028): Update format documentation to make it clearer that + `pp_print_newline` flushes its newline + (Florian Angeletti, review by Gabriel Scherer) + + - [#12201](https://github.com/ocaml/ocaml/issues/12201): in the tutorial on modules, replace priority queue example by + a simpler example based on FIFO queues. + (Xavier Leroy, review by Anil Madhavapeddy and Nicolás Ojeda Bär). + + - [#12352](https://github.com/ocaml/ocaml/issues/12352): Fix a typo in the documentation of Arg.write_arg + (Christophe Raffalli, review by Florian Angeletti) + + - [#7179](https://github.com/ocaml/ocaml/issues/7179), [#11894](https://github.com/ocaml/ocaml/issues/11894): correct the description of CAMLreturn and CAMLreturn0 in + the Interfacing C page and memory.h file. + (Dong An, review by Guillaume Munch-Maccagnoni and Olivier Nicole ) + + ### Compiler user-interface and warnings: + + - [#10647](https://github.com/ocaml/ocaml/issues/10647): Show hints for the "undefined global" error in the toplevel + (Wiktor Kuchta, review by Gabriel Scherer) + + - [#12116](https://github.com/ocaml/ocaml/issues/12116): Don't suggest to insert a semicolon when the type is not unit + (Jules Aguillon, review by Florian Angeletti) + + - [#11679](https://github.com/ocaml/ocaml/issues/11679): Improve the error message about too many arguments to a function + (Jules Aguillon, review by Gabriel Scherer and Florian Angeletti) + + - [#10009](https://github.com/ocaml/ocaml/issues/10009): Improve the error reported by mismatched struct/sig and =/: in module + and module type bindings. + (Jules Aguillon, review by Gabriel Scherer) + + - [#11530](https://github.com/ocaml/ocaml/issues/11530): Include kinds in kind mismatch error message. + "Error: This variant or record definition does not match that of type M.t + The original is abstract, but this is a record". + (Leonhard Markert, review by Gabriel Scherer and Florian Angeletti) + + - [#11646](https://github.com/ocaml/ocaml/issues/11646): Add colors to error message hints. + (Christiana Anthony, review by Florian Angeletti) + + - [#11235](https://github.com/ocaml/ocaml/issues/11235), [#11864](https://github.com/ocaml/ocaml/issues/11864): usage warnings for constructors and fields can now be disabled + on field-by-field or constructor-by-constructor basis + (Florian Angeletti, review by Gabriel Scherer) + + - [#11888](https://github.com/ocaml/ocaml/issues/11888): Improve the error message when type variables cannot be deduced from + the type parameters: + Before: + "Error: In this definition, a type variable cannot be deduced + from the type parameters." + After: + "Error: In the GADT constructor + T : 'a -> 'a s t + the type variable 'a cannot be deduced from the type parameters." + (Stefan Muenzel, review by Florian Angeletti and Gabriel Scherer) + + + - [#10818](https://github.com/ocaml/ocaml/issues/10818): Preserve integer literal formatting in type hint. + (Leonhard Markert, review by Gabriel Scherer and Florian Angeletti) + + - [#11338](https://github.com/ocaml/ocaml/issues/11338): Turn some partial application warnings into hints. + (Leo White, review by Stephen Dolan) + + - [#10931](https://github.com/ocaml/ocaml/issues/10931): Improve warning 14 (illegal backslash) with a better explanation + of the causes and how to fix it. + (David Allsopp, Florian Angeletti, Lucas De Angelis, Gabriel Scherer, + review by Nicolás Ojeda Bär, Florian Angeletti, David Allsopp and + Gabriel Scherer) + + - [#10911](https://github.com/ocaml/ocaml/issues/10911): Improve the location reported by parenthesized assert expressions + (Fabian Hemmer, review by Gabriel Scherer) + + - [#1391](https://github.com/ocaml/ocaml/issues/1391), [#7645](https://github.com/ocaml/ocaml/issues/7645), [#3922](https://github.com/ocaml/ocaml/issues/3922): Add an early error when compiling different + modules with mismatching -for-pack + (Pierre Chambart and Vincent Laviron, review by Mark Shinwell) + + - [#11297](https://github.com/ocaml/ocaml/issues/11297): Report "unclosed" error when "done" is missing in a "do .. done" + construct. + (Nicolás Ojeda Bär, review by Gabriel Scherer) + + - [#11635](https://github.com/ocaml/ocaml/issues/11635), [#5461](https://github.com/ocaml/ocaml/issues/5461), [#10564](https://github.com/ocaml/ocaml/issues/10564): turn warning 31 (Module_linked_twice) into a hard error + for ocamlc — this was already an error with ocamlopt. + (Hugo Heuzard, review by Valentin Gatien-Baron and Gabriel Scherer) + + - [#11653](https://github.com/ocaml/ocaml/issues/11653): Add the -no-absname option to ocamlc, ocamlopt and ocamldep. + (Abiola Abdulsalam, review by Sébastien Hinderer and Florian Angeletti) + + - [#11696](https://github.com/ocaml/ocaml/issues/11696): Add the -no-g option to ocamlc and ocamlopt. + (Abiola Abdulsalam, review by Sébastien Hinderer, Nicolás Ojeda Bär and + Florian Angeletti) + + - [#11722](https://github.com/ocaml/ocaml/issues/11722): clearer error messages on non-well-founded type definitions + (Gabriel Scherer, review by Jacques Garrigue) + + - [#11819](https://github.com/ocaml/ocaml/issues/11819): make the `native_compiler` and `native_dynlink` configuration + variables available through ocamlc -config. + (Sébastien Hinderer, review by Gabriel Scherer and David Allsopp) + + - [#8602](https://github.com/ocaml/ocaml/issues/8602), [#11863](https://github.com/ocaml/ocaml/issues/11863): Add -stop-after lambda flag option + (Douglas Smith and Dmitrii Kosarev, review by Gabriel Scherer) + + - [#11910](https://github.com/ocaml/ocaml/issues/11910): Simplify naming convention for shadowed or ephemeral identifiers in + error messages (eg: `Illegal shadowing of included type t/2 by t`) + (Florian Angeletti, review by Jules Aguillon) + + - [#12024](https://github.com/ocaml/ocaml/issues/12024): insert a blank line between separate compiler messages + (Gabriel Scherer, review by Florian Angeletti, report by David Wong) + + - [#12088](https://github.com/ocaml/ocaml/issues/12088), [#9265](https://github.com/ocaml/ocaml/issues/9265), [#11949](https://github.com/ocaml/ocaml/issues/11949): ocamldebug: fix confusing repeating behavior + on blank lines within source scripts + (Damien Doligez, review by Gabriel Scherer, report by Gaëtan Gilbert) + + - [#12107](https://github.com/ocaml/ocaml/issues/12107): use aliases to mark weak row variables: `_[< ... ]`, `< _..>`, `_#ct` + are now rendered as `[< ...] as '_weak1`, `< .. > as '_weak1`, + and `#ct as '_weak1`. + (Florian Angeletti, suggestion by Stefan Muenzel, review by Gabriel Scherer) + + - [#12051](https://github.com/ocaml/ocaml/issues/12051): Improve the error messages when type variables cannot be generalized + (Stefan Muenzel, review by Florian Angeletti) + + * (*breaking change*) [#12094](https://github.com/ocaml/ocaml/issues/12094): Trigger warning 5 (ignored-partial-application) when the scrutinee of + a pattern matching is of arrow type and all cases match wildcard or exception + patterns. + (Nicolás Ojeda Bär, review by Gabriel Scherer) + + ### Internal/compiler-libs changes: + + - [#11018](https://github.com/ocaml/ocaml/issues/11018), [#11869](https://github.com/ocaml/ocaml/issues/11869): Clean up Types.Variance, adding a description of + the lattice used, and defining explicitly composition. + (Jacques Garrigue, review by Gabriel Scherer and Jeremy Yallop) + + - [#11536](https://github.com/ocaml/ocaml/issues/11536): Introduce wrapper functions for level management + ([Ctype.with_level], etc) and for type variable scoping + ([Typetexp.with_local_type_variable_scope]). + The older API ([Ctype.(begin_def,end_def)], [Typetexp.(narrow,widen)], etc.) + is now removed. + (Jacques Garrigue and Takafumi Saikawa, review by Gabriel Scherer) + + - [#11601](https://github.com/ocaml/ocaml/issues/11601), [#11612](https://github.com/ocaml/ocaml/issues/11612), [#11628](https://github.com/ocaml/ocaml/issues/11628), [#11613](https://github.com/ocaml/ocaml/issues/11613), [#11623](https://github.com/ocaml/ocaml/issues/11623), [#12120](https://github.com/ocaml/ocaml/issues/12120) : Clean up some + global state handling in emitcode, bytepackager, bytegen, + bytesections, spill. + (Hugo Heuzard, Stefan Muenzel, review by Vincent Laviron, Gabriel Scherer + and Nathanaëlle Courant) + + - [#12119](https://github.com/ocaml/ocaml/issues/12119), [#12188](https://github.com/ocaml/ocaml/issues/12188), [#12191](https://github.com/ocaml/ocaml/issues/12191): mirror type constraints on value binding in the + parsetree: + the constraint `typ` in `let pat : typ = exp` is now directly stored + in the value binding node in the parsetree. + (Florian Angeletti, review by Richard Eisenberg) + + - [#11912](https://github.com/ocaml/ocaml/issues/11912): Refactoring handling of scoped type variables + (Richard Eisenberg, review by Gabriel Scherer and Florian Angeletti) + + + - [#11691](https://github.com/ocaml/ocaml/issues/11691), [#11706](https://github.com/ocaml/ocaml/issues/11706): use __asm__ instead of asm for strict ISO C conformance + (Xavier Leroy, report by Gregg Reynolds , review by Sadiq Jaffer) + + - [#11764](https://github.com/ocaml/ocaml/issues/11764): add prototypes to old-style C function definitions and declarations + (Antonin Décimo, review by Xavier Leroy) + + - [#11693](https://github.com/ocaml/ocaml/issues/11693): Remove use of C99 Variable Length Arrays (VLAs) in the runtime. + (David Allsopp, review by Xavier Leroy, Guillaume Munch-Maccagnoni, + Stefan Muenzel and Gabriel Scherer) + + - [#12138](https://github.com/ocaml/ocaml/issues/12138): Generalise interface for BUILD_PATH_PREFIX_MAP mapping. + Absolute paths are now rewritten too. + (Richard L Ford, suggestions and review by Gabriel Scherer) + + - [#10512](https://github.com/ocaml/ocaml/issues/10512): explain the compilation strategy for switches on constructors + (Gabriel Scherer, review by Vincent Laviron) + + - [#11990](https://github.com/ocaml/ocaml/issues/11990): Improve comments and macros around frame descriptors. + (Nick Barnes, review by Gabriel Scherer) + + - [#11847](https://github.com/ocaml/ocaml/issues/11847), [#11849](https://github.com/ocaml/ocaml/issues/11849), [#11851](https://github.com/ocaml/ocaml/issues/11851), [#11898](https://github.com/ocaml/ocaml/issues/11898): small refactorings in the type checker + (Gabriel Scherer, review by Nicolás Ojeda Bär) + + - [#11027](https://github.com/ocaml/ocaml/issues/11027): Separate typing counter-examples from type_pat into retype_pat; + type_pat is no longer in CPS. + (Jacques Garrigue and Takafumi Saikawa, review by Gabriel Scherer) + + - [#11286](https://github.com/ocaml/ocaml/issues/11286), [#11515](https://github.com/ocaml/ocaml/issues/11515): disambiguate identifiers by using how recently they have + been bound in the current environment + (Florian Angeletti, review by Gabriel Scherer) + + - [#11364](https://github.com/ocaml/ocaml/issues/11364): Allow `make -C testsuite promote` to take `TEST` and `LIST` variables + (Antal Spector-Zabusky, review by Gabriel Scherer and David Allsopp) + + - [#11446](https://github.com/ocaml/ocaml/issues/11446): document switch compilation (lambda/switch.ml) + (Gabriel Scherer, review by Luc Maranget and Vincent Laviron) + + - [#11568](https://github.com/ocaml/ocaml/issues/11568): Encode inline record types in Path.t + (Leo White and Hyunggyu Jang, review by Gabriel Scherer) + + - [#11569](https://github.com/ocaml/ocaml/issues/11569): Remove hash type encoding + (Hyunggyu Jang, review by Gabriel Scherer and Florian Angeletti) + + - [#11627](https://github.com/ocaml/ocaml/issues/11627): use return values instead of globals for linear scan intervals + (Stefan Muenzel, review by Nicolás Ojeda Bär) + + - [#11634](https://github.com/ocaml/ocaml/issues/11634): Dll.open_dll now properly handles opening for execution while already + opened for checking + (Hugo Heuzard, review by Nicolás Ojeda Bär) + + * (*breaking change*) [#11745](https://github.com/ocaml/ocaml/issues/11745), [#12358](https://github.com/ocaml/ocaml/issues/12358): Debugger and toplevels: embed printer types rather than + reading their representations from topdirs.cmi at runtime. + This change also removes the ocamlmktop initialization module introduced + in [#11382](https://github.com/ocaml/ocaml/issues/11382) which was no longer useful. + This change breaks toplevel scripts relying on the visibility of `Topdirs` + in the initial toplevel environment without loading `topfind`. + Since the opam default `.ocamlinit` file loads `topfind`, it is expected + that only scripts run with `ocaml -noinit` are affected. + For those scripts, accessing `Topdirs` now requires the `compiler-libs` + directory to be added to the toplevel search path with + ``` + #directory "+compiler-libs";; + ```` + as was already the case for the other modules in the toplevel interface + library. + (Sébastien Hinderer, review by Florian Angeletti, Nicolás Ojeda Bär and + Gabriel Scherer) + + - [#11615](https://github.com/ocaml/ocaml/issues/11615): remove global variables form asmcomp/linearize.ml + (Stefan Muenzel, review by Nicolás Ojeda Bär + + - [#10856](https://github.com/ocaml/ocaml/issues/10856): Add location, attribute(s) visitors to Tast_mapper/Tast_iterator + (Yan Dong, review by Nicolás Ojeda Bär and Gabriel Scherer) + + - [#11763](https://github.com/ocaml/ocaml/issues/11763), [#11759](https://github.com/ocaml/ocaml/issues/11759), [#11861](https://github.com/ocaml/ocaml/issues/11861): Enable stricter C compilation warnings, use + strict prototypes on primitives. + (Antonin Décimo, review by Xavier Leroy, David Allsopp and Sébastien + Hinderer) + + - [#11933](https://github.com/ocaml/ocaml/issues/11933): Use the correct machtype when reading the code pointer from closures + (Nathanaëlle Courant, review by Gabriel Scherer and Vincent Laviron) + + - [#11972](https://github.com/ocaml/ocaml/issues/11972): refactor runtime/frame_descriptors.c + in preparation for quadratic-time fix + (Gabriel Scherer, review by Enguerrand Decorne) + + - [#11997](https://github.com/ocaml/ocaml/issues/11997): translate structured constants into their Obj.t representation + at compile time rather than link time. Changes the way dumpobj prints + these constants because their representation becomes untyped. + (Sébastien Hinderer, review by Xavier Leroy, Nicolás Ojeda Bär and + Hugo Heuzard) + + - [#12011](https://github.com/ocaml/ocaml/issues/12011): remove Ctype.reified_var_counter + (Takafumi Saikawa and Jacques Garrigue, review by Gabriel Scherer) + + - [#12012](https://github.com/ocaml/ocaml/issues/12012): move calls to Typetexp.TyVarEnv.reset inside with_local_level etc. + (Jacques Garrigue and Takafumi Saikawa, review by Gabriel Scherer) + + - [#12034](https://github.com/ocaml/ocaml/issues/12034): a logarithmic algorithm to find the next free variable + (Gabriel Scherer, review by Stefan Muenzel) + + - [#12092](https://github.com/ocaml/ocaml/issues/12092): remove Lev_module_definition from lambda + (Nick Roberts, review by Gabriel Scherer) + + - [#12117](https://github.com/ocaml/ocaml/issues/12117): Remove arity-interrupting elaboration of module unpacks + (Nick Roberts, review by Richard Eisenberg and Jacques Garrigue) + + - [#12118](https://github.com/ocaml/ocaml/issues/12118): stop storing names of predefined exceptions in the + cu_required_globals field of compilation unit descriptors. + (Sébastien Hinderer, review by Vincent Laviron) + + - [#12125](https://github.com/ocaml/ocaml/issues/12125): Add Misc.print_see_manual and modify [@manual_ref] to accept + lists for simpler printing of manual references + (Stefan Muenzel, review by Florian Angeletti) + + - [#12509](https://github.com/ocaml/ocaml/issues/12509): Use strict prototypes on primitives when generating a standalone + bytecode executable (`ocamlc -custom`). + (Antonin Décimo, review by Xavier Leroy) + + ### Build system: + + - [#11844](https://github.com/ocaml/ocaml/issues/11844): Reduce verbosity of `make` logs by printing program invocations in + shorthand (eg `OCAMLC foo.cmo`). Setting `V=1` recovers the old style (with + full command-lines). + (Xavier Leroy, Nicolás Ojeda Bär, review by Sébastien Hinderer) + + + - [#11590](https://github.com/ocaml/ocaml/issues/11590): Allow installing to a destination path containing spaces. + (Élie Brami, review by Sébastien Hinderer and David Allsopp) + + - [#11243](https://github.com/ocaml/ocaml/issues/11243), [#11248](https://github.com/ocaml/ocaml/issues/11248), [#11268](https://github.com/ocaml/ocaml/issues/11268), [#11420](https://github.com/ocaml/ocaml/issues/11420), [#11675](https://github.com/ocaml/ocaml/issues/11675): merge the sub-makefiles into + the root Makefile. + (Sébastien Hinderer, review by David Allsopp and Florian Angeletti) + + - [#11828](https://github.com/ocaml/ocaml/issues/11828): Compile otherlibs/ C stubs in two version for native and bytecode + (Olivier Nicole, review by Sébastien Hinderer and Xavier Leroy) + + - [#12265](https://github.com/ocaml/ocaml/issues/12265): Stop adding -lexecinfo to cclibs (leftover debugging code from the + multicore project). Harden the feature probe for -lm in configure so -lm is + only added if strictly necessary. configure.ac now correctly propagates + library flags for the Windows ports, allowing Windows OCaml to be configured + with ZSTD support. + (David Allsopp, review by Sébastien Hinderer) + + - [#12372](https://github.com/ocaml/ocaml/issues/12372): Pass option -no-execute-only to the linker for OpenBSD >= 7.3 + so that code sections remain readable, as needed for closure marshaling. + (Xavier Leroy and Anil Madhavapeddy, review by Anil Madhavapeddy and + Sébastien Hinderer) + + ### Bug fixes: + + - [#12062](https://github.com/ocaml/ocaml/issues/12062): fix runtime events consumer: when events are dropped they shouldn't be + parsed. (Lucas Pluvinage) + + - [#12132](https://github.com/ocaml/ocaml/issues/12132): Fix overcounting of minor collections in GC stats. + (Damien Doligez, review by Gabriel Scherer) + + - [#12017](https://github.com/ocaml/ocaml/issues/12017): Re-register finaliser only after calling user alarm in Gc.create_alarm + (Fabrice Buoro, report by Sam Goldman, review by Guillaume Munch-Maccagnoni) + + - [#11887](https://github.com/ocaml/ocaml/issues/11887), [#11893](https://github.com/ocaml/ocaml/issues/11893): Code duplication in pattern-matching compilation + (Vincent Laviron, report par Greta Yorsh, review by Luc Maranget and + Gabriel Scherer) + + - [#10664](https://github.com/ocaml/ocaml/issues/10664), [#11600](https://github.com/ocaml/ocaml/issues/11600): Unsoundness in the typing of polymorphic methods + involving polymorphic variants + (Jacques Garrigue, report by Mike Shulman, review by Gabriel Scherer) + + - [#11302](https://github.com/ocaml/ocaml/issues/11302), [#11412](https://github.com/ocaml/ocaml/issues/11412): `ocamlc` and `ocamlopt` should not remove generated files + when they are not regular files. + (Xavier Leroy, report by Thierry Martinez, review by + Anil Madhavapeddy, Nicolás Ojeda Bär, David Allsopp) + + - [#10348](https://github.com/ocaml/ocaml/issues/10348), [#10560](https://github.com/ocaml/ocaml/issues/10560), [#11561](https://github.com/ocaml/ocaml/issues/11561): Expand GADT equations lazily during unification to + avoid ambiguity + (Jacques Garrigue, review by Leo White) + + - [#11436](https://github.com/ocaml/ocaml/issues/11436): Fix wrong stack backtrace for out-of-bound exceptions raised + by leaf functions. + (Tom Kelly and Xavier Leroy, review by Mark Shinwell) + + - [#11450](https://github.com/ocaml/ocaml/issues/11450), [#12018](https://github.com/ocaml/ocaml/issues/12018): Fix erroneous functor error messages that were too eager to + cast `struct end` functor arguments as unit modules in `F(struct end)`. + (Florian Angetti, review by Gabriel Scherer) + + - [#11643](https://github.com/ocaml/ocaml/issues/11643): Add missing test declaration to float_compare test, so that it will + run. + (Stefan Muenzel, review by David Allsopp) + + - [#11630](https://github.com/ocaml/ocaml/issues/11630): Use correct location when reporting record labels with non-existent + paths. + (Nicolás Ojeda Bär, report by Jason Gross, review by Gabriel Scherer) + + - [#11727](https://github.com/ocaml/ocaml/issues/11727): Ensure push_defaults can push past module patterns, fixing an + currying optimisation accidentally disabled by [#10340](https://github.com/ocaml/ocaml/issues/10340). + (Stephen Dolan, review by Gabriel Scherer) + + - [#11771](https://github.com/ocaml/ocaml/issues/11771): Use a more relaxed mode for unification in Ctype.subst + (Leo White, review by Jacques Garrigue and Gabriel Scherer) + + - [#11803](https://github.com/ocaml/ocaml/issues/11803), [#11808](https://github.com/ocaml/ocaml/issues/11808): on x86, the destination of an integer comparison must be + a register, it cannot be a stack slot. + (Vincent Laviron, review by Xavier Leroy, report by + Emilio Jesús Gallego Arias) + + - [#11809](https://github.com/ocaml/ocaml/issues/11809): Protect Parmatch.pats_of_type from missing cmis + (Jacques Garrigue, review by Stephen Dolan and Gabriel Scherer) + + - [#11824](https://github.com/ocaml/ocaml/issues/11824): Fix a crash when calling `ocamlrun -b` + (Florian Angeletti, review by Sébastien Hinderer) + + - [#11815](https://github.com/ocaml/ocaml/issues/11815): Marshalling continuations raises invalid argument exception. + (Jérôme Vouillon, review by Nicolás Ojeda Bär, Stephen Dolan and + Hugo Heuzard) + + - [#11846](https://github.com/ocaml/ocaml/issues/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 + 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 + KC Sivaramakrishnan) + + - [#11850](https://github.com/ocaml/ocaml/issues/11850): When stopping before the `emit` phase (using `-stop-after`), an empty + temporary assembly file is no longer left in the file system. + (Nicolás Ojeda Bär, review by Gabriel Scherer and Xavier Leroy) + + - [#11866](https://github.com/ocaml/ocaml/issues/11866): Fix the result of `caml_read_directory()` on non-existent paths. + (Andrei Paskevich and Charlène Gros, review by David Allsopp and + Nicolás Ojeda Bär) + + - [#11879](https://github.com/ocaml/ocaml/issues/11879): Bugfix for Ctype.nondep_type + (Stephen Dolan, review by Gabriel Scherer) + + - [#12004](https://github.com/ocaml/ocaml/issues/12004): Don't ignore function attributes on lambdas with locally abstract + types. + (Chris Casinghino, review by Gabriel Scherer) + + - [#12037](https://github.com/ocaml/ocaml/issues/12037): Fix some data races by using volatile when necessary + (Fabrice Buoro and Olivier Nicole, review by Guillaume Munch-Maccagnoni, + Gabriel Scherer and Luc Maranget) + + - [#12046](https://github.com/ocaml/ocaml/issues/12046): Flush stderr when tracing the parser + (Hugo Heuzard, review by David Allsopp and Nicolás Ojeda Bär) + + - [#12061](https://github.com/ocaml/ocaml/issues/12061), [#12063](https://github.com/ocaml/ocaml/issues/12063): don't add inconsistent equalities when computing + high-level error messages for functor applications and inclusions. + (Florian Angeletti, review by Gabriel Scherer) + + - [#12075](https://github.com/ocaml/ocaml/issues/12075): auto-detect whether `ar` support @FILE arguments at + configure-time to avoid using this feature with toolchains + that do not support it (eg FreeBSD/Darwin). + (Nicolás Ojeda Bär, review by Xavier Leroy, David Allsop, Javier + Chávarri, Anil Madhavapeddy) + + - [#12103](https://github.com/ocaml/ocaml/issues/12103), 12104: fix a concurrency memory-safety bug in Buffer + (Gabriel Scherer, review by Florian Angeletti, report by Samuel Hym) + + - [#12112](https://github.com/ocaml/ocaml/issues/12112): Fix caml_callback{2,3}_exn when used with effect handlers. + (Lucas Pluvinage, review by Gabriel Scherer, David Allsopp and Xavier Leroy) + + - [#12134](https://github.com/ocaml/ocaml/issues/12134): Use ghost location for nodes created when handling defaults in + optional arguments. + (Paul-Elliot Anglès d'Auriac, review by Gabriel Scherer) + + - [#12153](https://github.com/ocaml/ocaml/issues/12153): Fix segfault in bytecode programs involving recursive value + definitions of values of size 0 + (Vincent Laviron, Xavier Leroy, Gabriel Scherer, + review by Xavier Leroy, report by Nick Roberts) + + - [#12162](https://github.com/ocaml/ocaml/issues/12162): Fix miscompilation on amd64 backends involving integer overflows + (Vincent Laviron and Greta Yorsh, review by Stefan Muenzel) + + - [#12170](https://github.com/ocaml/ocaml/issues/12170): fix pthread_geaffinity_np configure check for android + (David Allsopp, review by Sébastien Hinderer) + + - [#12178](https://github.com/ocaml/ocaml/issues/12178): Fix runtime events consumer poll function returning an invalid value + instead of an OCaml integer value. (Lucas Pluvinage) + + - [#12252](https://github.com/ocaml/ocaml/issues/12252): Fix shared library build error on RISC-V. + (Edwin Török, review by Nicolás Ojeda Bär and Xavier Leroy) + + - [#12255](https://github.com/ocaml/ocaml/issues/12255), [#12256](https://github.com/ocaml/ocaml/issues/12256): Handle large signal numbers correctly (Nick Barnes, + review by David Allsopp). + + - [#12277](https://github.com/ocaml/ocaml/issues/12277): ARM64, fix a potential assembler error for very large functions by + emitting stack reallocation code before the body of the function. + (Xavier Leroy, review by KC Sivaramakrishnan) + + - [#12253](https://github.com/ocaml/ocaml/issues/12253), [#12342](https://github.com/ocaml/ocaml/issues/12342): Fix infinite loop in signal handling. + (Guillaume Munch-Maccagnoni, report by Thomas Leonard, review by + KC Sivaramakrishnan and Sadiq Jaffer) + + - [#12445](https://github.com/ocaml/ocaml/issues/12445): missing GC root registrations in runtime/io.c + (Gabriel Scherer, review by Xavier Leroy and Jeremy Yallop) + + - [#12481](https://github.com/ocaml/ocaml/issues/12481), [#12505](https://github.com/ocaml/ocaml/issues/12505): Fix incorrect initialization of array expressions + `[|e1;...;eN|]` when `N` is large enough to require major heap allocation. + (Xavier Leroy, report by Andrey Popp, analysis by KC Sivaramakrishnan + and Vincent Laviron, review by Gabriel Scherer) + + - [#11150](https://github.com/ocaml/ocaml/issues/11150), [#11207](https://github.com/ocaml/ocaml/issues/11207), [#11936](https://github.com/ocaml/ocaml/issues/11936): Avoid recomputation in Typedecl.check_wellfounded + (Jacques Garrigue, report by Boris Yakobowski, review by Gabriel Scherer) + + - [#11186](https://github.com/ocaml/ocaml/issues/11186), [#11188](https://github.com/ocaml/ocaml/issues/11188): Fix composition of coercions with aliases + (Vincent Laviron, report and review by Leo White) + + - [#12486](https://github.com/ocaml/ocaml/issues/12486): Fix delivery of unhandled effect exceptions on s390x + (Miod Vallat, report by Jan Midtgaard, review by Vincent Laviron and Xavier + Leroy) + +--- + +We have the pleasure of celebrating the anniversary of Olympe de Gouges' +"Declaration of the Rights of Woman and of the Female Citizen" by announcing the +release of OCaml version 5.1.0. + +Some of the highlights in OCaml 5.1.0 are: + + - Many runtime performance regression and memory-leaks fixes + (dynlinking, weak array, weak hash sets, GC with idle domains, GC prefetching) + - Restored support for native code generation on RISC-V and s390x architectures + - Restored Cygwin port + - Reduced installation size (50% reduction) + - Compressed compilation artefacts (.cmi, .cmt, .cmti, .cmo, .cma files) + - 19 error message improvements + - 14 standard library functions made tail-recursive with Tail-Recursion-Modulo-Cons (TRMC), such as `List.append` and `List.map` + - 57 new standard library functions + - More examples in the standard library documentation + - 42 bug fixes + +OCaml 5.1.0 is still a relatively experimental release compared to the OCaml +4.14 branch. In particular: + + - The POWER port is being tested in the dev version of the compiler. + - The Windows MSVC port is still unavailable. + - Ephemeron performances need to be investigated. + - GC compaction is a work in progress. + - `statmemprof` is a work in progress. + - There are a number of known runtime concurrency bugs (that trigger under + rare circumstances). + +We are planning to address those regressions, hopefully in time for the OCaml 5.2.0 release for some of them. Meanwhile, the OCaml 4.14 branch will be maintained, and the next release on the OCaml 4.14 branch, OCaml 4.14.2, should follow this release in the upcoming months. + + +Please report any unexpected behaviours on the [OCaml issue tracker](https://github.com/ocaml/ocaml/issues) +and post any questions or comments you might have on our +[discussion forums](https://discuss.ocaml.org). + + + + +The full list of changes can be found in the changelog below. + +--- + +## Installation Instructions + +The base compiler can be installed as an opam switch with the following commands: +```bash +opam update +opam switch create 5.1.0 +``` + +The source code for the release candidate is also directly available on: + +* [GitHub](https://github.com/ocaml/ocaml/archive/5.1.0.tar.gz) +* [OCaml archives at Inria](https://caml.inria.fr/pub/distrib/ocaml-5.1/ocaml-5.1.0.tar.gz) + +### Fine-Tuned Compiler Configuration + +If you want to tweak the configuration of the compiler, you can switch to the option variant with: +```bash +opam update +opam switch create ocaml-variants.5.1.0+options +``` +where `` is a comma-separated list of `ocaml-option-*` packages. For instance, for a `flambda` and `no-flat-float-array` switch: +```bash +opam switch create 5.1.0+flambda+nffa ocaml-variants.5.0.0+options ocaml-option-flambda ocaml-option-no-flat-float-array +``` diff --git a/data/releases/5.0.0.md b/data/releases/5.0.0.md index f163479012..dd2f608c3c 100644 --- a/data/releases/5.0.0.md +++ b/data/releases/5.0.0.md @@ -2,7 +2,7 @@ kind: compiler version: 5.0.0 date: 2022-12-16 -is_latest: true +is_latest: false intro: | This page describes OCaml version **5.0.0**, released on 2022-12-16. Go [here](/releases) for a list of all releases. @@ -13,21 +13,21 @@ highlights: | with support for [shared memory parallelism](https://v2.ocaml.org/releases/5.0/manual/parallelism.html) and [effect handlers](https://v2.ocaml.org/releases/5.0/manual/effects.html). --- -## What's new +## What's New OCaml 5.0.0 introduces a completely new runtime system with support for [shared memory parallelism](https://v2.ocaml.org/releases/5.0/manual/parallelism.html) and [effect handlers](https://v2.ocaml.org/releases/5.0/manual/effects.html). -As a language, OCaml 5 is fully compatible with OCaml 4 down to the performance +As a language, OCaml 5 is fully compatible with OCaml 4, down to the performance characteristics of your programs. In other words, any code that works with OCaml 4 should work the same with OCaml 5. The currently known exceptions to this rule are: -- the removal of many long-deprecated functions and modules -- changes to the internal runtime API -- the performance of ephemerons is currently (and temporarily) strongly degraded. +- The removal of many long-deprecated functions and modules +- Changes to the internal runtime API +- The performance of ephemerons is currently (and temporarily) strongly degraded For a comprehensive list of changes and details on all new features, -bug fixes, optimizations, etc., please consult the +bug fixes, optimisations, etc., please consult the [changelog](#Changes). @@ -50,19 +50,19 @@ The source code for the release candidate is also directly available on: * [OCaml archives at Inria](https://caml.inria.fr/pub/distrib/ocaml-5.0/ocaml-5.0.0.tar.gz) -### Configuration options +### Configuration Options The configuration of the installed opam switch can be tuned with the following options: -- ocaml-option-afl: set OCaml to be compiled with afl-fuzz instrumentation -- ocaml-option-bytecode-only: compile OCaml without the native-code compiler -- ocaml-option-flambda: set OCaml to be compiled with flambda activated -- ocaml-option-musl: set OCaml to be compiled with musl-gcc -- ocaml-option-no-flat-float-array: set OCaml to be compiled with --disable-flat-float-array -- ocaml-option-static :set OCaml to be compiled with musl-gcc -static -- ocaml-option-address-sanitizer: set OCaml to be compiled with address sanitizer -- ocaml-option-leak-sanitizer: set OCaml to be compiled with leak sanitizer +- `ocaml-option-afl`: set OCaml to be compiled with `afl-fuzz` instrumentation +- `ocaml-option-bytecode-only`: compile OCaml without the native-code compiler +- `ocaml-option-flambda`: set OCaml to be compiled with `flambda` activated +- `ocaml-option-musl`: set OCaml to be compiled with `musl-gcc` +- `ocaml-option-no-flat-float-array`: set OCaml to be compiled with `--disable-flat-float-array` +- `ocaml-option-static`: set OCaml to be compiled with `musl-gcc -static` +- `ocaml-option-address-sanitizer`: set OCaml to be compiled with address sanitiser +- `ocaml-option-leak-sanitizer`: set OCaml to be compiled with leak sanitiser For instance, one can install a switch with both `flambda` and the naked-pointer checker enabled with @@ -78,17 +78,17 @@ opam switch create 5.0.0+flambda+nnpchecker ocaml-variants.5.0.0+options ocaml-o ``` -Source distribution +Source Distribution ------------------- - [Source tarball](https://github.com/ocaml/ocaml/archive/5.0.0.tar.gz) - (.tar.gz) for compilation under Unix (including Linux and MacOS X) - and Microsoft Windows (including Cygwin). + (.tar.gz) for compilation under Unix (including Linux and macOS X) + and Microsoft Windows (including Cygwin) - Also available in [.zip](https://github.com/ocaml/ocaml/archive/5.0.0.zip) - format. -- [OPAM](https://opam.ocaml.org/) is a source-based distribution of + format +- [Opam](https://opam.ocaml.org/) is a source-based distribution of OCaml and many companion libraries and tools. Compilation and installation are automated by powerful package managers. - The official development repo is hosted on @@ -110,26 +110,26 @@ targets traditionally associated with other languages: * [Js_of_ocaml](http://ocsigen.org/js_of_ocaml/) is a stable OCaml to JavaScript compiler. -User's manual +User Manual ------------- -The user's manual for OCaml can be: +The user manual for OCaml can be: -- [browsed +- [Browsed online](https://v2.ocaml.org/releases/5.0/manual/index.html), -- downloaded as a single +- Downloaded as a single [PDF](https://v2.ocaml.org/releases/5.0/ocaml-5.0-refman.pdf), or [plain text](https://v2.ocaml.org/releases/5.0/ocaml-5.0-refman.txt) - document, -- downloaded as a single + document +- Downloaded as a single [TAR](https://v2.ocaml.org/releases/5.0/ocaml-5.0-refman-html.tar.gz) or [ZIP](https://v2.ocaml.org/releases/5.0/ocaml-5.0-refman-html.zip) - archive of HTML files, -- downloaded as a single + archive of HTML files +- Downloaded as a single [tarball](https://v2.ocaml.org/releases/5.0/ocaml-5.0-refman.info.tar.gz) - of Emacs info files, + of Emacs info files ## Changes diff --git a/data/releases/5.1.0.md b/data/releases/5.1.0.md new file mode 100644 index 0000000000..9472457172 --- /dev/null +++ b/data/releases/5.1.0.md @@ -0,0 +1,1043 @@ +--- +kind: compiler +version: 5.1.0 +date: 2023-09-14 +is_latest: true +intro: | + This page describes OCaml version **5.1.0**, released on + 2023-09-14. Go [here](/releases) for a list of all releases. + + This release is available as an [opam](/p/ocaml/5.1.0) package. +highlights: | + + - Many runtime performance regression and memory-leaks fixes + (dynlinking, weak array, weak hash sets, GC with idle domains, GC prefetching) + - Restored support for native code generation on RISC-V and s390x architectures + - Restored Cygwin port + - Reduced installation size (50% reduction) + - Compressed compilation artefacts (.cmi, .cmt, .cmti, .cmo, .cma files) + - 19 error message improvements + - 14 standard library functions made tail-recursive with Tail-Recursion-Modulo-Cons (TRMC), such as `List.append` and `List.map` + - 57 new standard library functions + - More examples in the standard library documentation + - 42 bug fixes + +--- + +## What's New + +Some of the highlights in OCaml 5.1.0 are: + + - Many runtime performance regression and memory-leak fixes (dynlinking, weak array, weak hash sets, GC with idle domains, GC prefetching). + - Restored support for native code generation on RISC-V and s390x architectures. + - Restored Cygwin port. + - Reduced installation size (50% reduction) + - Compressed compilation artefacts (.cmi, .cmt, .cmti, .cmo, .cma files) + - 19 error message improvements + - 14 standard library functions made tail-recursive with Tail-Recursion-Modulo-Cons (TRMC), such as `List.append` and `List.map`. + - 57 new standard library functions + - More examples in the standard library documentation + - 42 bug fixes + +OCaml 5.1.0 is still a relatively experimental release compared to the OCaml +4.14 branch. In particular + + - The POWER port is being tested in the dev version of the compiler. + - The Windows MSVC port is still unavailable. + - Ephemeron performances need to be investigated. + - GC compaction is a work in progress. + - `statmemprof` is a work in progress. + - There are a number of known runtime concurrency bugs (that trigger under + rare circumstances). + +For a comprehensive list of changes and details on all new features, +bug fixes, optimizations, etc., please consult the +[changelog](#Changes). + +--- + +## Installation Instructions + +The base compiler can be installed as an opam switch with the following commands: +```bash +opam update +opam switch create 5.1.0 +``` + +The source code for the release candidate is also directly available on: + +* [GitHub](https://github.com/ocaml/ocaml/archive/5.1.0.tar.gz) +* [OCaml archives at Inria](https://caml.inria.fr/pub/distrib/ocaml-5.1/ocaml-5.1.0.tar.gz) + + +### Configuration Options + +The configuration of the installed opam switch can be tuned with the +following options: + +- `ocaml-option-afl`: set OCaml to be compiled with `afl-fuzz` instrumentation +- `ocaml-option-bytecode-only`: compile OCaml without the native-code compiler +- `ocaml-option-flambda`: set OCaml to be compiled with `flambda` activated +- `ocaml-option-musl`: set OCaml to be compiled with `musl-gcc` +- `ocaml-option-no-flat-float-array`: set OCaml to be compiled with `--disable-flat-float-array` +- `ocaml-option-static`: set OCaml to be compiled with `musl-gcc -static` +- `ocaml-option-address-sanitizer`: set OCaml to be compiled with address sanitiser +- `ocaml-option-leak-sanitizer`: set OCaml to be compiled with leak sanitiser +- `ocaml-option-fp`: set OCaml to be compiled with frame pointers + +For instance, one can install a switch with both `flambda` and the `--disable-flat-float-array` option with + + +``` +opam switch create 5.1.0+flambda+nffa ocaml-variants.5.1.0+options ocaml-option-flambda ocaml-option-no-flat-float-array +``` + + +Source Distribution +------------------- + +- [Source + tarball](https://github.com/ocaml/ocaml/archive/5.1.0.tar.gz) + (.tar.gz) for compilation under Unix (including Linux and macOS X) + and Microsoft Windows (including Cygwin) +- Also available in + [.zip](https://github.com/ocaml/ocaml/archive/5.1.0.zip) + format +- [Opam](https://opam.ocaml.org/) is a source-based distribution of + OCaml and many companion libraries and tools. Compilation and + installation are automated by powerful package managers. +- The official development repo is hosted on + [GitHub](https://github.com/ocaml/ocaml) + +The +[INSTALL](https://v2.ocaml.org/releases/5.1/notes/INSTALL.adoc) file +of the distribution provides detailed compilation and installation +instructions — see also the [Windows release +notes](https://v2.ocaml.org/releases/5.1/notes/README.win32.adoc) for +instructions on how to build under Windows. + +Alternative Compilers +--------------------- + +Additionally, the following projects allow you to compile OCaml code to +targets traditionally associated with other languages: + +* [Js_of_ocaml](http://ocsigen.org/js_of_ocaml/) is a stable OCaml + to JavaScript compiler. + +User Manual +------------- + +The user manual for OCaml can be: + +- [Browsed + online](https://v2.ocaml.org/releases/5.1/manual/index.html), +- Downloaded as a single + [PDF](https://v2.ocaml.org/releases/5.1/ocaml-5.1-refman.pdf), + or [plain + text](https://v2.ocaml.org/releases/5.1/ocaml-5.1-refman.txt) + document, +- Downloaded as a single + [TAR](https://v2.ocaml.org/releases/5.1/ocaml-5.1-refman-html.tar.gz) + or + [ZIP](https://v2.ocaml.org/releases/5.1/ocaml-5.1-refman-html.zip) + archive of HTML files, +- Downloaded as a single + [tarball](https://v2.ocaml.org/releases/5.1/ocaml-5.1-refman.info.tar.gz) + of Emacs info files, + + +## Changes + + +This is the +[changelog](https://v2.ocaml.org/releases/5.1/notes/Changes). +(Changes that can break existing programs are marked with a "breaking change" warning) + + +### Restored Backends + +- [#11418](https://github.com/ocaml/ocaml/issues/11418), [#11708](https://github.com/ocaml/ocaml/issues/11708): RISC-V multicore support. + (Nicolás Ojeda Bär, review by KC Sivaramakrishnan) + +- [#11712](https://github.com/ocaml/ocaml/issues/11712), [#12258](https://github.com/ocaml/ocaml/issues/12258), [#12261](https://github.com/ocaml/ocaml/issues/12261): s390x / IBM Z multicore support: + OCaml & C stack separation; dynamic stack size checks; fiber and + effects support. + (Aleksei Nikiforov, with help from Vincent Laviron and Xavier Leroy, + additional suggestions by Luc Maranget, + review by the same and KC Sivaramakrishnan) + +- [#11642](https://github.com/ocaml/ocaml/issues/11642): Restore Cygwin port. Add GC messages for address space reservations + when OCAMLRUNPARAM option v includes 0x1000. + (David Allsopp, review by Xavier Leroy, Guillaume Munch-Maccagnoni + and Gabriel Scherer) + +### Standard library: + +- [#12006](https://github.com/ocaml/ocaml/issues/12006), [#12064](https://github.com/ocaml/ocaml/issues/12064): Add `Marshal.Compression` flag to `Marshal.to_*` functions. + When this flag is explicitly set, marshaled data is compressed using ZSTD. + On some practical examples, the marshalled output became three times smaller + at no noticeable cost on the marshalling time. + (Xavier Leroy, review by Edwin Török and Gabriel Scherer, fix by Damien + Doligez) + +- [#11848](https://github.com/ocaml/ocaml/issues/11848): Add `List.find_mapi`, + `List.find_index: ('a -> bool) -> 'a list -> int option`, + `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) + +- [#11410](https://github.com/ocaml/ocaml/issues/11410): Add Set.to_list, Map.to_list, Map.of_list, + `Map.add_to_list: key -> 'a -> 'a list t -> 'a list t`. + (Daniel Bünzli, review by Nicolás Ojeda Bär and Gabriel Scherer) + +- [#11836](https://github.com/ocaml/ocaml/issues/11836), [#11837](https://github.com/ocaml/ocaml/issues/11837): Add `Array.map_inplace`, `Array.mapi_inplace`, + `Float.Array.mapi_inplace` and `Float.Array.mapi_inplace`. + (Léo Andrès, review by Gabriel Scherer, KC Sivaramakrishnan and + Nicolás Ojeda Bär) + +- [#10967](https://github.com/ocaml/ocaml/issues/10967): Add Filename.temp_dir. + (David Turner, review by Anil Madhavapeddy, Valentin Gatien-Baron, Nicolás + Ojeda Bär, Gabriel Scherer, and Daniel Bünzli) + +- [#11246](https://github.com/ocaml/ocaml/issues/11246): Add "hash" and "seeded_hash" functions to Bool, Int, Char, Float, + Int32, Int64, and Nativeint. + (Nicolás Ojeda Bär, review by Xavier Leroy and Gabriel Scherer) + +- [#11488](https://github.com/ocaml/ocaml/issues/11488): Add `Mutex.protect: Mutex.t -> (unit -> 'a) -> 'a` + for resource-safe critical sections protected by a mutex. + (Simon Cruanes, review by Gabriel Scherer, Xavier Leroy, + Guillaume Munch-Maccagnoni) + +- [#11581](https://github.com/ocaml/ocaml/issues/11581): Add type equality witness + `type (_, _) eq = Equal: ('a, 'a) eq` + in a new module Stdlib.Type. + (Nicolás Ojeda Bär, review by Daniel Bünzli, Jacques Garrigue, Florian + Angeletti, Alain Frisch, Gabriel Scherer, Jeremy Yallop and Xavier Leroy) + +- [#11843](https://github.com/ocaml/ocaml/issues/11843): Add `In_channel.input_lines` and `In_channel.fold_lines`. + (Xavier Leroy, review by Nicolás Ojeda Bär and Wiktor Kuchta). + +- [#11856](https://github.com/ocaml/ocaml/issues/11856), [#11859](https://github.com/ocaml/ocaml/issues/11859): Using TRMC, the following `Stdlib` functions are now + tail-recursive: + Stdlib.(@), List.append, + List.concat_map. + (Jeremy Yallop, review by Daniel Bünzli, Anil Madhavapeddy, Nicolás Ojeda Bär, + Gabriel Scherer, and Bannerets) + +- [#11362](https://github.com/ocaml/ocaml/issues/11362), [#11402](https://github.com/ocaml/ocaml/issues/11402): Using TRMC, the following `Stdlib` functions are now + tail-recursive: + List.map, List.mapi, List.map2, + List.filter, List.filteri, List.filter_map, + List.init, + List.of_seq. + (Nicolás Ojeda Bär, review by Xavier Leroy and Gabriel Scherer) + + +- [#11878](https://github.com/ocaml/ocaml/issues/11878), [#11965](https://github.com/ocaml/ocaml/issues/11965): Prevent seek_in from marking buffer data as valid after + closing the channel. This could lead to inputting uninitialised bytes. + (Samuel Hym, review by Xavier Leroy and Olivier Nicole) + +- [#11128](https://github.com/ocaml/ocaml/issues/11128): Add In_channel.isatty, Out_channel.isatty. + (Nicolás Ojeda Bär, review by Gabriel Scherer and Florian Angeletti) + +- [#10859](https://github.com/ocaml/ocaml/issues/10859): Add `Format.pp_print_iter` and `Format.pp_print_array`. + (Léo Andrès and Daniel Bünzli, review by David Allsopp and Hugo Heuzard) + +- [#10789](https://github.com/ocaml/ocaml/issues/10789): Add `Stack.drop` + (Léo Andrès, review by Gabriel Scherer) + +* (*breaking change*) [#10899](https://github.com/ocaml/ocaml/issues/10899): Change Stdlib.nan from signaling NaN to quiet NaN. + (Greta Yorsh, review by Xavier Leroy, Guillaume Melquiond and + Gabriel Scherer) + +- [#11026](https://github.com/ocaml/ocaml/issues/11026), [#11667](https://github.com/ocaml/ocaml/issues/11667), [#11858](https://github.com/ocaml/ocaml/issues/11858): Rename the type of the accumulator + of fold functions to 'acc: + fold_left : ('acc -> 'a -> 'acc) -> 'acc -> 'a list -> 'acc + fold_right : ('a -> 'acc -> 'acc) -> 'a list -> 'acc -> 'acc + fold_left_map : ('acc -> 'a -> 'acc * 'b) -> 'acc -> 'a list -> 'acc * 'b list + ... + (Valentin Gatien-Baron and Francois Berenger, + review by Gabriel Scherer and Nicolás Ojeda Bär) + +- [#11354](https://github.com/ocaml/ocaml/issues/11354): Hashtbl.find_all is now tail-recursive. + (Fermín Reig, review by Gabriel Scherer) + +- [#11500](https://github.com/ocaml/ocaml/issues/11500): Make Hashtbl.mem non-allocating. + (Simmo Saan, review by Nicolás Ojeda Bär) + +- [#11412](https://github.com/ocaml/ocaml/issues/11412): Add Sys.is_regular_file + (Xavier Leroy, review by Anil Madhavapeddy, Nicolás Ojeda Bär, David Allsopp) + +- [#11322](https://github.com/ocaml/ocaml/issues/11322), [#11329](https://github.com/ocaml/ocaml/issues/11329): serialization functions Random.State.{of,to}_binary_string + between Random.State.t and string + (Gabriel Scherer, report by Yotam Barnoy, + review by Daniel Bünzli, Damien Doligez, Hugo Heuzard and Xavier Leroy) + +- [#11830](https://github.com/ocaml/ocaml/issues/11830): Add Type.Id with + `val provably_equal : 'a Type.Id.t -> 'b Type.Id.t -> ('a, 'b) Type.eq option` + (Daniel Bünzli, review by Jeremy Yallop, Gabriel Scherer, Wiktor Kuchta, + Nicolás Ojeda Bär) + +- [#12184](https://github.com/ocaml/ocaml/issues/12184), [#12320](https://github.com/ocaml/ocaml/issues/12320): Sys.rename Windows fixes on directory corner cases. + (Jan Midtgaard, review by Anil Madhavapeddy) + +* (*breaking change*) [#11565](https://github.com/ocaml/ocaml/issues/11565): Enable -strict-formats by default. Some incorrect format + specifications (for `printf`) where silently ignored and now fail. + Those new failures occur at compile-time, except if you use advanced + format features like `%(...%)` that parse format strings dynamically. + Pass `-no-strict-formats` to revert to the previous lenient behavior. + (Nicolás Ojeda Bär, review by David Allsopp) + +### Installation Size + + Specific efforts have been made during this release to reduce the filesystem +size of installed artifacts of the compiler distribution. +The installation size of 5.1 is 272 MiB compared to 521 MiB for 5.0. +Some of those changes will benefit all OCaml packages. + +- ocaml/RFCs[#23](https://github.com/ocaml/ocaml/issues/23), [#12006](https://github.com/ocaml/ocaml/issues/12006): use compressed marshaled format from [#12006](https://github.com/ocaml/ocaml/issues/12006) for .cmi, + .cmt, .cmti files, and for debug info in .cmo and .cma files, resulting in + major reduction in size. + (Xavier Leroy, review by Edwin Török and Gabriel Scherer, + RFC by Simon Cruanes) + +- [#11981](https://github.com/ocaml/ocaml/issues/11981): Reduce size of OCaml installations by removing debugging information + from installed bytecode executables. It is no longer possible to + run `ocamldebug` over these installed bytecode executables, nor to get + exception backtraces for them. + (Xavier Leroy, review by David Allsopp, report by Fabrice Le Fessant) + +* (*breaking change*) [#11993](https://github.com/ocaml/ocaml/issues/11993): install only bytecode executables for the `ocamlmklib`, `ocamlcmt`, + `ocamlprof`, `ocamlcp`, `ocamloptp`, and `ocamlmktop` tools, but no + native-code executables. A tool like `ocamlmklib` for example is now + installed directly to `$BINDIR/ocamlmklib`; `ocamlmklib.byte` and + `ocamlmklib.opt` are no longer installed to `$BINDIR`. + (Xavier Leroy, review by Gabriel Scherer) + +### Runtime System: + +- [#11589](https://github.com/ocaml/ocaml/issues/11589), [#11903](https://github.com/ocaml/ocaml/issues/11903): Modify the GC pacing code to make sure the GC keeps + up with allocations in the presence of idle domains. + (Damien Doligez and Stephen Dolan, report by Florian Angeletti, + review by KC Sivaramakrishnan and Sadiq Jaffer) + +- [#11743](https://github.com/ocaml/ocaml/issues/11743): Speed up weak array operations + (KC Sivaramakrishnan, review by François Bobot and Sadiq Jaffer) + +- [#12131](https://github.com/ocaml/ocaml/issues/12131): Simplify implementation of weak hash sets, fixing a + performance regression. (Nick Barnes, review by François Bobot, + Alain Frisch and Damien Doligez). + +- [#11474](https://github.com/ocaml/ocaml/issues/11474), [#11998](https://github.com/ocaml/ocaml/issues/11998), [#12065](https://github.com/ocaml/ocaml/issues/12065): Add support for user-defined events in the runtime + event tracing system. + (Lucas Pluvinage, review by Sadiq Jaffer, Guillaume Munch-Maccagnoni, + Enguerrand Decorne, Gabriel Scherer and Anil Madhavapeddy) + +- [#11827](https://github.com/ocaml/ocaml/issues/11827), [#12249](https://github.com/ocaml/ocaml/issues/12249): Restore prefetching for GC marking + (Fabrice Buoro and Stephen Dolan, review by Gabriel Scherer and Sadiq Jaffer) + +- [#11935](https://github.com/ocaml/ocaml/issues/11935): Load frametables of dynlink'd modules in batch + (Stephen Dolan, review by David Allsopp and Guillaume Munch-Maccagnoni) + + +* (*breaking change*) [#11865](https://github.com/ocaml/ocaml/issues/11865), [#11868](https://github.com/ocaml/ocaml/issues/11868), [#11876](https://github.com/ocaml/ocaml/issues/11876): Clarify that the operations of a custom + block must never access the OCaml runtime. The previous + documentation only mentioned the main illicit usages. In particular, + since OCaml 5.0, it is no longer safe to call + `caml_remove_global_root` or `caml_remove_generational_global_root` + from within the C finaliser of a custom block, or within the + finalisation function passed to `caml_alloc_final`. As a workaround, + such a finalisation operation can be registered with `Gc.finalize` + instead, which guarantees to run the finaliser at a safe point. + (Report by Timothy Bourke, discussion by Yotam Barnoy, Timothy + Bourke, Sadiq Jaffer, Xavier Leroy, Guillaume Munch-Maccagnoni, and + Gabriel Scherer) + +- [#12130](https://github.com/ocaml/ocaml/issues/12130): Fix multicore crashes with weak hash sets. Fixes [#11934](https://github.com/ocaml/ocaml/issues/11934). + (Nick Barnes, review by François Bobot) + +- [#12099](https://github.com/ocaml/ocaml/issues/12099): Add `ocamlrund` option, `-events`, to produce a trace of + debug events during bytecode interpretation. Fixes [#12098](https://github.com/ocaml/ocaml/issues/12098). + (Richard L Ford, review by Gabriel Scherer) + +- [#12001](https://github.com/ocaml/ocaml/issues/12001): Fix book keeping for last finalisers during the minor cycle + (KC Sivaramakrishnan and Enguerrand Decorne, report by Guillaume Bury + and Vincent Laviron, review by Sadiq Jaffer and KC Sivaramakrishnan) + +- [#11919](https://github.com/ocaml/ocaml/issues/11919): New runtime events counters for major heap stats and minor heap + resizing. + (Sadiq Jaffer, review by Gabriel Scherer and David Allsopp) + +- [#11287](https://github.com/ocaml/ocaml/issues/11287), [#11872](https://github.com/ocaml/ocaml/issues/11872), [#11955](https://github.com/ocaml/ocaml/issues/11955): Clean up reserved header bits (once used for + Spacetime profiling). + (Nick Barnes, review by Gabriel Scherer and Damien Doligez) + +- [#11750](https://github.com/ocaml/ocaml/issues/11750): Decouple major slice from minor GC. + (KC Sivaramakrishnan, review by Sadiq Jaffer, Guillaume Munch-Maccagnoni and + Damien Doligez) + +- [#11796](https://github.com/ocaml/ocaml/issues/11796): protect lazy computation of code fragment digest by a mutex. + This makes the thread sanitiser happier and avoids duplicating + the hashing work. + (Gabriel Scherer, review by Xavier Leroy, report by Olivier Nicole) + +- [#11137](https://github.com/ocaml/ocaml/issues/11137): new `Unsafe_store_tag(val, new_tag)` macro to stop using + `Tag_val(val)` as lvalue. + (Gabriel Scherer, review by Xavier Leroy, Guillaume Munch-Maccagnoni + and Nicolás Ojeda Bär) + +- [#11880](https://github.com/ocaml/ocaml/issues/11880): Restore the correct sigmask in systhreads. + (Christiano Haesbaert, review by Guillaume Munch-Maccagnoni and + Sébastien Hinderer) + +- [#11881](https://github.com/ocaml/ocaml/issues/11881): Fix thread-unsafety of registration of operations for "custom" + values. + (Guillaume Munch-Maccagnoni, review by Gabriel Scherer and KC + Sivaramakrishnan) + +- [#11980](https://github.com/ocaml/ocaml/issues/11980): fix quadratic behavior in natdynlink by using a STW section + for frame-descriptor updates. + (Gabriel Scherer, review by Sadiq Jaffer, report by André Maroneze + for Frama-C and Guillaume Melquiond for Coq) + +- [#12121](https://github.com/ocaml/ocaml/issues/12121): unrooted implementations of `caml_callback*_exn` + (Gabriel Scherer, review by KC Sivaramakrishnan and Xavier Leroy) + +- [#3921](https://github.com/ocaml/ocaml/issues/3921), [#12039](https://github.com/ocaml/ocaml/issues/12039), [#12128](https://github.com/ocaml/ocaml/issues/12128): poll for signals in long-running polymorphic + comparisons. + (B. Szilvasy, Gabriel Scherer and Xavier Leroy, review by + Stefan Muenzel, Guillaume Munch-Maccagnoni and Damien Doligez) + +- [#12231](https://github.com/ocaml/ocaml/issues/12231): Support MinGW-w64 11.0 winpthreads library, where the macro + to set up to get flexdll working changed + (David Allsopp and Samuel Hym, light review by Xavier Leroy) + +### Language features: + +* (*breaking change*) [#11694](https://github.com/ocaml/ocaml/issues/11694): Add short syntax for generative functor types `() -> ...` + (Jeremy Yallop, review by Gabriel Scherer, Nicolás Ojeda Bär, + Jacques Garrigue) + + +* (*breaking change*) [#11457](https://github.com/ocaml/ocaml/issues/11457): Remove old polymorphic variant syntax. + With ``type t = [ `A | `B ]``, one could use the syntax `#t` in types, + where it means the same thing as `[< t]`, and in patterns, where it means + ``(`A | `B)``. The use of `#t` in types for polymorphic variants + was deprecated since 2001 and is now removed. The syntax remains available + in patterns, or for objects -- when `t` is a class type. + (Stefan Muenzel, review by Gabriel Scherer and Jacques Garrigue) + +* (*breaking change*) [#11984](https://github.com/ocaml/ocaml/issues/11984): Add dedicated syntax for generative functor application. + Previously, OCaml did not disinguish between `F ()` and + `F (struct end)`, even though the latter looks applicative. Instead, + the decision between generative and applicative functor application + was made based on the type of `F`. With this patch, we now distinguish + these two application forms; writing `F (struct end)` for a generative + functor leads to new warning 73. + (Frederic Bour and Richard Eisenberg, review by Florian Angeletti) + + +- [#9975](https://github.com/ocaml/ocaml/issues/9975), [#11365](https://github.com/ocaml/ocaml/issues/11365): Make empty types (`type t = |`) immediate. + (Antal Spector-Zabusky, review by Gabriel Scherer) + +### Type System: + +* (*Breaking change*) [#6941](https://github.com/ocaml/ocaml/issues/6941), [#11187](https://github.com/ocaml/ocaml/issues/11187): prohibit using classes through recursive modules + inheriting or including a class belonging to a mutually-recursive module + would previous behave incorrectly, which now results in a clean error. + (Leo White, review by Gabriel Scherer and Florian Angeletti) + +* (*Breaking change*) [#12189](https://github.com/ocaml/ocaml/issues/12189), [#12211](https://github.com/ocaml/ocaml/issues/12211): anonymous row variables in explicitly polymorphic type + annotation, e.g., `'a. [< X of 'a ] -> 'a`, are now implicitly + universally quantified (in other words, the example above is now read + as `'a 'r. ([< X of 'a ] as 'r) -> 'a`). + (Florian Angeletti and Gabriel Scherer, review by Jacques Garrigue) + +### Code Generation and Optimisations: + +- [#11967](https://github.com/ocaml/ocaml/issues/11967): Remove traces of `Obj.truncate`, which allows some mutable + loads to become immutable. + (Nick Barnes, review by Vincent Laviron and KC Sivaramakrishnan) + +- [#9945](https://github.com/ocaml/ocaml/issues/9945), [#10883](https://github.com/ocaml/ocaml/issues/10883): Turn Boolean-result float comparisons into primitive operations + Uses the architecture's elementary operations for float comparisons, + when available, rather than branching and then setting the return value. + (Stefan Muenzel, review by Stephen Dolan, Alain Frisch and Vincent Laviron) + +- [#8998](https://github.com/ocaml/ocaml/issues/8998), [#11321](https://github.com/ocaml/ocaml/issues/11321), [#11430](https://github.com/ocaml/ocaml/issues/11430): change mangling of OCaml long identifiers + from `camlModule__name_NNN` to `camlModule.name_NNN`. The previous + mangling schema, using `__`, was ambiguous. + (Xavier Leroy, report by sliquister and Michael Bacarella, + review by Gabriel Scherer) + +- [#10834](https://github.com/ocaml/ocaml/issues/10834): The `-safer-matching` option disables type-based optimisations of + pattern-matching compilation. This allows to produce a match failure if + a pattern-matching was wrongly assumed to be exhaustive. Since the + exhaustiveness check for GADTs has had bugs in the past, it may be + useful if you need extra security with GADTs. + (Jacques Garrigue, review by Gabriel Scherer) + +- [#11102](https://github.com/ocaml/ocaml/issues/11102): Speed up register allocation by permanently spilling registers + (Stephen Dolan, review by Xavier Leroy) + +- [#11383](https://github.com/ocaml/ocaml/issues/11383): Restrict the local function optimisation to forbid moving code + inside a sub-function + (Vincent Laviron, review by Gabriel Scherer) + +- [#11686](https://github.com/ocaml/ocaml/issues/11686): Better spilling heuristic for the Linear Scan allocator for more + efficient stack usage. + (Nicolás Ojeda Bär, Gabriel Scherer, Alain Frisch, review by Gabriel Scherer, + Alain Frisch and Nathanaëlle Courant) + +- [#11904](https://github.com/ocaml/ocaml/issues/11904): Remove arm, i386 native-code backends that were already + disabled at configuration time. + (Nicolás Ojeda Bär, review by Stephen Dolan, Anil Madhavapeddy, and Xavier + Leroy) + +### Other Libraries: + +- [#11374](https://github.com/ocaml/ocaml/issues/11374): Remove pointer cast to a type with stricter alignment requirements + in Windows implementation of `Unix.gettimeofday`. Windows implementations of + `caml_unix_map_file`, `caml_unix_lseek`, and `caml_unix_lseek_64` now release the + runtime lock. Windows implementation of `caml_unix_lockf` modernised and + simplified. Where possible, 64 bit integers are used instead of LARGE_INTEGER + structs. + (David Allsopp, review by Jonah Beckford and Xavier Leroy) + +- [#11475](https://github.com/ocaml/ocaml/issues/11475): Make Unix terminal interface bindings domain-safe + (Olivier Nicole and Xavier Leroy, review by Xavier Leroy) + +- [#11775](https://github.com/ocaml/ocaml/issues/11775): Unix.write on a non-blocking socket under Windows will return normally + if the write blocks after some data has already been written (as otherwise + there is no way of knowing how much data has been written before + blocking). The same behaviour was already present under Unix. + (Nicolás Ojeda Bär, review by David Allsopp) + +* (*Breaking change*) [#11991](https://github.com/ocaml/ocaml/issues/11991): Unix on Windows: map ERROR_TOO_MANY_LINKS to EMLINK. + (Nicolás Ojeda Bär) + +- [#12067](https://github.com/ocaml/ocaml/issues/12067): Document Windows specific meanings of `Unix.process_status` + type + (Samuel Hym, review by David Allsopp) + +- [#12072](https://github.com/ocaml/ocaml/issues/12072): Document and test that Sys.rename works over directories too + (Jan Midtgaard, review by Anil Madhavapeddy and Xavier Leroy) + +### Tools: + +- [#11889](https://github.com/ocaml/ocaml/issues/11889), [#11978](https://github.com/ocaml/ocaml/issues/11978): `ocamldoc`: handle injectivity annotations and wildcards in type + parameters. + (Florian Angeletti, report by Wiktor Kuchta, review by Jules Aguillon) + +- [#11787](https://github.com/ocaml/ocaml/issues/11787): Fix GDB scripts to work with OCaml 5's heap layout. (Nick + Barnes) + +- [#11772](https://github.com/ocaml/ocaml/issues/11772): fix `ocamlyacc`'s handling of raw string literals + (Demi Marie Obenour) + +- [#9290](https://github.com/ocaml/ocaml/issues/9290): Add a directive to switch off debugging in toplevel. + This allows to see optimised bytecode with `-dlambda`. + (Jacques Garrigue, review by Gabriel Scherer) + +- [#11166](https://github.com/ocaml/ocaml/issues/11166): `ocamllex`: the union of two character sets "cset1 | cset2" can now be + used in any context where a character set is expected. + (Nicolás Ojeda Bär, Martin Jambon, review by Sébastien Hinderer) + +- [#11718](https://github.com/ocaml/ocaml/issues/11718): `ocamlyacc`: OCaml-style comments are now supported, in addition to + the C-style comments already supported. The syntax is the same as that used + in OCaml code. + (Demi Marie Obenour, review by Damien Doligez) + +- [#11728](https://github.com/ocaml/ocaml/issues/11728): `ocamlyacc`: generate line directives for %type declarations + (Demi Marie Obenour, review by Damien Doligez) + +- [#11773](https://github.com/ocaml/ocaml/issues/11773): `ocamlyacc`: Do not allow quoted literals (such as 'a' or "bc") + in a token name or %type declaration. Previously such literals were + accepted by `ocamlyacc`, but produced malformed OCaml that was rejected + by the compiler. + (Demi Marie Obenour, review by Gabriel Scherer) + +- [#11774](https://github.com/ocaml/ocaml/issues/11774): `ocamlyacc`: fail if there is an I/O error + (Demi Marie Obenour, review by Gabriel Scherer) + +- [#11973](https://github.com/ocaml/ocaml/issues/11973): Add support for postfixed mingw host triplets + (Romain Beauxis) + +- [#12165](https://github.com/ocaml/ocaml/issues/12165): `ocamldoc`, use standard doctype to avoid quirk mode. + (Florian Angeletti, review by Gabriel Scherer) + +### Manual and Documentation: + +- [#11476](https://github.com/ocaml/ocaml/issues/11476): Add examples in documentation of Hashtbl, Queue, Atomic, Format + (Simon Cruanes, review by Yotam Barnoy, Gabriel Scherer, Daniel Bünzli, + Ulugbek Abdullaev, and Nicolás Ojeda Bär) + +- [#11883](https://github.com/ocaml/ocaml/issues/11883), [#11884](https://github.com/ocaml/ocaml/issues/11884): Update documentation for In_channel and Out_channel + with examples and sections to group related functions. + (Kiran Gopinathan, review by Daniel Bünzli and Xavier Leroy) + + +- [#12095](https://github.com/ocaml/ocaml/issues/12095), [#12097](https://github.com/ocaml/ocaml/issues/12097): Put the sample code of the user's manual and reference + documentation of the standard library under the CC0 1.0 Universal + (CC0 1.0) Public Domain Dedication license. + +- [#11892](https://github.com/ocaml/ocaml/issues/11892): Document the semantic differences of `Unix.exec*` between Unix and + Windows. + (Boris Yakobowski, review by Daniel Bünzli, Gabriel Scherer and Nicolás Ojeda + Bär) + +- [#9430](https://github.com/ocaml/ocaml/issues/9430), [#11291](https://github.com/ocaml/ocaml/issues/11291): Document the general desugaring rules for binding operators. + (Gabriel Scherer, review by Nicolás Ojeda Bär) + +- [#11481](https://github.com/ocaml/ocaml/issues/11481): Fix the type of `Unix.umask` to `Unix.file_perm -> Unix.file_perm` + (Favonia, review by Sébastien Hinderer) + +- [#11676](https://github.com/ocaml/ocaml/issues/11676): Fix missing since annotation in the `Sys` and `Format` modules + (Github user Bukolab99, review by Florian Angeletti) + +- [#12028](https://github.com/ocaml/ocaml/issues/12028): Update format documentation to make it clearer that + `pp_print_newline` flushes its newline + (Florian Angeletti, review by Gabriel Scherer) + +- [#12201](https://github.com/ocaml/ocaml/issues/12201): in the tutorial on modules, replace priority queue example by + a simpler example based on FIFO queues. + (Xavier Leroy, review by Anil Madhavapeddy and Nicolás Ojeda Bär). + +- [#12352](https://github.com/ocaml/ocaml/issues/12352): Fix a typo in the documentation of `Arg.write_arg` + (Christophe Raffalli, review by Florian Angeletti) + +### Compiler User-Interface and Warnings: + +- [#10647](https://github.com/ocaml/ocaml/issues/10647): Show hints for the "undefined global" error in the toplevel + (Wiktor Kuchta, review by Gabriel Scherer) + +- [#12116](https://github.com/ocaml/ocaml/issues/12116): Don't suggest to insert a semicolon when the type is not unit + (Jules Aguillon, review by Florian Angeletti) + +- [#11679](https://github.com/ocaml/ocaml/issues/11679): Improve the error message about too many arguments to a function + (Jules Aguillon, review by Gabriel Scherer and Florian Angeletti) + +- [#10009](https://github.com/ocaml/ocaml/issues/10009): Improve the error reported by mismatched `struct/sig` and `=/:` in module + and module type bindings + (Jules Aguillon, review by Gabriel Scherer) + +- [#11530](https://github.com/ocaml/ocaml/issues/11530): Include kinds in kind mismatch error message. + "Error: This variant or record definition does not match that of type M.t + The original is abstract, but this is a record". + (Leonhard Markert, review by Gabriel Scherer and Florian Angeletti) + +- [#11646](https://github.com/ocaml/ocaml/issues/11646): Add colors to error message hints. + (Christiana Anthony, review by Florian Angeletti) + +- [#11235](https://github.com/ocaml/ocaml/issues/11235), [#11864](https://github.com/ocaml/ocaml/issues/11864): usage warnings for constructors and fields can now be disabled + on field-by-field or constructor-by-constructor basis + (Florian Angeletti, review by Gabriel Scherer) + +- [#11888](https://github.com/ocaml/ocaml/issues/11888): Improve the error message when type variables cannot be deduced from + the type parameters: + Before: + "Error: In this definition, a type variable cannot be deduced + from the type parameters." + After: + "Error: In the GADT constructor + T : 'a -> 'a s t + the type variable 'a cannot be deduced from the type parameters." + (Stefan Muenzel, review by Florian Angeletti and Gabriel Scherer) + + +- [#10818](https://github.com/ocaml/ocaml/issues/10818): Preserve integer literal formatting in type hint. + (Leonhard Markert, review by Gabriel Scherer and Florian Angeletti) + +- [#11338](https://github.com/ocaml/ocaml/issues/11338): Turn some partial application warnings into hints. + (Leo White, review by Stephen Dolan) + +- [#10931](https://github.com/ocaml/ocaml/issues/10931): Improve warning 14 (illegal backslash) with a better explanation + of the causes and how to fix it. + (David Allsopp, Florian Angeletti, Lucas De Angelis, Gabriel Scherer, + review by Nicolás Ojeda Bär, Florian Angeletti, David Allsopp and + Gabriel Scherer) + +- [#10911](https://github.com/ocaml/ocaml/issues/10911): Improve the location reported by parenthesised assert expressions + (Fabian Hemmer, review by Gabriel Scherer) + +- [#1391](https://github.com/ocaml/ocaml/issues/1391), [#7645](https://github.com/ocaml/ocaml/issues/7645), [#3922](https://github.com/ocaml/ocaml/issues/3922): Add an early error when compiling different + modules with mismatching -for-pack + (Pierre Chambart and Vincent Laviron, review by Mark Shinwell) + +- [#11297](https://github.com/ocaml/ocaml/issues/11297): Report "unclosed" error when "done" is missing in a "do .. done" + construct. + (Nicolás Ojeda Bär, review by Gabriel Scherer) + +- [#11635](https://github.com/ocaml/ocaml/issues/11635), [#5461](https://github.com/ocaml/ocaml/issues/5461), [#10564](https://github.com/ocaml/ocaml/issues/10564): turn warning 31 (Module_linked_twice) into a hard error + for `ocamlc` — this was already an error with `ocamlopt`. + (Hugo Heuzard, review by Valentin Gatien-Baron and Gabriel Scherer) + +- [#11653](https://github.com/ocaml/ocaml/issues/11653): Add the `-no-absname` option to `ocamlc`, `ocamlopt`, and `ocamldep`. + (Abiola Abdulsalam, review by Sébastien Hinderer and Florian Angeletti) + +- [#11696](https://github.com/ocaml/ocaml/issues/11696): Add the `-no-g` option to `ocamlc` and `ocamlopt`. + (Abiola Abdulsalam, review by Sébastien Hinderer, Nicolás Ojeda Bär and + Florian Angeletti) + +- [#11722](https://github.com/ocaml/ocaml/issues/11722): clearer error messages on non-well-founded type definitions + (Gabriel Scherer, review by Jacques Garrigue) + +- [#11819](https://github.com/ocaml/ocaml/issues/11819): make the `native_compiler` and `native_dynlink` configuration + variables available through `ocamlc -config`. + (Sébastien Hinderer, review by Gabriel Scherer and David Allsopp) + +- [#8602](https://github.com/ocaml/ocaml/issues/8602), [#11863](https://github.com/ocaml/ocaml/issues/11863): Add `-stop-after` lambda flag option + (Douglas Smith and Dmitrii Kosarev, review by Gabriel Scherer) + +- [#11910](https://github.com/ocaml/ocaml/issues/11910): Simplify naming convention for shadowed or ephemeral identifiers in + error messages (eg: `Illegal shadowing of included type t/2 by t`) + (Florian Angeletti, review by Jules Aguillon) + +- [#12024](https://github.com/ocaml/ocaml/issues/12024): insert a blank line between separate compiler messages + (Gabriel Scherer, review by Florian Angeletti, report by David Wong) + +- [#12088](https://github.com/ocaml/ocaml/issues/12088), [#9265](https://github.com/ocaml/ocaml/issues/9265), [#11949](https://github.com/ocaml/ocaml/issues/11949): `ocamldebug`: fix confusing repeating behavior + on blank lines within source scripts + (Damien Doligez, review by Gabriel Scherer, report by Gaëtan Gilbert) + +- [#12107](https://github.com/ocaml/ocaml/issues/12107): use aliases to mark weak row variables: `_[< ... ]`, `< _..>`, `_#ct` + are now rendered as `[< ...] as '_weak1`, `< .. > as '_weak1`, + and `#ct as '_weak1`. + (Florian Angeletti, suggestion by Stefan Muenzel, review by Gabriel Scherer) + +- [#12051](https://github.com/ocaml/ocaml/issues/12051): Improve the error messages when type variables cannot be generalised + (Stefan Muenzel, review by Florian Angeletti) + +* (*breaking change*) [#12094](https://github.com/ocaml/ocaml/issues/12094): Trigger warning 5 (ignored-partial-application) when the scrutinee of + a pattern matching is of arrow type and all cases match wildcard or exception + patterns. + (Nicolás Ojeda Bär, review by Gabriel Scherer) + +### Internal/Compiler-Libs Changes: + +- [#11018](https://github.com/ocaml/ocaml/issues/11018), [#11869](https://github.com/ocaml/ocaml/issues/11869): Clean up Types.Variance, adding a description of + the lattice used and defining explicitly composition. + (Jacques Garrigue, review by Gabriel Scherer and Jeremy Yallop) + +- [#11536](https://github.com/ocaml/ocaml/issues/11536): Introduce wrapper functions for level management + ([Ctype.with_level], etc) and for type variable scoping + ([Typetexp.with_local_type_variable_scope]). + The older API ([Ctype.(begin_def,end_def)], [Typetexp.(narrow,widen)], etc.) + is now removed. + (Jacques Garrigue and Takafumi Saikawa, review by Gabriel Scherer) + +- [#11601](https://github.com/ocaml/ocaml/issues/11601), [#11612](https://github.com/ocaml/ocaml/issues/11612), [#11628](https://github.com/ocaml/ocaml/issues/11628), [#11613](https://github.com/ocaml/ocaml/issues/11613), [#11623](https://github.com/ocaml/ocaml/issues/11623), [#12120](https://github.com/ocaml/ocaml/issues/12120) : Clean up some + global state handling in emitcode, bytepackager, bytegen, + bytesections, spill. + (Hugo Heuzard, Stefan Muenzel, review by Vincent Laviron, Gabriel Scherer + and Nathanaëlle Courant) + +- [#12119](https://github.com/ocaml/ocaml/issues/12119), [#12188](https://github.com/ocaml/ocaml/issues/12188), [#12191](https://github.com/ocaml/ocaml/issues/12191): mirror type constraints on value binding in the + parsetree: + the constraint `typ` in `let pat : typ = exp` is now directly stored + in the value binding node in the parsetree. + (Florian Angeletti, review by Richard Eisenberg) + +- [#11912](https://github.com/ocaml/ocaml/issues/11912): Refactoring handling of scoped type variables + (Richard Eisenberg, review by Gabriel Scherer and Florian Angeletti) + + +- [#11691](https://github.com/ocaml/ocaml/issues/11691), [#11706](https://github.com/ocaml/ocaml/issues/11706): use __asm__ instead of asm for strict ISO C conformance + (Xavier Leroy, report by Gregg Reynolds , review by Sadiq Jaffer) + +- [#11764](https://github.com/ocaml/ocaml/issues/11764): add prototypes to old-style C function definitions and declarations + (Antonin Décimo, review by Xavier Leroy) + +- [#11693](https://github.com/ocaml/ocaml/issues/11693): Remove use of C99 Variable Length Arrays (VLAs) in the runtime. + (David Allsopp, review by Xavier Leroy, Guillaume Munch-Maccagnoni, + Stefan Muenzel and Gabriel Scherer) + +- [#12138](https://github.com/ocaml/ocaml/issues/12138): Generalise interface for BUILD_PATH_PREFIX_MAP mapping. + Absolute paths are now rewritten too. + (Richard L Ford, suggestions and review by Gabriel Scherer) + +- [#10512](https://github.com/ocaml/ocaml/issues/10512): explain the compilation strategy for switches on constructors + (Gabriel Scherer, review by Vincent Laviron) + +- [#11990](https://github.com/ocaml/ocaml/issues/11990): Improve comments and macros around frame descriptors. + (Nick Barnes, review by Gabriel Scherer) + +- [#11847](https://github.com/ocaml/ocaml/issues/11847), [#11849](https://github.com/ocaml/ocaml/issues/11849), [#11851](https://github.com/ocaml/ocaml/issues/11851), [#11898](https://github.com/ocaml/ocaml/issues/11898): small refactorings in the type checker + (Gabriel Scherer, review by Nicolás Ojeda Bär) + +- [#11027](https://github.com/ocaml/ocaml/issues/11027): Separate typing counter-examples from type_pat into retype_pat; + type_pat is no longer in CPS. + (Jacques Garrigue and Takafumi Saikawa, review by Gabriel Scherer) + +- [#11286](https://github.com/ocaml/ocaml/issues/11286), [#11515](https://github.com/ocaml/ocaml/issues/11515): disambiguate identifiers by using how recently they have + been bound in the current environment + (Florian Angeletti, review by Gabriel Scherer) + +- [#11364](https://github.com/ocaml/ocaml/issues/11364): Allow `make -C testsuite promote` to take `TEST` and `LIST` variables + (Antal Spector-Zabusky, review by Gabriel Scherer and David Allsopp) + +- [#11446](https://github.com/ocaml/ocaml/issues/11446): document switch compilation (lambda/switch.ml) + (Gabriel Scherer, review by Luc Maranget and Vincent Laviron) + +- [#11568](https://github.com/ocaml/ocaml/issues/11568): Encode inline record types in Path.t + (Leo White and Hyunggyu Jang, review by Gabriel Scherer) + +- [#11569](https://github.com/ocaml/ocaml/issues/11569): Remove hash type encoding + (Hyunggyu Jang, review by Gabriel Scherer and Florian Angeletti) + +- [#11627](https://github.com/ocaml/ocaml/issues/11627): use return values instead of globals for linear scan intervals + (Stefan Muenzel, review by Nicolás Ojeda Bär) + +- [#11634](https://github.com/ocaml/ocaml/issues/11634): Dll.open_dll now properly handles opening for execution while already + opened for checking + (Hugo Heuzard, review by Nicolás Ojeda Bär) + +* (*breaking change*) [#11745](https://github.com/ocaml/ocaml/issues/11745), [#12358](https://github.com/ocaml/ocaml/issues/12358): Debugger and toplevels: embed printer types rather than + reading their representations from `topdirs.cmi` at runtime. + This change also removes the `ocamlmktop` initialisation module introduced + in [#11382](https://github.com/ocaml/ocaml/issues/11382) which was no longer useful. + This change breaks toplevel scripts relying on the visibility of `Topdirs` + in the initial toplevel environment without loading `topfind`. + Since the opam default `.ocamlinit` file loads `topfind`, it is expected + that only scripts run with `ocaml -noinit` are affected. + For those scripts, accessing `Topdirs` now requires the `compiler-libs` + directory to be added to the toplevel search path with + ``` + #directory "+compiler-libs";; + ```` + as was already the case for the other modules in the toplevel interface + library. + (Sébastien Hinderer, review by Florian Angeletti, Nicolás Ojeda Bär and + Gabriel Scherer) + +- [#11615](https://github.com/ocaml/ocaml/issues/11615): remove global variables form asmcomp/linearize.ml + (Stefan Muenzel, review by Nicolás Ojeda Bär + +- [#10856](https://github.com/ocaml/ocaml/issues/10856): Add location, attribute(s) visitors to Tast_mapper/Tast_iterator + (Yan Dong, review by Nicolás Ojeda Bär and Gabriel Scherer) + +- [#11763](https://github.com/ocaml/ocaml/issues/11763), [#11759](https://github.com/ocaml/ocaml/issues/11759), [#11861](https://github.com/ocaml/ocaml/issues/11861): Enable stricter C compilation warnings, use + strict prototypes on primitives. + (Antonin Décimo, review by Xavier Leroy, David Allsopp, and Sébastien + Hinderer) + +- [#11933](https://github.com/ocaml/ocaml/issues/11933): Use the correct machtype when reading the code pointer from closures + (Nathanaëlle Courant, review by Gabriel Scherer and Vincent Laviron) + +- [#11972](https://github.com/ocaml/ocaml/issues/11972): refactor runtime/frame_descriptors.c + in preparation for quadratic-time fix + (Gabriel Scherer, review by Enguerrand Decorne) + +- [#11997](https://github.com/ocaml/ocaml/issues/11997): translate structured constants into their Obj.t representation + at compile time rather than link time. Changes the way `dumpobj` prints + these constants because their representation becomes untyped. + (Sébastien Hinderer, review by Xavier Leroy, Nicolás Ojeda Bär and + Hugo Heuzard) + +- [#12011](https://github.com/ocaml/ocaml/issues/12011): remove `Ctype.reified_var_counter` + (Takafumi Saikawa and Jacques Garrigue, review by Gabriel Scherer) + +- [#12012](https://github.com/ocaml/ocaml/issues/12012): move calls to `Typetexp.TyVarEnv.reset` inside `with_local_level`, etc. + (Jacques Garrigue and Takafumi Saikawa, review by Gabriel Scherer) + +- [#12034](https://github.com/ocaml/ocaml/issues/12034): a logarithmic algorithm to find the next free variable + (Gabriel Scherer, review by Stefan Muenzel) + +- [#12092](https://github.com/ocaml/ocaml/issues/12092): remove `Lev_module_definition` from lambda + (Nick Roberts, review by Gabriel Scherer) + +- [#12117](https://github.com/ocaml/ocaml/issues/12117): Remove `arity-interrupting` elaboration of module unpacks + (Nick Roberts, review by Richard Eisenberg and Jacques Garrigue) + +- [#12118](https://github.com/ocaml/ocaml/issues/12118): stop storing names of predefined exceptions in the + cu_required_globals field of compilation unit descriptors. + (Sébastien Hinderer, review by Vincent Laviron) + +- [#12125](https://github.com/ocaml/ocaml/issues/12125): Add `Misc.print_see_manual` and modify [@manual_ref] to accept + lists for simpler printing of manual references + (Stefan Muenzel, review by Florian Angeletti) + +### Build system: + +- [#11844](https://github.com/ocaml/ocaml/issues/11844): Reduce verbosity of `make` logs by printing program invocations in + shorthand (e.g., `OCAMLC foo.cmo`). Setting `V=1` recovers the old style (with + full command-lines). + (Xavier Leroy, Nicolás Ojeda Bär, review by Sébastien Hinderer) + + +- [#11590](https://github.com/ocaml/ocaml/issues/11590): Allow installing to a destination path containing spaces. + (Élie Brami, review by Sébastien Hinderer and David Allsopp) + +- [#11243](https://github.com/ocaml/ocaml/issues/11243), [#11248](https://github.com/ocaml/ocaml/issues/11248), [#11268](https://github.com/ocaml/ocaml/issues/11268), [#11420](https://github.com/ocaml/ocaml/issues/11420), [#11675](https://github.com/ocaml/ocaml/issues/11675): merge the sub-makefiles into + the root Makefile. + (Sébastien Hinderer, review by David Allsopp and Florian Angeletti) + +- [#11828](https://github.com/ocaml/ocaml/issues/11828): Compile otherlibs/ C stubs in two version for native and bytecode + (Olivier Nicole, review by Sébastien Hinderer and Xavier Leroy) + +- [#12265](https://github.com/ocaml/ocaml/issues/12265): Stop adding `-lexecinfo` to `cclibs` (leftover debugging code from the + Multicore project). Harden the feature probe for `-lm` in configure so `-lm` is + only added if strictly necessary. `configure.ac` now correctly propagates + library flags for the Windows ports, allowing Windows OCaml to be configured + with ZSTD support. + (David Allsopp, review by Sébastien Hinderer) + +- [#12372](https://github.com/ocaml/ocaml/issues/12372): Pass option `-no-execute-only` to the linker for OpenBSD >= 7.3 + so that code sections remain readable, as needed for closure marshaling. + (Xavier Leroy and Anil Madhavapeddy, review by Anil Madhavapeddy and + Sébastien Hinderer) + +### Bug fixes: + +- [#12062](https://github.com/ocaml/ocaml/issues/12062): fix runtime events consumer: when events are dropped they shouldn't be + parsed. (Lucas Pluvinage) + +- [#12132](https://github.com/ocaml/ocaml/issues/12132): Fix overcounting of minor collections in GC stats. + (Damien Doligez, review by Gabriel Scherer) + +- [#12017](https://github.com/ocaml/ocaml/issues/12017): Reregister finaliser only after calling user alarm in `Gc.create_alarm` + (Fabrice Buoro, report by Sam Goldman, review by Guillaume Munch-Maccagnoni) + +- [#11887](https://github.com/ocaml/ocaml/issues/11887), [#11893](https://github.com/ocaml/ocaml/issues/11893): Code duplication in pattern-matching compilation + (Vincent Laviron, report par Greta Yorsh, review by Luc Maranget and + Gabriel Scherer) + +- [#10664](https://github.com/ocaml/ocaml/issues/10664), [#11600](https://github.com/ocaml/ocaml/issues/11600): Unsoundness in the typing of polymorphic methods + involving polymorphic variants + (Jacques Garrigue, report by Mike Shulman, review by Gabriel Scherer) + +- [#11302](https://github.com/ocaml/ocaml/issues/11302), [#11412](https://github.com/ocaml/ocaml/issues/11412): `ocamlc` and `ocamlopt` should not remove generated files + when they are not regular files. + (Xavier Leroy, report by Thierry Martinez, review by + Anil Madhavapeddy, Nicolás Ojeda Bär, David Allsopp) + +- [#10348](https://github.com/ocaml/ocaml/issues/10348), [#10560](https://github.com/ocaml/ocaml/issues/10560), [#11561](https://github.com/ocaml/ocaml/issues/11561): Expand GADT equations lazily during unification to + avoid ambiguity + (Jacques Garrigue, review by Leo White) + +- [#11436](https://github.com/ocaml/ocaml/issues/11436): Fix wrong stack backtrace for out-of-bound exceptions raised + by leaf functions. + (Tom Kelly and Xavier Leroy, review by Mark Shinwell) + +- [#11450](https://github.com/ocaml/ocaml/issues/11450), [#12018](https://github.com/ocaml/ocaml/issues/12018): Fix erroneous functor error messages that were too eager to + cast `struct end` functor arguments as unit modules in `F(struct end)`. + (Florian Angetti, review by Gabriel Scherer) + +- [#11643](https://github.com/ocaml/ocaml/issues/11643): Add missing test declaration to `float_compare` test, so that it will + run. + (Stefan Muenzel, review by David Allsopp) + +- [#11630](https://github.com/ocaml/ocaml/issues/11630): Use correct location when reporting record labels with non-existent + paths. + (Nicolás Ojeda Bär, report by Jason Gross, review by Gabriel Scherer) + +- [#11727](https://github.com/ocaml/ocaml/issues/11727): Ensure push_defaults can push past module patterns, fixing an + currying optimisation accidentally disabled by [#10340](https://github.com/ocaml/ocaml/issues/10340). + (Stephen Dolan, review by Gabriel Scherer) + +- [#11732](https://github.com/ocaml/ocaml/issues/11732): Ensure that types from packed modules are always generalised + (Stephen Dolan and Leo White, review by Jacques Garrigue) + +- [#11771](https://github.com/ocaml/ocaml/issues/11771): Use a more relaxed mode for unification in `Ctype.subst` + (Leo White, review by Jacques Garrigue and Gabriel Scherer) + +- [#11776](https://github.com/ocaml/ocaml/issues/11776): Extend environment with functor parameters in `strengthen_lazy`. + (Chris Casinghino and Luke Maurer, review by Gabriel Scherer) + +- [#11803](https://github.com/ocaml/ocaml/issues/11803), [#11808](https://github.com/ocaml/ocaml/issues/11808): on x86, the destination of an integer comparison must be + a register; it cannot be a stack slot. + (Vincent Laviron, review by Xavier Leroy, report by + Emilio Jesús Gallego Arias) + +- [#11809](https://github.com/ocaml/ocaml/issues/11809): Protect `Parmatch.pats_of_type` from missing CMIs + (Jacques Garrigue, review by Stephen Dolan and Gabriel Scherer) + +- [#11824](https://github.com/ocaml/ocaml/issues/11824): Fix a crash when calling `ocamlrun -b` + (Florian Angeletti, review by Sébastien Hinderer) + +- [#11815](https://github.com/ocaml/ocaml/issues/11815): Marshalling continuations raises invalid argument exception. + (Jérôme Vouillon, review by Nicolás Ojeda Bär, Stephen Dolan and + Hugo Heuzard) + +- [#11846](https://github.com/ocaml/ocaml/issues/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 + 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 + KC Sivaramakrishnan) + +- [#11850](https://github.com/ocaml/ocaml/issues/11850): When stopping before the `emit` phase (using `-stop-after`), an empty + temporary assembly file is no longer left in the file system. + (Nicolás Ojeda Bär, review by Gabriel Scherer and Xavier Leroy) + +- [#11866](https://github.com/ocaml/ocaml/issues/11866): Fix the result of `caml_read_directory()` on non-existent paths. + (Andrei Paskevich and Charlène Gros, review by David Allsopp and + Nicolás Ojeda Bär) + +- [#11879](https://github.com/ocaml/ocaml/issues/11879): Bugfix for `Ctype.nondep_type` + (Stephen Dolan, review by Gabriel Scherer) + +- [#12004](https://github.com/ocaml/ocaml/issues/12004): Don't ignore function attributes on lambdas with locally abstract + types. + (Chris Casinghino, review by Gabriel Scherer) + +- [#12037](https://github.com/ocaml/ocaml/issues/12037): Fix some data races by using volatile when necessary + (Fabrice Buoro and Olivier Nicole, review by Guillaume Munch-Maccagnoni, + Gabriel Scherer and Luc Maranget) + +- [#12046](https://github.com/ocaml/ocaml/issues/12046): Flush `stderr` when tracing the parser + (Hugo Heuzard, review by David Allsopp and Nicolás Ojeda Bär) + +- [#12061](https://github.com/ocaml/ocaml/issues/12061), [#12063](https://github.com/ocaml/ocaml/issues/12063): don't add inconsistent equalities when computing + high-level error messages for functor applications and inclusions. + (Florian Angeletti, review by Gabriel Scherer) + +- [#12075](https://github.com/ocaml/ocaml/issues/12075): auto-detect whether `ar` support @FILE arguments at + configure-time to avoid using this feature with toolchains + that do not support it (eg FreeBSD/Darwin). + (Nicolás Ojeda Bär, review by Xavier Leroy, David Allsop, Javier + Chávarri, Anil Madhavapeddy) + +- [#12103](https://github.com/ocaml/ocaml/issues/12103), 12104: fix a concurrency memory-safety bug in Buffer + (Gabriel Scherer, review by Florian Angeletti, report by Samuel Hym) + +- [#12112](https://github.com/ocaml/ocaml/issues/12112): Fix `caml_callback{2,3}_exn` when used with effect handlers. + (Lucas Pluvinage, review by Gabriel Scherer, David Allsopp and Xavier Leroy) + +- [#12134](https://github.com/ocaml/ocaml/issues/12134): Use ghost location for nodes created when handling defaults in + optional arguments. + (Paul-Elliot Anglès d'Auriac, review by Gabriel Scherer) + +- [#12153](https://github.com/ocaml/ocaml/issues/12153): Fix segfault in bytecode programs involving recursive value + definitions of values of size 0 + (Vincent Laviron, Xavier Leroy, Gabriel Scherer, + review by Xavier Leroy, report by Nick Roberts) + +- [#12162](https://github.com/ocaml/ocaml/issues/12162): Fix miscompilation on AMD64 backends involving integer overflows + (Vincent Laviron and Greta Yorsh, review by Stefan Muenzel) + +- [#12170](https://github.com/ocaml/ocaml/issues/12170): fix `pthread_geaffinity_np` configure check for Android + (David Allsopp, review by Sébastien Hinderer) + +- [#12178](https://github.com/ocaml/ocaml/issues/12178): Fix runtime events consumer poll function returning an invalid value + instead of an OCaml integer value. (Lucas Pluvinage) + +- [#12252](https://github.com/ocaml/ocaml/issues/12252): Fix shared library build error on RISC-V. + (Edwin Török, review by Nicolás Ojeda Bär and Xavier Leroy) + +- [#12255](https://github.com/ocaml/ocaml/issues/12255), [#12256](https://github.com/ocaml/ocaml/issues/12256): Handle large signal numbers correctly (Nick Barnes, + review by David Allsopp). + +- [#12277](https://github.com/ocaml/ocaml/issues/12277): ARM64, fix a potential assembler error for very large functions by + emitting stack reallocation code before the body of the function. + (Xavier Leroy, review by KC Sivaramakrishnan) + +- [#12253](https://github.com/ocaml/ocaml/issues/12253), [#12342](https://github.com/ocaml/ocaml/issues/12342): Fix infinite loop in signal handling. + (Guillaume Munch-Maccagnoni, report by Thomas Leonard, review by + KC Sivaramakrishnan and Sadiq Jaffer) + +- [#12445](https://github.com/ocaml/ocaml/issues/12445): missing GC root registrations in `runtime/io.c` + (Gabriel Scherer, review by Xavier Leroy and Jeremy Yallop)