10811 lines
435 KiB
Plaintext
10811 lines
435 KiB
Plaintext
Working version
|
|
----------------
|
|
|
|
### Language features:
|
|
|
|
### Runtime system:
|
|
|
|
### Code generation and optimizations:
|
|
|
|
### Standard library:
|
|
|
|
### Other libraries:
|
|
|
|
### Tools:
|
|
|
|
### Manual and documentation:
|
|
|
|
### Compiler user-interface and warnings:
|
|
|
|
### Internal/compiler-libs changes:
|
|
|
|
- #9650: keep refactoring the pattern-matching compiler
|
|
(Gabriel Scherer, review by Thomas Refis)
|
|
|
|
### Build system:
|
|
|
|
### Bug fixes:
|
|
|
|
OCaml 4.12.0
|
|
------------
|
|
|
|
### Language features:
|
|
|
|
- #1655: pattern aliases do not ignore type constraints
|
|
(Thomas Refis, review by Jacques Garrigue and Gabriel Scherer)
|
|
|
|
* #9500, #9727: Injectivity annotations
|
|
One can now mark type parameters as injective, which is useful for
|
|
abstract types:
|
|
module Vec : sig type !'a t end = struct type 'a t = 'a array end
|
|
On non-abstract types, this can be used to check the injectivity of
|
|
parameters. Since all parameters of record and sum types are by definition
|
|
injective, this only makes sense for type abbreviations:
|
|
type !'a t = 'a list
|
|
(Jacques Garrigue, review by Jeremy Yallop and Leo White)
|
|
|
|
- #9429: Add unary operators containing `#` to the parser for use in ppx
|
|
rewriters
|
|
(Leo White, review by Damien Doligez)
|
|
|
|
### Supported platforms:
|
|
|
|
- #9699: add support for iOS and macOS on ARM 64 bits
|
|
(GitHub user @EduardoRFS, review by Xavier Leroy, Nicolás Ojeda Bär
|
|
and Anil Madhavapeddy, additional testing by Michael Schmidt)
|
|
|
|
### Type system:
|
|
|
|
* #9811: remove propagation from previous branches
|
|
Type information inferred from previous branches was propagated in
|
|
non-principal mode. Revert this for better compatibility with
|
|
-principal mode.
|
|
For the time being, infringing code should result in a principality warning.
|
|
(Jacques Garrigue, review by Thomas Refis and Gabriel Scherer)
|
|
|
|
### Runtime system:
|
|
|
|
- #2195: Improve error message in bytecode stack trace printing and load
|
|
debug information during bytecode startup if OCAMLRUNPARAM=b=2.
|
|
(David Allsopp, review by Gabriel Scherer and Xavier Leroy)
|
|
|
|
- #9756: garbage collector colors change
|
|
removes the gray color from the major gc
|
|
(Sadiq Jaffer and Stephen Dolan reviewed by Xavier Leroy,
|
|
KC Sivaramakrishnan, Damien Doligez and Jacques-Henri Jourdan)
|
|
|
|
- #1795, #9543: modernize signal handling on Linux i386, PowerPC, and s390x,
|
|
adding support for Musl ppc64le along the way.
|
|
(Xavier Leroy and Anil Madhavapeddy, review by Stephen Dolan)
|
|
|
|
- #9466: Memprof: optimize random samples generation.
|
|
(Jacques-Henri Jourdan review by Xavier Leroy and Stephen Dolan)
|
|
|
|
- #9628: Memprof: disable sampling when memprof is suspended.
|
|
(Jacques-Henri Jourdan review by Gabriel Scherer and Stephen Dolan)
|
|
|
|
- #9508: Remove support for FreeBSD prior to 4.0R, that required explicit
|
|
floating-point initialization to behave like IEEE standard
|
|
(Hannes Mehnert, review by David Allsopp)
|
|
|
|
* #9513: Selectively initialise blocks in `Obj.new_block`. Reject `Custom_tag`
|
|
objects and zero-length `String_tag` objects.
|
|
(KC Sivaramakrishnan, review by David Allsopp, Xavier Leroy, Mark Shinwell
|
|
and Leo White)
|
|
|
|
- #9564: Add a macro to construct out-of-heap block header.
|
|
(KC Sivaramakrishnan, review by Stephen Dolan, Gabriel Scherer,
|
|
and Xavier Leroy)
|
|
|
|
* #5154, #9569, #9734: Add `Val_none`, `Some_val`, `Is_none`, `Is_some`,
|
|
`caml_alloc_some`, and `Tag_some`. As these macros are sometimes defined by
|
|
authors of C bindings, this change may cause warnings/errors in case of
|
|
redefinition.
|
|
(Nicolás Ojeda Bär, review by Stephen Dolan, Gabriel Scherer, Mark Shinwell,
|
|
and Xavier Leroy)
|
|
|
|
- #8807, #9503: Use different symbols for do_local_roots on bytecode and native
|
|
(Stephen Dolan, review by David Allsopp and Xavier Leroy)
|
|
|
|
- #9619: Change representation of function closures so that code pointers
|
|
can be easily distinguished from environment variables
|
|
(Xavier Leroy, review by Mark Shinwell and Damien Doligez)
|
|
|
|
- #9634: Allow initial and repeated commas in `OCAMLRUNPARAM`.
|
|
(Nicolás Ojeda Bär, review by Gabriel Scherer)
|
|
|
|
- #9648, #9689: Update the generic hash function to take advantage
|
|
of the new representation for function closures
|
|
(Xavier Leroy, review by Stephen Dolan)
|
|
|
|
- #9649: Update the marshaler (output_value) to take advantage
|
|
of the new representation for function closures
|
|
(Xavier Leroy, review by Damien Doligez)
|
|
|
|
- #9654: More efficient management of code fragments.
|
|
(Xavier Leroy, review by Jacques-Henri Jourdan, Damien Doligez, and
|
|
Stephen Dolan)
|
|
|
|
- #9670: Report full major collections in Gc stats.
|
|
(Leo White, review by Gabriel Scherer)
|
|
|
|
- #9675: Remove the caml_static_{alloc,free,resize} primitives, now unused.
|
|
(Xavier Leroy, review by Gabriel Scherer)
|
|
|
|
- #9678: Reimplement `Obj.reachable_words` using a hash table to
|
|
detect sharing, instead of temporary in-place modifications. This
|
|
is a prerequisite for Multicore OCaml.
|
|
(Xavier Leroy, review by Jacques-Henri Jourdan and Sébastien Hinderer)
|
|
|
|
* #9697: Remove the Is_in_code_area macro and the registration of DLL code
|
|
areas in the page table, subsumed by the new code fragment management API
|
|
(Xavier Leroy, review by Jacques-Henri Jourdan)
|
|
|
|
- #9710: Drop "support" for an hypothetical JIT for OCaml bytecode
|
|
which has never existed.
|
|
(Jacques-Henri Jourdan, review by Xavier Leroy)
|
|
|
|
- #9728: Take advantage of the new closure representation to simplify the
|
|
compaction algorithm and remove its dependence on the page table
|
|
(Damien Doligez, review by Jacques-Henri Jourdan and Xavier Leroy)
|
|
|
|
- #9742, #9989: Ephemerons are now compatible with infix pointers occurring
|
|
when using mutually recursive functions.
|
|
(Jacques-Henri Jourdan, review by François Bobot)
|
|
|
|
* #1128, #7503, #9036, #9722: EINTR-based signal handling.
|
|
When a signal arrives, avoid running its OCaml handler in the middle
|
|
of a blocking section. Instead, allow control to return quickly to
|
|
a polling point where the signal handler can safely run, ensuring that
|
|
I/O locks are not held while it runs. A polling point was removed from
|
|
caml_leave_blocking_section, and one added to caml_raise.
|
|
(Stephen Dolan, review by Goswin von Brederlow, Xavier Leroy, Damien
|
|
Doligez, Anil Madhavapeddy, Guillaume Munch-Maccagnoni and Jacques-
|
|
Henri Jourdan)
|
|
|
|
- #9888, #9890: Fixes a bug in the `riscv` backend where register t0 was not
|
|
saved/restored when performing a GC. This could potentially lead to a
|
|
segfault.
|
|
(Nicolás Ojeda Bär, report by Xavier Leroy, review by Xavier Leroy)
|
|
|
|
- #9909: Remove caml_code_area_start and caml_code_area_end globals (no longer
|
|
needed as the pagetable heads towards retirement).
|
|
(David Allsopp, review by Xavier Leroy)
|
|
|
|
- #9949: Clarify documentation of GC message 0x1 and make sure it is
|
|
displayed every time a major cycle is forcibly finished.
|
|
(Damien Doligez, review by Xavier Leroy)
|
|
|
|
- #9951: Ensure that the mark stack push optimisation handles naked pointers
|
|
(KC Sivaramakrishnan, reported by Enguerrand Decorne, review by Gabriel
|
|
Scherer, and Xavier Leroy)
|
|
|
|
- #9534, #9947: Introduce a naked pointers checker mode to the runtime
|
|
(configure option --enable-naked-pointers-checker). Alarms are printed
|
|
when the garbage collector finds out-of-heap pointers that could
|
|
cause a crash in no-naked-pointers mode.
|
|
(Enguerrand Decorne, KC Sivaramakrishnan, Xavier Leroy, Stephen Dolan,
|
|
David Allsopp, Nicolás Ojeda Bär review by Xavier Leroy, Nicolás Ojeda Bär)
|
|
|
|
* #9674: Memprof: guarantee that an allocation callback is always run
|
|
in the same thread the allocation takes place
|
|
(Jacques-Henri Jourdan, review by Stephen Dolan)
|
|
|
|
### Code generation and optimizations:
|
|
|
|
- #9551: ocamlc no longer loads DLLs at link time to check that
|
|
external functions referenced from OCaml code are defined.
|
|
Instead, .so/.dll files are parsed directly by pure OCaml code.
|
|
(Nicolás Ojeda Bär, review by Daniel Bünzli, Gabriel Scherer,
|
|
Anil Madhavapeddy, and Xavier Leroy)
|
|
|
|
- #9620: Limit the number of parameters for an uncurried or untupled
|
|
function. Functions with more parameters than that are left
|
|
partially curried or tupled.
|
|
(Xavier Leroy, review by Mark Shinwell)
|
|
|
|
- #9752: Revised handling of calling conventions for external C functions.
|
|
Provide a more precise description of the types of unboxed arguments,
|
|
so that the ARM64 iOS/macOS calling conventions can be honored.
|
|
(Xavier Leroy, review by Mark Shinwell and Github user @EduardoRFS)
|
|
|
|
- #9838: Ensure that Cmm immediates are generated as Cconst_int where
|
|
possible, improving instruction selection.
|
|
(Stephen Dolan, review by Leo White and Xavier Leroy)
|
|
|
|
- #9864: Revised recognition of immediate arguments to integer operations.
|
|
Fixes several issues that could have led to producing assembly code
|
|
that is rejected by the assembler.
|
|
(Xavier Leroy, review by Stephen Dolan)
|
|
|
|
- #9969, #9981: Added mergeable flag to ELF sections containing mergeable
|
|
constants. Fixes compatibility with the integrated assembler in clang 11.0.0.
|
|
(Jacob Young, review by Nicolás Ojeda Bär)
|
|
|
|
### Standard library:
|
|
|
|
- #9865: add Format.pp_print_seq
|
|
(Raphaël Proust, review by Nicolás Ojeda Bär)
|
|
|
|
- #9781: add injectivity annotations to parameterized abstract types
|
|
(Jeremy Yallop, review by Nicolás Ojeda Bär)
|
|
|
|
* #9765: add init functions to Bigarray.
|
|
(Jeremy Yallop, review by Gabriel Scherer, Nicolás Ojeda Bär, and
|
|
Xavier Leroy)
|
|
|
|
* #9554: add primitive __FUNCTION__ that returns the name of the current method
|
|
or function, including any enclosing module or class.
|
|
(Nicolás Ojeda Bär, Stephen Dolan, review by Stephen Dolan)
|
|
|
|
- #9075: define to_rev_seq in Set and Map modules.
|
|
(Sébastien Briais, review by Gabriel Scherer and Nicolás Ojeda Bär)
|
|
|
|
- #9561: Unbox Unix.gettimeofday and Unix.time
|
|
(Stephen Dolan, review by David Allsopp)
|
|
|
|
- #9570: Provide an Atomic module with a trivial purely-sequential
|
|
implementation, to help write code that is compatible with Multicore
|
|
OCaml.
|
|
(Gabriel Scherer, review by Xavier Leroy)
|
|
|
|
- #9571: Make at_exit and Printexc.register_printer thread-safe.
|
|
(Guillaume Munch-Maccagnoni, review by Gabriel Scherer and Xavier Leroy)
|
|
|
|
- #9066: a new Either module with
|
|
type 'a Either.t = Left of 'a | Right of 'b
|
|
(Gabriel Scherer, review by Daniel Bünzli, Thomas Refis, Jeremy Yallop)
|
|
|
|
- #9066: List.partition_map :
|
|
('a -> ('b, 'c) Either.t) -> 'a list -> 'b list * 'c list
|
|
(Gabriel Scherer, review by Jeremy Yallop)
|
|
|
|
- #9587: Arg: new Rest_all spec to get all rest arguments in a list
|
|
(this is similar to Rest, but makes it possible to detect when there
|
|
are no arguments (an empty list) after the rest marker)
|
|
(Gabriel Scherer, review by Nicolás Ojeda Bär and David Allsopp)
|
|
|
|
- #9655: Obj: introduce type raw_data and functions raw_field, set_raw_field
|
|
to manipulate out-of-heap pointers in no-naked-pointer mode,
|
|
and more generally all other data that is not a well-formed OCaml value
|
|
(Xavier Leroy, review by Damien Doligez and Gabriel Scherer)
|
|
|
|
- #9533: Added String.starts_with and String.ends_with.
|
|
(Bernhard Schommer, review by Daniel Bünzli, Gabriel Scherer and
|
|
Alain Frisch)
|
|
|
|
- #9663: Extend Printexc API for raw backtrace entries.
|
|
(Stephen Dolan, review by Nicolás Ojeda Bär and Gabriel Scherer)
|
|
|
|
* #9668: List.equal, List.compare
|
|
(This could break code using "open List" by shadowing
|
|
Stdlib.{equal,compare}.)
|
|
(Gabriel Scherer, review by Nicolás Ojeda Bär, Daniel Bünzli and Alain Frisch)
|
|
|
|
- #9763: Add function Hashtbl.rebuild to convert from old hash table
|
|
formats (that may have been saved to persistent storage) to the
|
|
current hash table format. Remove leftover support for the hash
|
|
table format and generic hash function that were in use before OCaml 4.00.
|
|
(Xavier Leroy, review by Nicolás Ojeda Bär)
|
|
|
|
- #9797: Add Sys.mkdir and Sys.rmdir.
|
|
(David Allsopp, review by Nicolás Ojeda Bär, Sébastien Hinderer and
|
|
Xavier Leroy)
|
|
|
|
### Other libraries:
|
|
|
|
- #8796: On Windows, make Unix.utimes use FILE_FLAG_BACKUP_SEMANTICS flag
|
|
to allow it to work with directories.
|
|
(Daniil Baturin, review by Damien Doligez)
|
|
|
|
* #9206, #9419: update documentation of the threads library;
|
|
deprecate Thread.kill, Thread.wait_read, Thread.wait_write,
|
|
and the whole ThreadUnix module.
|
|
(Xavier Leroy, review by Florian Angeletti, Guillaume Munch-Maccagnoni,
|
|
and Gabriel Scherer)
|
|
|
|
- #9573: reimplement Unix.create_process and related functions without
|
|
Unix.fork, for better efficiency and compatibility with threads.
|
|
(Xavier Leroy, review by Gabriel Scherer and Anil Madhavapeddy)
|
|
|
|
- #9575: Add Unix.is_inet6_addr
|
|
(Nicolás Ojeda Bär, review by Xavier Leroy)
|
|
|
|
- #9593: Use new flag for non-elevated symbolic links and test for Developer
|
|
Mode on Windows
|
|
(Manuel Hornung, review by David Allsopp and Nicolás Ojeda Bär)
|
|
|
|
* #9601: Return EPERM for EUNKNOWN -1314 in win32unix (principally affects
|
|
error handling when Unix.symlink is unavailable)
|
|
(David Allsopp, review by Xavier Leroy)
|
|
|
|
- #9338, #9790: Dynlink: make sure *_units () functions report accurate
|
|
information before the first load.
|
|
(Daniel Bünzli, review by Xavier Leroy and Nicolás Ojeda Bär)
|
|
|
|
* #9757, #9846: check proper ownership when operating over mutexes.
|
|
Now, unlocking a mutex held by another thread or not locked at all
|
|
reliably raises a Sys_error exception. Before, it was undefined
|
|
behavior, but the documentation did not say so.
|
|
Likewise, locking a mutex already locked by the current thread
|
|
reliably raises a Sys_error exception. Before, it could
|
|
deadlock or succeed (and do recursive locking), depending on the OS.
|
|
(Xavier Leroy, report by Guillaume Munch-Maccagnoni, review by
|
|
Guillaume Munch-Maccagnoni, David Allsopp, and Stephen Dolan)
|
|
|
|
- #9802: Ensure signals are handled before Unix.kill returns
|
|
(Stephen Dolan, review by Jacques-Henri Jourdan)
|
|
|
|
- #9869: Add Unix.SO_REUSEPORT
|
|
(Yishuai Li, review by Xavier Leroy)
|
|
|
|
- #9906, #9914: Add Unix._exit as a way to exit the process immediately,
|
|
skipping any finalization action
|
|
(Ivan Gotovchits and Xavier Leroy, review by Sébastien Hinderer and
|
|
David Allsopp)
|
|
|
|
- #9930: new module Semaphore in the thread library, implementing
|
|
counting semaphores and binary semaphores
|
|
(Xavier Leroy, review by Daniel Bünzli and Damien Doligez,
|
|
additional suggestions by Stephen Dolan and Craig Ferguson)
|
|
|
|
- #9958: Raise exception in case of error in Unix.setsid.
|
|
(Nicolás Ojeda Bär, review by Stephen Dolan)
|
|
|
|
- #9971, #9973: Make sure the process can terminate when the last thread
|
|
calls Thread.exit.
|
|
(Xavier Leroy, report by Jacques-Henri Jourdan, review by David Allsopp
|
|
and Jacques-Henri Jourdan).
|
|
|
|
### Tools:
|
|
|
|
- #9551: ocamlobjinfo is now able to display information on .cmxs shared
|
|
libraries natively; it no longer requires libbfd to do so
|
|
(Nicolás Ojeda Bär, review by Daniel Bünzli, Gabriel Scherer,
|
|
Anil Madhavapeddy, and Xavier Leroy)
|
|
|
|
- #9606, #9635, #9637: fix performance regression in the debugger
|
|
(behaviors quadratic in the size of the debugged program)
|
|
(Xavier Leroy, report by Jacques Garrigue and Virgile Prevosto,
|
|
review by David Allsopp and Jacques-Henri Jourdan)
|
|
|
|
* #9299, #9795: ocamldep: do not process files during cli parsing. Fixes
|
|
various broken cli behaviours.
|
|
(Daniel Bünzli, review by Nicolás Ojeda Bär)
|
|
|
|
### Debugging and profiling:
|
|
|
|
- #9948: Remove Spacetime.
|
|
(Nicolás Ojeda Bär, review by Stephen Dolan and Xavier Leroy)
|
|
|
|
### Manual and documentation:
|
|
|
|
- #9468: HACKING.adoc: using dune to get merlin's support
|
|
(Thomas Refis, review by Gabriel Scherer)
|
|
|
|
- #9745: Manual: Standard Library labeled and unlabeled documentation unified
|
|
(John Whitington, review by Nicolás Ojeda Bär, David Allsopp,
|
|
Thomas Refis, and Florian Angeletti)
|
|
|
|
### Compiler user-interface and warnings:
|
|
|
|
- #1931: rely on levels to enforce principality in patterns
|
|
(Thomas Refis and Leo White, review by Jacques Garrigue)
|
|
|
|
* #9011: Do not create .a/.lib files when creating a .cmxa with no modules.
|
|
macOS ar doesn't support creating empty .a files (#1094) and MSVC doesn't
|
|
permit .lib files to contain no objects. When linking with a .cmxa containing
|
|
no modules, it is now not an error for there to be no .a/.lib file.
|
|
(David Allsopp, review by Xavier Leroy)
|
|
|
|
- #9560: Report partial application warnings on type errors in applications.
|
|
(Stephen Dolan, report and testcase by whitequark, review by Gabriel Scherer
|
|
and Thomas Refis)
|
|
|
|
- #9583: when bytecode linking fails due to an unavailable module, the module
|
|
that requires it is now included in the error message.
|
|
(Nicolás Ojeda Bär, review by Vincent Laviron)
|
|
|
|
- #9615: Attach package type attributes to core_type.
|
|
When parsing constraints on a first class module, attributes found after the
|
|
module type were parsed but ignored. Now they are attached to the
|
|
corresponding core_type.
|
|
(Etienne Millon, review by Thomas Refis)
|
|
|
|
- #6633, #9673: Add hint when a module is used instead of a module type or
|
|
when a module type is used instead of a module or when a class type is used
|
|
instead of a class.
|
|
(Xavier Van de Woestyne, report by whitequark, review by Florian Angeletti
|
|
and Gabriel Scherer)
|
|
|
|
- #9754: allow [@tailcall true] (equivalent to [@tailcall]) and
|
|
[@tailcall false] (warns if on a tailcall)
|
|
(Gabriel Scherer, review by Nicolás Ojeda Bär)
|
|
|
|
- #9657: Warnings can now be referred to by their mnemonic name. The names are
|
|
displayed using `-warn-help` and can be utilized anywhere where a warning list
|
|
specification is expected, e.g. `[@@@ocaml.warning ...]`.
|
|
(Nicolás Ojeda Bär, review by Gabriel Scherer, Florian Angeletti and Leo
|
|
White)
|
|
|
|
- #9751: Add warning 68. Pattern-matching depending on mutable state
|
|
prevents the remaining arguments from being uncurried.
|
|
(Hugo Heuzard, review by Leo White)
|
|
|
|
- #9783: Widen warning 16 to more cases.
|
|
(Leo White, review by Florian Angeletti)
|
|
|
|
### Internal/compiler-libs changes:
|
|
|
|
- #8987: Make some locations more accurate
|
|
(Thomas Refis, review by Gabriel Scherer)
|
|
|
|
- #9216: add Lambda.duplicate which refreshes bound identifiers
|
|
(Gabriel Scherer, review by Pierre Chambart and Vincent Laviron)
|
|
|
|
- #9376: Remove spurious Ptop_defs from #use
|
|
(Leo White, review by Damien Doligez)
|
|
|
|
- #9464, #9493, #9520, #9563, #9599, #9608, #9647: refactor
|
|
the pattern-matching compiler
|
|
(Thomas Refis and Gabriel Scherer, review by Florian Angeletti)
|
|
|
|
- #9604: refactoring of the ocamltest codebase.
|
|
(Nicolás Ojeda Bär, review by Gabriel Scherer and Sébastien Hinderer)
|
|
|
|
- #9498, #9511: make the pattern-matching analyzer more robust to
|
|
or-pattern explosion, by stopping after the first counter-example to
|
|
exhaustivity
|
|
(Gabriel Scherer, review by Luc Maranget, Thomas Refis and Florian Angeletti,
|
|
report by Alex Fedoseev through Hongbo Zhang)
|
|
|
|
- #9514: optimize pattern-matching exhaustivity analysis in the single-row case
|
|
(Gabriel Scherer, review by Stephen DOlan)
|
|
|
|
- #9442: refactor the implementation of the [@tailcall] attribute
|
|
to allow for a structured attribute payload
|
|
(Gabriel Scherer, review by Vladimir Keleshev and Nicolás Ojeda Bär)
|
|
|
|
- #9684: document in address_class.h the runtime value model in
|
|
naked-pointers and no-naked-pointers mode
|
|
(Xavier Leroy and Gabriel Scherer)
|
|
|
|
- #9696: ocamltest now shows its log when a test fails. In addition, the log
|
|
contains the output of executed programs.
|
|
(Nicolás Ojeda Bär, review by David Allsopp, Sébastien Hinderer and Gabriel
|
|
Scherer)
|
|
|
|
- #9688: Expose the main entrypoint in compilerlibs
|
|
(Stephen Dolan, review by Nicolás Ojeda Bär, Greta Yorsh and David Allsopp)
|
|
|
|
- #9715: recheck scope escapes after normalising paths
|
|
(Matthew Ryan, review by Gabriel Scherer and Thomas Refis)
|
|
|
|
- #9778: Fix printing for bindings where polymorphic type annotations and
|
|
attributes are present.
|
|
(Matthew Ryan, review by Nicolás Ojeda Bär)
|
|
|
|
- #9797, #9849: Eliminate the routine use of external commands in ocamltest.
|
|
ocamltest no longer calls the mkdir, rm and ln external commands (at present,
|
|
the only external command ocamltest uses is diff).
|
|
(David Allsopp, review by Nicolás Ojeda Bär, Sébastien Hinderer and
|
|
Xavier Leroy)
|
|
|
|
- #9801: Don't ignore EOL-at-EOF differences in ocamltest.
|
|
(David Allsopp, review by Damien Doligez, much input and thought from
|
|
Daniel Bünzli, Damien Doligez, Sébastien Hinderer, and Xavier Leroy)
|
|
|
|
- #9889: more caching when printing types with -short-path.
|
|
(Florian Angeletti, review by Gabriel Scherer)
|
|
|
|
- #9591: fix pprint of polyvariants that start with a core_type, closed,
|
|
not low (Chet Murthy, review by Florian Angeletti)
|
|
|
|
- #9590: fix pprint of extension constructors (and exceptions) that rebind
|
|
(Chet Murthy, review by octachron@)
|
|
|
|
- #8939: Command-line option to save Linear IR before emit.
|
|
(Greta Yorsh, review by Mark Shinwell, Sébastien Hinderer and Frédéric Bour)
|
|
|
|
- #9003: Start compilation from Emit when the input file is in Linear IR format.
|
|
(Greta Yorsh, review by Jérémie Dimino, Gabriel Scherer and Frédéric Bour)
|
|
|
|
- #9963: Centralized tracking of frontend's global state
|
|
(Frédéric Bour and Thomas Refis, review by Gabriel Scherer)
|
|
|
|
- #9631: Named text sections for caml_system__code_begin/end symbols
|
|
(Greta Yorsh, review by Frédéric Bour)
|
|
|
|
### Build system:
|
|
|
|
- #7121, #9558: Always the autoconf-discovered ld in PACKLD. For
|
|
cross-compilation, this means the triplet-prefixed version will always be
|
|
used.
|
|
(David Allsopp, report by Adrian Nader, review by Sébastien Hinderer)
|
|
|
|
- #9332, #9518, #9529: Cease storing C dependencies in the codebase. C
|
|
dependencies are generated on-the-fly in development mode. For incremental
|
|
compilation, the MSVC ports require GCC to be present.
|
|
(David Allsopp, review by Sébastien Hinderer, YAML-fu by Stephen Dolan)
|
|
|
|
- #9527: stop including configuration when running 'clean' rules
|
|
to avoid C dependency recomputation.
|
|
(Gabriel Scherer, review by David Allsopp)
|
|
|
|
- #9804: Build C stubs of libraries in otherlibs/ with debug info.
|
|
(Stephen Dolan, review by Sébastien Hinderer and David Allsopp)
|
|
|
|
- #9824, #9837: Honour the CFLAGS and CPPFLAGS variables.
|
|
(Sébastien Hinderer, review by David Allsopp)
|
|
|
|
- #9895, #9523: Avoid conflict with C++20 by not installing VERSION to the OCaml
|
|
Standard Library directory.
|
|
(Bernhard Schommer, review by David Allsopp)
|
|
|
|
### Bug fixes:
|
|
|
|
- #7538, #9669: Check for misplaced attributes on module aliases
|
|
(Leo White, report by Thomas Leonard, review by Florian Angeletti)
|
|
|
|
- #7902, #9556: Type-checker infers recursive type, even though -rectypes is
|
|
off.
|
|
(Jacques Garrigue, report by Francois Pottier, review by Leo White)
|
|
|
|
- #8746: Hashtbl: Restore ongoing traversal status after filter_map_inplace
|
|
(Mehdi Bouaziz, review by Alain Frisch)
|
|
|
|
- #8747, #9709: incorrect principality warning on functional updates of records
|
|
(Jacques Garrigue, report and review by Thomas Refis)
|
|
|
|
- #9421, #9427: fix printing of (::) in ocamldoc
|
|
(Florian Angeletti, report by Yawar Amin, review by Damien Doligez)
|
|
|
|
- #9440: for a type extension constructor with parameterised arguments,
|
|
REPL displayed <poly> for each as opposed to the concrete values used.
|
|
(Christian Quinn, review by Gabriel Scherer)
|
|
|
|
- #9433: Fix package constraints for module aliases
|
|
(Leo White, review by Jacques Garrigue)
|
|
|
|
- #9469: Better backtraces for lazy values
|
|
(Leo White, review by Nicolás Ojeda Bär)
|
|
|
|
- #9521, #9522: correctly fail when comparing functions
|
|
with Closure and Infix tags.
|
|
(Gabriel Scherer and Jeremy Yallop and Xavier Leroy,
|
|
report by Twitter user @st_toHKR through Jun Furuse)
|
|
|
|
- #9611: maintain order of load path entries in various situations: when passing
|
|
them to system linker, ppx contexts, etc.
|
|
(Nicolás Ojeda Bär, review by Jérémie Dimino and Gabriel Scherer)
|
|
|
|
- #9633: ocamltest: fix a bug when certain variables set in test scripts would
|
|
be ignored (eg `ocamlrunparam`).
|
|
(Nicolás Ojeda Bär, review by Sébastien Hinderer)
|
|
|
|
- #9681, #9690, #9693: small runtime changes
|
|
for the new closure representation (#9619)
|
|
(Xavier Leroy, Sadiq Jaffer, Gabriel Scherer,
|
|
review by Xavier Leroy and Jacques-Henri Jourdan)
|
|
|
|
- #9759, #9767: Spurious GADT ambiguity without -principal
|
|
(Jacques Garrigue, report by Thomas Refis,
|
|
review by Thomas Refis and Gabriel Scherer)
|
|
|
|
- #9799, #9803: pat_env points to the correct environment
|
|
(Thomas Refis, report by Alex Fedoseev, review by Gabriel Scherer)
|
|
|
|
- #9825, #9830: the C global variable caml_fl_merge and the C function
|
|
caml_spacetime_my_profinfo (bytecode version) were declared and
|
|
defined with different types. This is undefined behavior and
|
|
cancause link-time errors with link-time optimization (LTO).
|
|
(Xavier Leroy, report by Richard Jones, review by Nicolás Ojeda Bär)
|
|
|
|
- #9753: fix build for Android
|
|
(Github user @EduardoRFS, review by Xavier Leroy)
|
|
|
|
- #9848, #9855: Fix double free of bytecode in toplevel
|
|
(Stephen Dolan, report by Sampsa Kiiskinen, review by Gabriel Scherer)
|
|
|
|
- #9858, #9861: Compiler fails with Ctype.Nondep_cannot_erase exception
|
|
(Thomas Refis, report by @pveber, review by Florian Angeletti)
|
|
|
|
- #9860: wrong range constraint for subtract immediate on zSystems / s390x
|
|
(Xavier Leroy, review by Stephen Dolan)
|
|
|
|
- #9868, #9872, #9892: bugs in {in,out}_channel_length and seek_in
|
|
for files opened in text mode under Windows
|
|
(Xavier Leroy, report by Alain Frisch, review by Nicolás Ojeda Bär
|
|
and Alain Frisch)
|
|
|
|
- #9925: Correct passing -fdebug-prefix-map to flexlink on Cygwin by prefixing
|
|
it with -link.
|
|
(David Allsopp, review by Xavier Leroy)
|
|
|
|
- #9927: Restore Cygwin64 support.
|
|
(David Allsopp, review by Xavier Leroy)
|
|
|
|
- #9940: Fix unboxing of allocated constants from other compilation units
|
|
(Vincent Laviron, report by Stephen Dolan, review by Xavier Leroy and
|
|
Stephen Dolan)
|
|
|
|
- #9999: fix -dsource printing of the pattern (`A as x | (`B as x)).
|
|
(Gabriel Scherer, report by Anton Bachin, review by Florian Angeletti)
|
|
|
|
OCaml 4.11.1
|
|
------------
|
|
|
|
### Bug fixes:
|
|
|
|
- #9856, #9857: Prevent polymorphic type annotations from generalizing
|
|
weak polymorphic variables.
|
|
(Leo White, review by Jacques Garrigue)
|
|
|
|
- #9859, #9862: Remove an erroneous assertion when inferred function types
|
|
appear in the right hand side of an explicit :> coercion
|
|
(Florian Angeletti, review by Thomas Refis)
|
|
|
|
OCaml 4.11.0 (19 August 2020)
|
|
---------------------------
|
|
|
|
(Changes that can break existing programs are marked with a "*")
|
|
|
|
### Runtime system:
|
|
|
|
- #9096: Print function names in backtraces.
|
|
Old output:
|
|
> Called from file "foo.ml", line 16, characters 42-53
|
|
New output:
|
|
> Called from Foo.bar in file "foo.ml", line 16, characters 42-53
|
|
(Stephen Dolan, review by Leo White and Mark Shinwell)
|
|
|
|
- #9082: The instrumented runtime now records logs in the CTF format.
|
|
A new API is available in the runtime to collect runtime statistics,
|
|
replacing the previous instrumented runtime macros.
|
|
Gc.eventlog_pause and Gc.eventlog_resume were added to allow user to control
|
|
instrumentation in a running program.
|
|
See the manual for more information on how to use this instrumentation mode.
|
|
(Enguerrand Decorne and Stephen Dolan, with help and review from
|
|
David Allsopp, Sébastien Hinderer, review by Anil Madhavapeddy,
|
|
Nicolás Ojeda Bär, Shakthi Kannan, KC Sivaramakrishnan, Gabriel Scherer,
|
|
Guillaume Munch-Maccagnoni, Damien Doligez, Leo White, Daniel Bünzli
|
|
and Xavier Leroy)
|
|
|
|
- #9230, #9362: Memprof support for native allocations.
|
|
(Jacques-Henri Jourdan and Stephen Dolan, review by Gabriel Scherer)
|
|
|
|
- #8920, #9238, #9239, #9254, #9458: New API for statistical memory profiling
|
|
in Memprof.Gc. The new version does no longer use ephemerons and allows
|
|
registering callbacks for promotion and deallocation of memory
|
|
blocks.
|
|
The new API no longer gives the block tags to the allocation callback.
|
|
(Stephen Dolan and Jacques-Henri Jourdan, review by Damien Doligez
|
|
and Gabriel Scherer)
|
|
|
|
- #9353: Reimplement `output_value` and the `Marshal.to_*` functions
|
|
using a hash table to detect sharing, instead of temporary in-place
|
|
modifications. This is a prerequisite for Multicore OCaml.
|
|
(Xavier Leroy and Basile Clément, review by Gabriel Scherer and
|
|
Stephen Dolan)
|
|
|
|
|
|
- #9119: Make [caml_stat_resize_noexc] compatible with the [realloc]
|
|
API when the old block is NULL.
|
|
(Jacques-Henri Jourdan, review by Xavier Leroy)
|
|
|
|
- #9233: Restore the bytecode stack after an allocation.
|
|
(Stephen Dolan, review by Gabriel Scherer and Jacques-Henri Jourdan)
|
|
|
|
- #9249: restore definition of ARCH_ALIGN_INT64 in m.h if the architecture
|
|
requires 64-bit integers to be double-word aligned (autoconf regression)
|
|
(David Allsopp, review by Sébastien Hinderer)
|
|
|
|
- #9259: Made `Ephemeron.blit_key` and `Weak.blit` faster. They are now
|
|
linear in the size of the range being copied instead of depending on the
|
|
total sizes of the ephemerons or weak arrays involved.
|
|
(Arseniy Alekseyev, design advice by Leo White, review by François Bobot
|
|
and Damien Doligez)
|
|
|
|
- #9279: Memprof optimisation.
|
|
(Stephen Dolan, review by Jacques-Henri Jourdan)
|
|
|
|
- #9280: Micro-optimise allocations on amd64 to save a register.
|
|
(Stephen Dolan, review by Xavier Leroy)
|
|
|
|
- #9426: build the Mingw ports with higher levels of GCC optimization
|
|
(Xavier Leroy, review by Sébastien Hinderer)
|
|
|
|
* #9483: Remove accidental inclusion of <stdio.h> in <caml/misc.h>
|
|
The only release with the inclusion of stdio.h has been 4.10.0
|
|
(Christopher Zimmermann, review by Xavier Leroy and David Allsopp)
|
|
|
|
- #9282: Make Cconst_symbol have typ_int to fix no-naked-pointers mode.
|
|
(Stephen Dolan, review by Mark Shinwell, Xavier Leroy and Vincent Laviron)
|
|
|
|
- #9497: Harmonise behaviour between bytecode and native code for
|
|
recursive module initialisation in one particular case (fixes #9494).
|
|
(Mark Shinwell, David Allsopp, Vincent Laviron, Xavier Leroy,
|
|
Geoff Reedy, original bug report by Arlen Cox)
|
|
|
|
- #8791: use a variable-length encoding when marshalling bigarray dimensions,
|
|
avoiding overflow.
|
|
(Jeremy Yallop, Stephen Dolan, review by Xavier Leroy)
|
|
|
|
### Code generation and optimizations:
|
|
|
|
- #9441: Add RISC-V RV64G native-code backend.
|
|
(Nicolás Ojeda Bär, review by Xavier Leroy and Gabriel Scherer)
|
|
|
|
- #9316, #9443, #9463, #9782: Use typing information from Clambda
|
|
for mutable Cmm variables.
|
|
(Stephen Dolan, review by Vincent Laviron, Guillaume Bury, Xavier Leroy,
|
|
and Gabriel Scherer; temporary bug report by Richard Jones)
|
|
|
|
- #8637, #8805, #9247, #9296: Record debug info for each allocation.
|
|
(Stephen Dolan and Jacques-Henri Jourdan, review by Damien Doligez,
|
|
KC Sivaramakrishnan and Xavier Leroy)
|
|
|
|
|
|
- #9193: Make tuple matching optimisation apply to Lswitch and Lstringswitch.
|
|
(Stephen Dolan, review by Thomas Refis and Gabriel Scherer)
|
|
|
|
- #9392: Visit registers at most once in Coloring.iter_preferred.
|
|
(Stephen Dolan, review by Pierre Chambart and Xavier Leroy)
|
|
|
|
- #9549, #9557: Make -flarge-toc the default for PowerPC and introduce
|
|
-fsmall-toc to enable the previous behaviour.
|
|
(David Allsopp, report by Nathaniel Wesley Filardo, review by Xavier Leroy)
|
|
|
|
### Language features
|
|
|
|
- #8820, #9166: quoted extensions: {%foo|...|} is lighter syntax for
|
|
[%foo {||}], and {%foo bar|...|bar} for [%foo {bar|...|bar}].
|
|
(Gabriel Radanne, Leo White, Gabriel Scherer and Pieter Goetschalckx,
|
|
request by Bikal Lem)
|
|
|
|
- #7364, #2188, #9592, #9609: improvement of the unboxability check for types
|
|
with a single constructor. Mutually-recursive type declarations can
|
|
now contain unboxed types. This is based on the paper
|
|
https://arxiv.org/abs/1811.02300
|
|
(Gabriel Scherer and Rodolphe Lepigre,
|
|
review by Jeremy Yallop, Damien Doligez and Frédéric Bour)
|
|
|
|
- #1154, #1706: spellchecker hints and type-directed disambiguation
|
|
for extensible sum type constructors
|
|
(Florian Angeletti, review by Alain Frisch, Gabriel Radanne, Gabriel Scherer
|
|
and Leo White)
|
|
|
|
|
|
- #6673, #1132, #9617: Relax the handling of explicit polymorphic types.
|
|
This improves error messages in some polymorphic recursive definition,
|
|
and requires less polymorphic annotations in some cases of
|
|
mutually-recursive definitions involving polymorphic recursion.
|
|
(Leo White, review by Jacques Garrigue and Gabriel Scherer)
|
|
|
|
- #9232: allow any class type paths in #-types,
|
|
For instance, "val f: #F(X).t -> unit" is now allowed.
|
|
(Florian Angeletti, review by Gabriel Scherer, suggestion by Leo White)
|
|
|
|
### Standard library:
|
|
|
|
- #9077: Add Seq.cons and Seq.append
|
|
(Sébastien Briais, review by Yawar Amin and Florian Angeletti)
|
|
|
|
- #9235: Add Array.exists2 and Array.for_all2
|
|
(Bernhard Schommer, review by Armaël Guéneau)
|
|
|
|
- #9226: Add Seq.unfold.
|
|
(Jeremy Yallop, review by Hezekiah M. Carty, Gabriel Scherer and
|
|
Gabriel Radanne)
|
|
|
|
- #9059: Added List.filteri function, same as List.filter but
|
|
with the index of the element.
|
|
(Léo Andrès, review by Alain Frisch)
|
|
|
|
- #8894: Added List.fold_left_map function combining map and fold.
|
|
(Bernhard Schommer, review by Alain Frisch and github user @cfcs)
|
|
|
|
- #9365: Set.filter_map and Map.filter_map
|
|
(Gabriel Scherer, review by Stephen Dolan and Nicolás Ojeda Bär)
|
|
|
|
|
|
- #9248: Add Printexc.default_uncaught_exception_handler
|
|
(Raphael Sousa Santos, review by Daniel Bünzli)
|
|
|
|
- #8771: Lexing: add set_position and set_filename to change (fake)
|
|
the initial tracking position of the lexbuf.
|
|
(Konstantin Romanov, Miguel Lumapat, review by Gabriel Scherer,
|
|
Sébastien Hinderer, and David Allsopp)
|
|
|
|
- #9237: `Format.pp_update_geometry ppf (fun geo -> {geo with ...})`
|
|
for formatter geometry changes that are robust to new geometry fields.
|
|
(Gabriel Scherer, review by Josh Berdine and Florian Angeletti)
|
|
|
|
- #7110: Added Printf.ikbprintf and Printf.ibprintf
|
|
(Muskan Garg, review by Gabriel Scherer and Florian Angeletti)
|
|
|
|
- #9266: Install pretty-printer for the exception Fun.Finally_raised.
|
|
(Guillaume Munch-Maccagnoni, review by Daniel Bünzli, Gabriel Radanne,
|
|
and Gabriel Scherer)
|
|
|
|
### Other libraries:
|
|
|
|
- #9106: Register printer for Unix_error in win32unix, as in unix.
|
|
(Christopher Zimmermann, review by David Allsopp)
|
|
|
|
- #9183: Preserve exception backtrace of exceptions raised by top-level phrases
|
|
of dynlinked modules.
|
|
(Nicolás Ojeda Bär, review by Xavier Clerc and Gabriel Scherer)
|
|
|
|
- #9320, #9550: under Windows, make sure that the Unix.exec* functions
|
|
properly quote their argument lists.
|
|
(Xavier Leroy, report by André Maroneze, review by Nicolás Ojeda Bär
|
|
and David Allsopp)
|
|
|
|
- #9490, #9505: ensure proper rounding of file times returned by
|
|
Unix.stat, Unix.lstat, Unix.fstat.
|
|
(Xavier Leroy and Guillaume Melquiond, report by David Brown,
|
|
review by Gabriel Scherer and David Allsopp)
|
|
|
|
### Tools:
|
|
|
|
- #9283, #9455, #9457: add a new toplevel directive `#use_output "<command>"` to
|
|
run a command and evaluate its output.
|
|
(Jérémie Dimino, review by David Allsopp)
|
|
|
|
|
|
- #6969: Argument -nocwd added to ocamldep
|
|
(Muskan Garg, review by Florian Angeletti)
|
|
|
|
- #8676, #9594: turn debugger off in programs launched by the program
|
|
being debugged
|
|
(Xavier Leroy, report by Michael Soegtrop, review by Gabriel Scherer)
|
|
|
|
- #9057: aid debugging the debugger by preserving backtraces of unhandled
|
|
exceptions.
|
|
(David Allsopp, review by Gabriel Scherer)
|
|
|
|
- #9276: objinfo: cm[x]a print extra C options, objects and dlls in
|
|
the order given on the cli. Follow up to #4949.
|
|
(Daniel Bünzli, review by Gabriel Scherer)
|
|
|
|
- #463: objinfo: better errors on object files coming
|
|
from a different (older or newer), incompatible compiler version.
|
|
(Gabriel Scherer, review by Gabriel Radanne and Damien Doligez)
|
|
|
|
* #9197: remove compatibility logic from #244 that was designed to
|
|
synchronize toplevel printing margins with Format.std_formatter,
|
|
but also resulted in unpredictable/fragile changes to formatter
|
|
margins.
|
|
Setting the margins on the desired formatters should now work.
|
|
typically on `Format.std_formatter`.
|
|
Note that there currently is no robust way to do this from the
|
|
toplevel, as applications may redirect toplevel printing. In
|
|
a compiler/toplevel driver, one should instead access
|
|
`Location.formatter_for_warnings`; it is not currently exposed
|
|
to the toplevel.
|
|
(Gabriel Scherer, review by Armaël Guéneau)
|
|
|
|
- #9207, #9210: fix ocamlyacc to work correctly with up to 255 entry
|
|
points to the grammar.
|
|
(Andreas Abel, review by Xavier Leroy)
|
|
|
|
- #9482, #9492: use diversions (@file) to work around OS limitations
|
|
on length of Sys.command argument.
|
|
(Xavier Leroy, report by Jérémie Dimino, review by David Allsopp)
|
|
|
|
### Manual and documentation:
|
|
|
|
- #9141: beginning of the ocamltest reference manual
|
|
(Sébastien Hinderer, review by Gabriel Scherer and Thomas Refis)
|
|
|
|
- #9228: Various Map documentation improvements: add missing key argument in
|
|
the 'merge' example; clarify the relationship between input and output keys
|
|
in 'union'; note that find and find_opt return values, not bindings.
|
|
(Jeremy Yallop, review by Gabriel Scherer and Florian Angeletti)
|
|
|
|
- #9255, #9300: reference chapter, split the expression grammar
|
|
(Florian Angeletti, report by Harrison Ainsworth, review by Gabriel Scherer)
|
|
|
|
- #9325: documented base case for `List.for_all` and `List.exists`
|
|
(Glenn Slotte, review by Florian Angeletti)
|
|
|
|
- #9410, #9422: replaced naive fibonacci example with gcd
|
|
(Anukriti Kumar, review by San Vu Ngoc, Florian Angeletti, Léo Andrès)
|
|
|
|
- #9541: Add a documentation page for the instrumented runtime;
|
|
additional changes to option names in the instrumented runtime.
|
|
(Enguerrand Decorne, review by Anil Madhavapeddy, Gabriel Scherer,
|
|
Daniel Bünzli, David Allsopp, Florian Angeletti,
|
|
and Sébastien Hinderer)
|
|
|
|
- #9610: manual, C FFI: naked pointers are deprecated, detail the
|
|
forward-compatible options for handling out-of-heap pointers.
|
|
(Xavier Leroy, review by Mark Shinwell, David Allsopp and Florian Angeletti)
|
|
|
|
- #9618: clarify the Format documentation on the margin and maximum indentation
|
|
limit
|
|
(Florian Angeletti, review by Josh Berdine)
|
|
|
|
|
|
- #8644: fix formatting comment about @raise in stdlib's mli files
|
|
(Élie Brami, review by David Allsopp)
|
|
|
|
- #9327, #9401: manual, fix infix attribute examples
|
|
(Florian Angeletti, report by David Cadé, review by Gabriel Scherer)
|
|
|
|
- #9403: added a description for warning 67 and added a "." at the end of
|
|
warnings for consistency.
|
|
(Muskan Garg, review by Gabriel Scherer and Florian Angeletti)
|
|
|
|
- #7708, #9580: Ensure Stdlib documentation index refers to Stdlib.
|
|
(Stephen Dolan, review by Florian Angeletti, report by Hannes Mehnert)
|
|
|
|
### Compiler user-interface and warnings:
|
|
|
|
- #9712: Update the version format to allow "~".
|
|
The new format is "major.minor[.patchlevel][(+|~)additional-info]",
|
|
for instance "4.12.0~beta1+flambda".
|
|
This is a documentation-only change for the 4.11 branch, the new format
|
|
will be used starting with the 4.12 branch.
|
|
(Florian Angeletti, review by Damien Doligez and Xavier Leroy)
|
|
|
|
- #1664: make -output-complete-obj link the runtime native c libraries when
|
|
building shared libraries like `-output-obj`.
|
|
(Florian Angeletti, review by Nicolás Ojeda Bär)
|
|
|
|
- #9349: Support [@inlined hint] attribute.
|
|
(Leo White, review by Stephen Dolan)
|
|
|
|
- #2141: generate .annot files from cmt data; deprecate -annot.
|
|
(Nicolás Ojeda Bär, review by Alain Frisch, Gabriel Scherer and Damien
|
|
Doligez)
|
|
|
|
|
|
* #7678, #8631: ocamlc -c and ocamlopt -c pass same switches to the C
|
|
compiler when compiling .c files (in particular, this means ocamlopt
|
|
passes -fPIC on systems requiring it for shared library support).
|
|
(David Allsopp, report by Daniel Bünzli, review by Sébastien Hinderer)
|
|
|
|
- #9074: reworded error message for non-regular structural types
|
|
(Florian Angeletti, review by Jacques Garrigue and Leo White,
|
|
report by Chas Emerick)
|
|
|
|
- #8938: Extend ocamlopt option "-stop-after" to handle "scheduling" argument.
|
|
(Greta Yorsh, review by Florian Angeletti and Sébastien Hinderer)
|
|
|
|
- #8945, #9086: Fix toplevel show directive to work with constructors
|
|
(Simon Parry, review by Gabriel Scherer, Jeremy Yallop,
|
|
Alain Frisch, Florian Angeletti)
|
|
|
|
- #9107: improved error message for exceptions in module signature errors
|
|
(Gabriel Scherer, review by Florian Angeletti)
|
|
|
|
- #9208: -dno-locations option to hide source locations (and debug events)
|
|
from intermediate-representation dumps (-dfoo).
|
|
(Gabriel Scherer, review by Vincent Laviron)
|
|
|
|
- #9393: Improve recursive module usage warnings
|
|
(Leo White, review by Thomas Refis)
|
|
|
|
- #9486: Fix configuration for the Haiku operating system
|
|
(Sylvain Kerjean, review by David Allsopp and Sébastien Hinderer)
|
|
|
|
### Internal/compiler-libs changes:
|
|
|
|
- #9021: expose compiler Longident.t parsers
|
|
(Florian Angeletti, review by Gabriel Scherer)
|
|
|
|
- #9452: Add locations to docstring attributes
|
|
(Leo White, review by Gabriel Scherer)
|
|
|
|
|
|
- #463: a new Misc.Magic_number module for user-friendly parsing
|
|
and validation of OCaml magic numbers.
|
|
(Gabriel Scherer, review by Gabriel Radanne and Damien Doligez)
|
|
|
|
- #1176: encourage better compatibility with older Microsoft C compilers by
|
|
using GCC's -Wdeclaration-after-statement when available. Introduce
|
|
Caml_inline to stop abuse of the inline keyword on MSVC and to help ensure
|
|
that only static inline is used in the codebase (erroneous instance in
|
|
runtime/win32.c removed).
|
|
(David Allsopp, review by Oliver Andrieu and Xavier Leroy)
|
|
|
|
- #8934: Stop relying on location to track usage
|
|
(Thomas Refis, review by Gabriel Radanne)
|
|
|
|
- #8970: separate value patterns (matching on values) from computation patterns
|
|
(matching on the effects of a copmutation) in the typedtree.
|
|
(Gabriel Scherer, review by Jacques Garrigue and Alain Frisch)
|
|
|
|
- #9060: ensure that Misc.protect_refs preserves backtraces
|
|
(Gabriel Scherer, review by Guillaume Munch-Maccagnoni and David Allsopp)
|
|
|
|
- #9078: make all compilerlibs/ available to ocamltest.
|
|
(Gabriel Scherer, review by Sébastien Hinderer)
|
|
|
|
- #9079: typecore/parmatch: refactor ppat_of_type and refine
|
|
the use of backtracking on wildcard patterns
|
|
(Florian Angeletti, Jacques Garrigue, Gabriel Scherer,
|
|
review by Thomas Refis)
|
|
|
|
- #9081: typedtree, make the pat_env field of pattern data immutable
|
|
(Gabriel Scherer, review by Jacques Garrigue, report by Alain Frisch)
|
|
|
|
- #9178, #9182, #9196: refactor label-disambiguation (Typecore.NameChoice)
|
|
(Gabriel Scherer, Thomas Refis, Florian Angeletti and Jacques Garrigue,
|
|
reviewing each other without self-loops)
|
|
|
|
- #9321, #9322, #9359, #9361, #9417, #9447: refactor the
|
|
pattern-matching compiler
|
|
(Thomas Refis and Gabriel Scherer, review by Florian Angeletti)
|
|
|
|
- #9211, #9215, #9222: fix Makefile dependencies in
|
|
compilerlibs, dynlink, ocamltest.
|
|
(Gabriel Scherer, review by Vincent Laviron and David Allsopp)
|
|
|
|
- #9275: Short circuit simple inclusion checks
|
|
(Leo White, review by Thomas Refis)
|
|
|
|
- #9305: Avoid polymorphic compare in Ident
|
|
(Leo White, review by Xavier Leroy and Gabriel Scherer)
|
|
|
|
- #7927: refactor val_env met_env par_env to class_env
|
|
(Muskan Garg, review by Gabriel Scherer and Florian Angeletti)
|
|
|
|
- #2324, #9613: Replace the caml_int_compare and caml_float_compare
|
|
(C functions) with primitives.
|
|
(Greta Yorsh, review by Stephen Dolan and Vincent Laviron)
|
|
|
|
- #9246: Avoid rechecking functor applications
|
|
(Leo White, review by Jacques Garrigue)
|
|
|
|
- #9402: Remove `sudo:false` from .travis.yml
|
|
(Hikaru Yoshimura)
|
|
|
|
* #9411: forbid optional arguments reordering with -nolabels
|
|
(Thomas Refis, review by Frédéric Bour and Jacques Garrigue)
|
|
|
|
- #9414: testsuite, ocamltest: keep test artifacts only on failure.
|
|
Use KEEP_TEST_DIR_ON_SUCCESS=1 to keep all artifacts.
|
|
(Gabriel Scherer, review by Sébastien Hinderer)
|
|
|
|
|
|
### Build system:
|
|
|
|
- #9250: Add --disable-ocamltest to configure and disable building for
|
|
non-development builds.
|
|
(David Allsopp, review by Sébastien Hinderer)
|
|
|
|
### Bug fixes:
|
|
|
|
- #7520, #9547: Odd behaviour of refutation cases with polymorphic variants
|
|
(Jacques Garrigue, report by Leo White, reviews by Gabriel Scherer and Leo)
|
|
|
|
- #7562, #9456: ocamlopt-generated code crashed on Alpine Linux on
|
|
ppc64le, arm, and i386. Fixed by turning PIE off for musl-based Linux
|
|
systems except amd64 (x86_64) and s390x.
|
|
(Xavier Leroy, review by Gabriel Scherer)
|
|
|
|
- #7683, #1499: Fixes one case where the evaluation order in native-code
|
|
may not match the one in bytecode.
|
|
(Nicolás Ojeda Bär, report by Pierre Chambart, review by Gabriel Scherer)
|
|
|
|
- #7696, #6608: Record expression deleted when all fields specified
|
|
(Jacques Garrigue, report by Jeremy Yallop)
|
|
|
|
- #7741, #9645: Failure to report escaping type variable
|
|
(Jacques Garrigue, report by Gabriel Radanne, review by Gabriel Scherer)
|
|
|
|
- #7817, #9546: Unsound inclusion check for polymorphic variant
|
|
(Jacques Garrigue, report by Mikhail Mandrykin, review by Gabriel Scherer)
|
|
|
|
- #7897, #9537: Fix warning 38 for rebound extension constructors
|
|
(Leo White, review by Florian Angeletti)
|
|
|
|
- #7917, #9426: Use GCC option -fexcess-precision=standard when available,
|
|
avoiding a problem with x87 excess precision in Float.round.
|
|
(Xavier Leroy, review by Sébastien Hinderer)
|
|
|
|
- #9011: Allow linking .cmxa files with no units on MSVC by not requiring the
|
|
.lib file to be present.
|
|
(David Allsopp, report by Dimitry Bely, review by Xavier Leroy)
|
|
|
|
- #9064: Relax the level handling when unifying row fields
|
|
(Leo White, review by Jacques Garrigue)
|
|
|
|
- #9097: Do not emit references to dead labels introduced by #2321 (spacetime).
|
|
(Greta Yorsh, review by Mark Shinwell)
|
|
|
|
- #9163: Treat loops properly in un_anf
|
|
(Leo White, review by Mark Shinwell, Pierre Chambart and Vincent Laviron)
|
|
|
|
- #9189, #9281: fix a conflict with Gentoo build system
|
|
by removing an one-letter Makefile variable.
|
|
(Florian Angeletti, report by Ralph Seichter, review by David Allsopp
|
|
and Damien Doligez)
|
|
|
|
- #9225: Do not drop bytecode debug info after C calls.
|
|
(Stephen Dolan, review by Gabriel Scherer and Jacques-Henri Jourdan)
|
|
|
|
- #9231: Make sure a debug event (and the corresponding debug
|
|
information) is inserted after every primitive that can appear in a
|
|
collected call stack, and make sure ocamlc preserves such events
|
|
even if they are at tail position.
|
|
(Jacques-Henri Jourdan, review by Gabriel Scherer)
|
|
|
|
- #9244: Fix some missing usage warnings
|
|
(Leo White, review by Florian Angeletti)
|
|
|
|
- #9274, avoid reading cmi file while printing types
|
|
(Florian Angeletti, review by Gabriel Scherer)
|
|
|
|
- #9307, #9345: reproducible env summaries for reproducible compilation
|
|
(Florian Angeletti, review by Leo White)
|
|
|
|
- #9309, #9318: Fix exhaustivity checking with empty types
|
|
(Florian Angeletti, Stefan Muenzel and Thomas Refis, review by Gabriel Scherer
|
|
and Thomas Refis)
|
|
|
|
- #9335: actually have --disable-stdlib-manpages not build the manpages
|
|
(implementation conflicted with #8837 which wasn't picked up in review)
|
|
(David Allsopp, review by Florian Angeletti and Sébastien Hinderer)
|
|
|
|
- #9343: Re-enable `-short-paths` for some error messages
|
|
(Leo White, review by Florian Angeletti)
|
|
|
|
- #9355, #9356: ocamldebug, fix a fatal error when printing values
|
|
whose type involves a functor application.
|
|
(Florian Angeletti, review by Gabriel Scherer, report by Cyril Six)
|
|
|
|
- #9367: Make bytecode and native-code backtraces agree.
|
|
(Stephen Dolan, review by Gabriel Scherer)
|
|
|
|
- #9375, #9477: add forgotten substitution when compiling anonymous modules
|
|
(Thomas Refis, review by Frédéric Bour, report by Andreas Hauptmann)
|
|
|
|
- #9384, #9385: Fix copy scope bugs in substitutions
|
|
(Leo White, review by Thomas Refis, report by Nick Roberts)
|
|
|
|
* #9388: Prohibit signature local types with constraints
|
|
(Leo White, review by Jacques Garrigue)
|
|
|
|
- #7141, #9389: returns exit_code for better user response on linking_error
|
|
(Anukriti Kumar, review by Gabriel Scherer and Valentin Gatien-Baron)
|
|
|
|
- #9406, #9409: fix an error with packed module types from missing
|
|
cmis.
|
|
(Florian Angeletti, report by Thomas Leonard, review by Gabriel Radanne
|
|
and Gabriel Scherer)
|
|
|
|
- #9415: Treat `open struct` as `include struct` in toplevel
|
|
(Leo White, review by Thomas Refis)
|
|
|
|
- #9416: Avoid warning 58 in flambda ocamlnat
|
|
(Leo White, review by Florian Angeletti)
|
|
|
|
- #9420: Fix memory leak when `caml_output_value_to_block` raises an exception
|
|
(Xavier Leroy, review by Guillaume Munch-Maccagnoni)
|
|
|
|
- #9428: Fix truncated exception backtrace for C->OCaml callbacks
|
|
on Power and Z System
|
|
(Xavier Leroy, review by Nicolás Ojeda Bär)
|
|
|
|
- #9623, #9642: fix typing environments in Typedecl.transl_with_constraint
|
|
(Gabriel Scherer, review by Jacques Garrigue and Leo White,
|
|
report by Hugo Heuzard)
|
|
|
|
- #9695, #9702: no error when opening an alias to a missing module
|
|
(Jacques Garrigue, report and review by Gabriel Scherer)
|
|
|
|
- #9714, #9724: Add a terminator to the `caml_domain_state` structure
|
|
to better ensure that members are correctly spaced.
|
|
(Antonin Décimo, review by David Allsopp and Xavier Leroy)
|
|
|
|
OCaml 4.10 maintenance branch
|
|
-----------------------------
|
|
|
|
### Runtime system:
|
|
|
|
- #9344, #9368: Disable exception backtraces in bytecode programs
|
|
built with "-output-complete-exe". At the moment, such programs do
|
|
not embed debug information and exception backtraces where causing
|
|
them to crash.
|
|
(Jérémie Dimino, review by Nicolás Ojeda Bär)
|
|
|
|
### Build system:
|
|
|
|
- #9531: fix support for the BFD library on FreeBSD
|
|
(Hannes Mehnert, review by Gabriel Scherer and David Allsopp)
|
|
|
|
### Bug fixes:
|
|
|
|
- #9068, #9437: ocamlopt -output-complete-obj failure on FreeBSD 12
|
|
(Xavier Leroy, report by Hannes Mehnert, review by Sébastien Hinderer)
|
|
|
|
- #9165, #9840: Add missing -function-sections flag in Makefiles.
|
|
(Greta Yorsh, review by David Allsopp)
|
|
|
|
- #9495: fix a bug where bytecode binaries compiled with `-output-complete-exe`
|
|
would not execute `at_exit` hooks at program termination (in particular,
|
|
output channels would not be flushed).
|
|
(Nicolás Ojeda Bär, review by David Allsopp)
|
|
|
|
- #9714, #9724: Use the C++ alignas keyword when compiling in C++ in MSVC.
|
|
Fixes a bug with MSVC C++ 2015 onwards.
|
|
(Antonin Décimo, review by David Allsopp and Xavier Leroy)
|
|
|
|
- #9736, #9749: Compaction must start in a heap where all free blocks are
|
|
blue, which was not the case with the best-fit allocator.
|
|
(Damien Doligez, report and review by Leo White)
|
|
|
|
### Tools:
|
|
|
|
- #9552: restore ocamloptp build and installation
|
|
(Florian Angeletti, review by David Allsopp and Xavier Leroy)
|
|
|
|
OCaml 4.10.0 (21 February 2020)
|
|
-------------------------------
|
|
|
|
(Changes that can break existing programs are marked with a "*")
|
|
|
|
### Language features
|
|
|
|
- #7757, #1726: multi-indices for extended indexing operators:
|
|
`a.%{0;1;2}` desugars to `( .%{ ;.. } ) a [|0;1;2|]`
|
|
(Florian Angeletti, review by Gabriel Radanne)
|
|
|
|
* #1859, #9117: enforce safe (immutable) strings by removing
|
|
the -unsafe-string option by default. This can be overridden by
|
|
a configure-time option (available since 4.04 in 2016):
|
|
--disable-force-safe-string since 4.08, -no-force-safe-since
|
|
between 4.07 and 4.04.
|
|
In the force-safe-string mode (now the default), the return type of the
|
|
String_val macro in C stubs is `const char*` instead of
|
|
`char*`. This change may break C FFI code.
|
|
(Kate Deplaix)
|
|
|
|
|
|
- #6662, #8908: allow writing "module _ = E" to ignore module expressions
|
|
(Thomas Refis, review by Gabriel Radanne)
|
|
|
|
### Runtime system:
|
|
|
|
- #8809, #9292: Add a best-fit allocator for the major heap; still
|
|
experimental, it should be much better than current allocation
|
|
policies (first-fit and next-fit) for programs with large heaps,
|
|
reducing both GC cost and memory usage.
|
|
This new best-fit is not (yet) the default; set it explicitly with
|
|
OCAMLRUNPARAM="a=2" (or Gc.set from the program). You may also want
|
|
to increase the `space_overhead` parameter of the GC (a percentage,
|
|
80 by default), for example OCAMLRUNPARAM="o=85", for optimal
|
|
speed.
|
|
(Damien Doligez, review by Stephen Dolan, Jacques-Henri Jourdan,
|
|
Xavier Leroy, Leo White)
|
|
|
|
* #8713, #8940, #9115, #9143, #9202, #9251:
|
|
Introduce a state table in the runtime to contain the global variables.
|
|
(The Multicore runtime will have one such state for each domain.)
|
|
|
|
This changes the status of some internal variables of the OCaml runtime;
|
|
in many cases the header file originally defining the internal variable
|
|
provides a compatibility macro with the old name, but programs
|
|
re-defining those variables by hand need to be fixed.
|
|
|
|
(KC Sivaramakrishnan and Stephen Dolan,
|
|
compatibility hacking by David Allsopp, Florian Angeletti, Kate Deplaix,
|
|
Jacques Garrigue, Guillaume Munch-Maccagnoni and Nicolás Ojeda Bär,
|
|
review by David Allsopp, Alain Frisch, Nicolás Ojeda Bär,
|
|
Gabriel Scherer, Damien Doligez, and Guillaume Munch-Maccagnoni)
|
|
|
|
- #8993: New C functions caml_process_pending_actions{,_exn} in
|
|
caml/signals.h, intended for executing all pending actions inside
|
|
long-running C functions (requested minor and major collections,
|
|
signal handlers, finalisers, and memprof callbacks). The function
|
|
caml_process_pending_actions_exn returns any exception arising
|
|
during their execution, allowing resources to be cleaned-up before
|
|
re-raising.
|
|
(Guillaume Munch-Maccagnoni, review by Jacques-Henri Jourdan,
|
|
Stephen Dolan, and Gabriel Scherer)
|
|
|
|
* #8691, #8897, #9027: Allocation functions are now guaranteed not to
|
|
trigger any OCaml callback when called from C. In long-running C
|
|
functions, this can be replaced with calls to
|
|
caml_process_pending_actions at safe points.
|
|
Side effect of this change: in bytecode mode, polling for
|
|
asynchronous callbacks is performed at every minor heap allocation,
|
|
in addition to function calls and loops as in previous OCaml
|
|
releases.
|
|
(Jacques-Henri Jourdan, review by Stephen Dolan, Gabriel Scherer and
|
|
Guillaume Munch-Maccagnoni)
|
|
|
|
* #9037: caml_check_urgent_gc is now guaranteed not to trigger any
|
|
finaliser. In long-running C functions, this can be replaced
|
|
with calls to caml_process_pending_actions at safe points.
|
|
(Guillaume Munch-Maccagnoni, review by Jacques-Henri Jourdan and
|
|
Stephen Dolan)
|
|
|
|
|
|
- #8619: Ensure Gc.minor_words remains accurate after a GC.
|
|
(Stephen Dolan, Xavier Leroy and David Allsopp,
|
|
review by Xavier Leroy and Gabriel Scherer)
|
|
|
|
- #8667: Limit GC credit to 1.0
|
|
(Leo White, review by Damien Doligez)
|
|
|
|
- #8670: Fix stack overflow detection with systhreads
|
|
(Stephen Dolan, review by Xavier Leroy, Anil Madhavapeddy, Gabriel Scherer,
|
|
Frédéric Bour and Guillaume Munch-Maccagnoni)
|
|
|
|
* #8711: The major GC hooks are no longer allowed to interact with the
|
|
OCaml heap.
|
|
(Jacques-Henri Jourdan, review by Damien Doligez)
|
|
|
|
- #8630: Use abort() instead of exit(2) in caml_fatal_error, and add
|
|
the new hook caml_fatal_error_hook.
|
|
(Jacques-Henri Jourdan, review by Xavier Leroy)
|
|
|
|
- #8641: Better call stacks when a C call is involved in byte code mode
|
|
(Jacques-Henri Jourdan, review by Xavier Leroy)
|
|
|
|
- #8634, #8668, #8684, #9103 (originally #847): Statistical memory profiling.
|
|
In OCaml 4.10, support for allocations in the minor heap in native
|
|
mode is not available, and callbacks for promotions and
|
|
deallocations are not available.
|
|
Hence, there is not any public API for this feature yet.
|
|
(Jacques-Henri Jourdan, review by Stephen Dolan, Gabriel Scherer
|
|
and Damien Doligez)
|
|
|
|
- #9268, #9271: Fix bytecode backtrace generation with large integers present.
|
|
(Stephen Dolan and Mark Shinwell, review by Gabriel Scherer and
|
|
Jacques-Henri Jourdan)
|
|
|
|
### Standard library:
|
|
|
|
- #8760: List.concat_map : ('a -> 'b list) -> 'a list -> 'b list
|
|
(Gabriel Scherer, review by Daniel Bünzli and Thomas Refis)
|
|
|
|
- #8832: List.find_map : ('a -> 'b option) -> 'a list -> 'b option
|
|
(Gabriel Scherer, review by Jeremy Yallop, Nicolás Ojeda Bär
|
|
and Daniel Bünzli)
|
|
|
|
- #7672, #1492: Add `Filename.quote_command` to produce properly-quoted
|
|
commands for execution by Sys.command.
|
|
(Xavier Leroy, review by David Allsopp and Damien Doligez)
|
|
|
|
- #8971: Add `Filename.null`, the conventional name of the "null" device.
|
|
(Nicolás Ojeda Bär, review by Xavier Leroy and Alain Frisch)
|
|
|
|
- #8651: add '%#F' modifier in printf to output OCaml float constants
|
|
in hexadecimal
|
|
(Pierre Roux, review by Gabriel Scherer and Xavier Leroy)
|
|
|
|
|
|
- #8657: Optimization in [Array.make] when initializing with unboxed
|
|
or young values.
|
|
(Jacques-Henri Jourdan, review by Gabriel Scherer and Stephen Dolan)
|
|
|
|
- #8716: Optimize [Array.fill] and [Hashtbl.clear] with a new runtime primitive
|
|
(Alain Frisch, review by David Allsopp, Stephen Dolan and Damien Doligez)
|
|
|
|
- #8530: List.sort: avoid duplicate work by chop
|
|
(Guillaume Munch-Maccagnoni, review by David Allsopp, Damien Doligez and
|
|
Gabriel Scherer)
|
|
|
|
### Other libraries:
|
|
|
|
- #1939, #2023: Implement Unix.truncate and Unix.ftruncate on Windows.
|
|
(Florent Monnier and Nicolás Ojeda Bär, review by David Allsopp)
|
|
|
|
### Code generation and optimizations:
|
|
|
|
- #8806: Add an [@@immediate64] attribute for types that are known to
|
|
be immediate only on 64 bit platforms
|
|
(Jérémie Dimino, review by Vladimir Keleshev)
|
|
|
|
- #9028, #9032: Fix miscompilation by no longer assuming that
|
|
untag_int (tag_int x) = x in Cmmgen; the compilation of `(n lsl 1) + 1`,
|
|
for example, would be incorrect if evaluated with a large value for `n`.
|
|
(Stephen Dolan, review by Vincent Laviron and Xavier Leroy)
|
|
|
|
- #8672: Optimise Switch code generation on booleans.
|
|
(Stephen Dolan, review by Pierre Chambart)
|
|
|
|
|
|
- #8990: amd64: Emit 32bit registers for Iconst_int when we can
|
|
(Xavier Clerc, Tom Kelly and Mark Shinwell, review by Xavier Leroy)
|
|
|
|
- #2322: Add pseudo-instruction `Ladjust_trap_depth` to replace
|
|
dummy Lpushtrap generated in linearize
|
|
(Greta Yorsh and Vincent Laviron, review by Xavier Leroy)
|
|
|
|
- #8707: Simplif: more regular treatment of Tupled and Curried functions
|
|
(Gabriel Scherer, review by Leo White and Alain Frisch)
|
|
|
|
- #8526: Add compile-time option -function-sections in ocamlopt to emit
|
|
each function in a separate named text section on supported targets.
|
|
(Greta Yorsh, review by Pierre Chambart)
|
|
|
|
- #2321: Eliminate dead ICatch handlers
|
|
(Greta Yorsh, review by Pierre Chambart and Vincent Laviron)
|
|
|
|
- #8919: lift mutable lets along with immutable ones
|
|
(Leo White, review by Pierre Chambart)
|
|
|
|
- #8909: Graph coloring register allocator: the weights put on
|
|
preference edges should not be divided by 2 in branches of
|
|
conditional constructs, because it is not good for performance
|
|
and because it leads to ignoring preference edges with 0 weight.
|
|
(Eric Stavarache, review by Xavier Leroy)
|
|
|
|
- #9006: int32 code generation improvements
|
|
(Stephen Dolan, designed with Greta Yorsh, review by Xavier Clerc,
|
|
Xavier Leroy and Alain Frisch)
|
|
|
|
- #9041: amd64: Avoid stall in sqrtsd by clearing destination.
|
|
(Stephen Dolan, with thanks to Andrew Hunter, Will Hasenplaugh,
|
|
Spiros Eliopoulos and Brian Nigito. Review by Xavier Leroy)
|
|
|
|
- #2165: better unboxing heuristics for let-bound identifiers
|
|
(Alain Frisch, review by Vincent Laviron and Gabriel Scherer)
|
|
|
|
- #8735: unbox across static handlers
|
|
(Alain Frisch, review by Vincent Laviron and Gabriel Scherer)
|
|
|
|
### Manual and documentation:
|
|
|
|
- #8718, #9089: syntactic highlighting for code examples in the manual
|
|
(Florian Angeletti, report by Anton Kochkov, review by Gabriel Scherer)
|
|
|
|
- #9101: add links to section anchor before the section title,
|
|
make the name of those anchor explicits.
|
|
(Florian Angeletti, review by Daniel Bünzli, Sébastien Hinderer,
|
|
and Gabriel Scherer)
|
|
|
|
- #9257, cautionary guidelines for using the internal runtime API
|
|
without too much updating pain.
|
|
(Florian Angeletti, review by Daniel Bünzli, Guillaume Munch-Maccagnoni
|
|
and KC Sivaramakrishnan)
|
|
|
|
|
|
- #8950: move local opens in pattern out of the extension chapter
|
|
(Florian Angeletti, review and suggestion by Gabriel Scherer)
|
|
|
|
- #9088, #9097: fix operator character classes
|
|
(Florian Angeletti, review by Gabriel Scherer,
|
|
report by Clément Busschaert)
|
|
|
|
- #9169: better documentation for the best-fit allocation policy
|
|
(Gabriel Scherer, review by Guillaume Munch-Maccagnoni
|
|
and Florian Angeletti)
|
|
|
|
### Compiler user-interface and warnings:
|
|
|
|
- #8833: Hint for (type) redefinitions in toplevel session
|
|
(Florian Angeletti, review by Gabriel Scherer)
|
|
|
|
- #2127, #9185: Refactor lookup functions
|
|
Included observable changes:
|
|
- makes the location of usage warnings and alerts for constructors more
|
|
precise
|
|
- don't warn about a constructor never being used to build values when it
|
|
has been defined as private
|
|
(Leo White, Hugo Heuzard review by Thomas Refis, Florian Angeletti)
|
|
|
|
- #8702, #8777: improved error messages for fixed row polymorphic variants
|
|
(Florian Angeletti, report by Leo White, review by Thomas Refis)
|
|
|
|
- #8844: Printing faulty constructors, inline records fields and their types
|
|
during type mismatches. Also slightly changed other type mismatches error
|
|
output.
|
|
(Mekhrubon Turaev, review by Florian Angeletti, Leo White)
|
|
|
|
- #8885: Warn about unused local modules
|
|
(Thomas Refis, review by Alain Frisch)
|
|
|
|
- #8872: Add ocamlc option "-output-complete-exe" to build a self-contained
|
|
binary for bytecode programs, containing the runtime and C stubs.
|
|
(Stéphane Glondu, Nicolás Ojeda Bär, review by Jérémie Dimino and Daniel
|
|
Bünzli)
|
|
|
|
- #8874: add tests for typechecking error messages and pack them into
|
|
pretty-printing boxes.
|
|
(Oxana Kostikova, review by Gabriel Scherer)
|
|
|
|
- #8891: Warn about unused functor parameters
|
|
(Thomas Refis, review by Gabriel Radanne)
|
|
|
|
- #8903: Improve errors for first-class modules
|
|
(Leo White, review by Jacques Garrigue)
|
|
|
|
- #8914: clarify the warning on unboxable types used in external primitives (61)
|
|
(Gabriel Scherer, review by Florian Angeletti, report on the Discourse forum)
|
|
|
|
- #9046: disable warning 30 by default
|
|
This outdated warning complained on label/constructor name conflicts
|
|
within a mutually-recursive type declarations; there is now no need
|
|
to complain thanks to type-based disambiguation.
|
|
(Gabriel Scherer)
|
|
|
|
### Tools:
|
|
|
|
* #6792, #8654 ocamldebug now supports programs using Dynlink. This
|
|
changes ocamldebug messages, which may break compatibility
|
|
with older emacs modes.
|
|
(whitequark and Jacques-Henri Jourdan, review by Gabriel Scherer
|
|
and Xavier Clerc)
|
|
|
|
- #8621: Make ocamlyacc a Windows Unicode application
|
|
(David Allsopp, review by Nicolás Ojeda Bär)
|
|
|
|
* #8834, `ocaml`: adhere to the XDG base directory specification to
|
|
locate an `.ocamlinit` file. Reads an `$XDG_CONFIG_HOME/ocaml/init.ml`
|
|
file before trying to lookup `~/.ocamlinit`. On Windows the behaviour
|
|
is unchanged.
|
|
(Daniel C. Bünzli, review by David Allsopp, Armaël Guéneau and
|
|
Nicolás Ojeda Bär)
|
|
|
|
- #9113: ocamldoc: fix the rendering of multi-line code blocks
|
|
in the 'man' backend.
|
|
(Gabriel Scherer, review by Florian Angeletti)
|
|
|
|
- #9127, #9130: ocamldoc: fix the formatting of closing brace in record types.
|
|
(David Allsopp, report by San Vu Ngoc)
|
|
|
|
- #9181: make objinfo work on Cygwin and look for the caml_plugin_header
|
|
symbol in both the static and the dynamic symbol tables.
|
|
(Sébastien Hinderer, review by Gabriel Scherer and David Allsopp)
|
|
|
|
### Build system:
|
|
|
|
- #8840: use ocaml{c,opt}.opt when available to build internal tools
|
|
On my machine this reduces parallel-build times from 3m30s to 2m50s.
|
|
(Gabriel Scherer, review by Xavier Leroy and Sébastien Hinderer)
|
|
|
|
- #8650: ensure that "make" variables are defined before use;
|
|
revise generation of config/util.ml to better quote special characters
|
|
(Xavier Leroy, review by David Allsopp)
|
|
|
|
- #8690, #8696: avoid rebuilding the world when files containing primitives
|
|
change.
|
|
(Stephen Dolan, review by Gabriel Scherer, Sébastien Hinderer and
|
|
Thomas Refis)
|
|
|
|
- #8835: new configure option --disable-stdlib-manpages to disable building
|
|
and installation of the library manpages.
|
|
(David Allsopp, review by Florian Angeletti and Gabriel Scherer)
|
|
|
|
- #8837: build manpages using ocamldoc.opt when available
|
|
cuts the manpages build time from 14s to 4s
|
|
(Gabriel Scherer, review by David Allsopp and Sébastien Hinderer,
|
|
report by David Allsopp)
|
|
|
|
- #8843, #8841: fix use of off_t on 32-bit systems.
|
|
(Stephen Dolan, report by Richard Jones, review by Xavier Leroy)
|
|
|
|
- #8947, #9134, #9302, #9311: fix/improve support for the BFD library
|
|
(Sébastien Hinderer, review by Damien Doligez and David Allsopp)
|
|
|
|
- #8951: let make's default target build the compiler
|
|
(Sébastien Hinderer, review by David Allsopp)
|
|
|
|
- #8995: allow developers to specify frequently-used configure options in
|
|
Git (ocaml.configure option) and a directory for host-specific, shareable
|
|
config.cache files (ocaml.configure-cache option). See HACKING.adoc for
|
|
further details.
|
|
(David Allsopp, review by Gabriel Scherer)
|
|
|
|
- #9136: Don't propagate Cygwin-style prefix from configure to
|
|
Makefile.config on Windows ports.
|
|
(David Allsopp, review by Sébastien Hinderer)
|
|
|
|
### Internal/compiler-libs changes:
|
|
|
|
- #8828: Added abstractions for variants, records, constructors, fields and
|
|
extension constructor types mismatch.
|
|
(Mekhrubon Turaev, review by Florian Angeletti, Leo White and Gabriel Scherer)
|
|
|
|
- #7927, #8527: Replace long tuples into records in typeclass.ml
|
|
(Ulugbek Abdullaev, review by David Allsopp and Gabriel Scherer)
|
|
|
|
- #1963: split cmmgen into generic Cmm helpers and clambda transformations
|
|
(Vincent Laviron, review by Mark Shinwell)
|
|
|
|
- #1901: Fix lexing of character literals in comments
|
|
(Pieter Goetschalckx, review by Damien Doligez)
|
|
|
|
- #1932: Allow octal escape sequences and identifiers containing apostrophes
|
|
in ocamlyacc actions and comments.
|
|
(Pieter Goetschalckx, review by Damien Doligez)
|
|
|
|
- #2288: Move middle end code from [Asmgen] to [Clambda_middle_end] and
|
|
[Flambda_middle_end]. Run [Un_anf] from the middle end, not [Cmmgen].
|
|
(Mark Shinwell, review by Pierre Chambart)
|
|
|
|
- #8692: Remove Misc.may_map and similar
|
|
(Leo White, review by Gabriel Scherer and Thomas Refis)
|
|
|
|
- #8677: Use unsigned comparisons in amd64 and i386 emitter of Lcondbranch3.
|
|
(Greta Yorsh, review by Xavier Leroy)
|
|
|
|
- #8766: Parmatch: introduce a type for simplified pattern heads
|
|
(Gabriel Scherer and Thomas Refis, review by Stephen Dolan and
|
|
Florian Angeletti)
|
|
|
|
- #8774: New implementation of Env.make_copy_of_types
|
|
(Alain Frisch, review by Thomas Refis, Leo White and Jacques Garrigue)
|
|
|
|
- #7924: Use a variant instead of an int in Bad_variance exception
|
|
(Rian Douglas, review by Gabriel Scherer)
|
|
|
|
- #8890: in -dtimings output, show time spent in C linker clearly
|
|
(Valentin Gatien-Baron)
|
|
|
|
- #8910, #8911: minor improvements to the printing of module types
|
|
(Gabriel Scherer, review by Florian Angeletti)
|
|
|
|
- #8913: ocamltest: improve 'promote' implementation to take
|
|
skipped lines/bytes into account
|
|
(Gabriel Scherer, review by Sébastien Hinderer)
|
|
|
|
- #8908: Use an option instead of a string for module names ("_" becomes None),
|
|
and a dedicated type for functor parameters: "()" maps to "Unit" (instead of
|
|
"*").
|
|
(Thomas Refis, review by Gabriel Radanne)
|
|
|
|
- #8928: Move contains_calls and num_stack_slots from Proc to Mach.fundecl
|
|
(Greta Yorsh, review by Florian Angeletti and Vincent Laviron)
|
|
|
|
- #8959, #8960, #8968, #9023: minor refactorings in the typing of patterns:
|
|
+ refactor the {let,pat}_bound_idents* functions
|
|
+ minor bugfix in type_pat
|
|
+ refactor the generic pattern-traversal functions
|
|
in Typecore and Typedtree
|
|
+ restrict the use of Need_backtrack
|
|
(Gabriel Scherer and Florian Angeletti,
|
|
review by Thomas Refis and Gabriel Scherer)
|
|
|
|
- #9030: clarify and document the parameter space of type_pat
|
|
(Gabriel Scherer and Florian Angeletti and Jacques Garrigue,
|
|
review by Florian Angeletti and Thomas Refis)
|
|
|
|
- #8975: "ocamltests" files are no longer required or used by
|
|
"ocamltest". Instead, any text file in the testsuite directory containing a
|
|
valid "TEST" block will be automatically included in the testsuite.
|
|
(Nicolás Ojeda Bär, review by Gabriel Scherer and Sébastien Hinderer)
|
|
|
|
- #8992: share argument implementations between executables
|
|
(Florian Angeletti, review by Gabriel Scherer)
|
|
|
|
- #9015: fix fatal error in pprint_ast (#8789)
|
|
(Damien Doligez, review by Thomas Refis)
|
|
|
|
### Bug fixes:
|
|
|
|
- #5673, #7636: unused type variable causes generalization error
|
|
(Jacques Garrigue and Leo White, review by Leo White,
|
|
reports by Jean-Louis Giavitto and Christophe Raffalli)
|
|
|
|
- #6922, #8955: Fix regression with -principal type inference for inherited
|
|
methods, allowing to compile ocamldoc with -principal
|
|
(Jacques Garrigue, review by Leo White)
|
|
|
|
- #7925, #8611: fix error highlighting for exceptionally
|
|
long toplevel phrases
|
|
(Kyle Miller, reported by Armaël Guéneau, review by Armaël Guéneau
|
|
and Nicolás Ojeda Bär)
|
|
|
|
- #8622: Don't generate #! headers over 127 characters.
|
|
(David Allsopp, review by Xavier Leroy and Stephen Dolan)
|
|
|
|
- #8715: minor bugfixes in CamlinternalFormat; removes the unused
|
|
and misleading function CamlinternalFormat.string_of_formatting_gen
|
|
(Gabriel Scherer and Florian Angeletti,
|
|
review by Florian Angeletti and Gabriel Radanne)
|
|
|
|
- #8792, #9018: Possible (latent) bug in Ctype.normalize_type
|
|
removed incrimined Btype.log_type, replaced by Btype.set_type
|
|
(Jacques Garrigue, report by Alain Frisch, review by Thomas Refis)
|
|
|
|
- #8856, #8860: avoid stackoverflow when printing cyclic type expressions
|
|
in some error submessages.
|
|
(Florian Angeletti, report by Mekhrubon Turaev, review by Leo White)
|
|
|
|
- #8875: fix missing newlines in the output from MSVC invocation.
|
|
(Nicolás Ojeda Bär, review by Gabriel Scherer)
|
|
|
|
- #8921, #8924: Fix stack overflow with Flambda
|
|
(Vincent Laviron, review by Pierre Chambart and Leo White,
|
|
report by Aleksandr Kuzmenko)
|
|
|
|
- #8892, #8895: fix the definition of Is_young when CAML_INTERNALS is not
|
|
defined.
|
|
(David Allsopp, review by Xavier Leroy)
|
|
|
|
- #8896: deprecate addr typedef in misc.h
|
|
(David Allsopp, suggestion by Xavier Leroy)
|
|
|
|
- #8981: Fix check for incompatible -c and -o options.
|
|
(Greta Yorsh, review by Damien Doligez)
|
|
|
|
- #9019, #9154: Unsound exhaustivity of GADTs from incomplete unification
|
|
Also fixes bug found by Thomas Refis in #9012
|
|
(Jacques Garrigue, report and review by Leo White, Thomas Refis)
|
|
|
|
- #9031: Unregister Windows stack overflow handler while shutting
|
|
the runtime down.
|
|
(Dmitry Bely, review by David Allsopp)
|
|
|
|
- #9051: fix unregistered local root in win32unix/select.c (could result in
|
|
`select` returning file_descr-like values which weren't in the original sets)
|
|
and correct initialisation of some blocks allocated with caml_alloc_small.
|
|
(David Allsopp, review by Xavier Leroy)
|
|
|
|
- #9073, #9120: fix incorrect GC ratio multiplier when allocating custom blocks
|
|
with caml_alloc_custom_mem in runtime/custom.c
|
|
(Markus Mottl, review by Gabriel Scherer and Damien Doligez)
|
|
|
|
- #9209, #9212: fix a development-version regression caused by #2288
|
|
(Kate Deplaix and David Allsopp, review by Sébastien Hinderer
|
|
and Gabriel Scherer )
|
|
|
|
- #9218, #9269: avoid a rare wrong module name error with "-annot" and
|
|
inline records.
|
|
(Florian Angeletti, review by Gabriel Scherer, report by Kate Deplaix)
|
|
|
|
- #9261: Fix a soundness bug in Rec_check, new in 4.10 (from #8908)
|
|
(Vincent Laviron, review by Jeremy Yallop and Gabriel Scherer)
|
|
|
|
OCaml 4.09 maintenance branch
|
|
-----------------------------
|
|
|
|
### Build system:
|
|
|
|
- #9383: Don't assume that AWKPATH includes .
|
|
(David Allsopp, report by Ian Zimmerman)
|
|
|
|
OCaml 4.09.1 (16 Mars 2020)
|
|
---------------------------
|
|
|
|
- #8855, #8858: Links for tools not created when installing with
|
|
--disable-installing-byecode-programs (e.g. ocamldep.opt installed, but
|
|
ocamldep link not created)
|
|
(David Allsopp, report by Thomas Leonard)
|
|
|
|
- #8953, #8954: Fix error submessages in the toplevel: do not display
|
|
dummy locations
|
|
(Armaël Guéneau, review by Gabriel Scherer)
|
|
|
|
- #8965, #8979: Alpine build failure caused by check-parser-uptodate-or-warn.sh
|
|
(Gabriel Scherer and David Allsopp, report by Anton Kochkov)
|
|
|
|
- #8985, #8986: fix generation of the primitives when the locale collation is
|
|
incompatible with C.
|
|
(David Allsopp, review by Nicolás Ojeda Bär, report by Sebastian Rasmussen)
|
|
|
|
- #9050, #9076: install missing compilerlibs/ocamlmiddleend archives
|
|
(Gabriel Scherer, review by Florian Angeletti, report by Olaf Hering)
|
|
|
|
- #9180: pass -fno-common option to C compiler when available,
|
|
so as to detect problematic multiple definitions of global variables
|
|
in the C runtime
|
|
(Xavier Leroy, review by Mark Shinwell)
|
|
|
|
- #9144, #9180: multiple definitions of global variables in the C runtime,
|
|
causing problems with GCC 10.0 and possibly with other C compilers
|
|
(Xavier Leroy, report by Jürgen Reuter, review by Mark Shinwell)
|
|
|
|
- #9128: Fix a bug in bytecode mode which could lead to a segmentation
|
|
fault. The bug was caused by the fact that the atom table shared a
|
|
page with some bytecode. The fix makes sure both the atom table and
|
|
the minor heap have their own pages.
|
|
(Jacques-Henri Jourdan, review by Stephen Dolan, Xavier Leroy and
|
|
Gabriel Scherer)
|
|
|
|
OCaml 4.09.0 (19 September 2019)
|
|
--------------------------------
|
|
|
|
### Runtime system:
|
|
|
|
* #1725, #2279: Deprecate Obj.set_tag and Obj.truncate
|
|
(Stephen Dolan, review by Gabriel Scherer, Damien Doligez and Xavier Leroy)
|
|
|
|
* #2240: Constify "identifier" in struct custom_operations
|
|
(Cedric Cellier, review by Xavier Leroy)
|
|
|
|
* #2293: Constify "caml_named_value"
|
|
(Stephen Dolan, review by Xavier Leroy)
|
|
|
|
- #8787, #8788: avoid integer overflow in caml_output_value_to_bytes
|
|
(Jeremy Yallop, report by Marcello Seri)
|
|
|
|
|
|
- #2075, #7729: rename _T macro used to support Unicode in the (Windows) runtime
|
|
in order to avoid compiler warning
|
|
(Nicolás Ojeda Bär, review by Gabriel Scherer and David Allsopp)
|
|
|
|
- #2250: Remove extra integer sign-extension in compare functions
|
|
(Stefan Muenzel, review by Xavier Leroy)
|
|
|
|
- #8607: Remove obsolete macros for pre-2002 MSVC support
|
|
(Stephen Dolan, review by Nicolás Ojeda Bär and David Allsopp)
|
|
|
|
- #8656: Fix a bug in [caml_modify_generational_global_root]
|
|
(Jacques-Henri Jourdan, review by Gabriel Scherer)
|
|
|
|
### Standard library:
|
|
|
|
- #2262: take precision (.<n>) and flags ('+' and ' ') into account
|
|
in printf %F
|
|
(Pierre Roux, review by Gabriel Scherer)
|
|
|
|
- #6148, #8596: optimize some buffer operations
|
|
(Damien Doligez, reports by John Whitington and Alain Frisch,
|
|
review by Jeremy Yallop and Gabriel Scherer)
|
|
|
|
### Other libraries:
|
|
|
|
* #2318: Delete the graphics library. This library is now available
|
|
as a separate "graphics" package in opam. Its new home is:
|
|
https://github.com/ocaml/graphics
|
|
(Jérémie Dimino, review by Nicolás Ojeda Bär, Xavier Leroy and
|
|
Sébastien Hinderer)
|
|
|
|
* #2289: Delete the vmthreads library. This library was deprecated in 4.08.0.
|
|
(Jérémie Dimino)
|
|
|
|
- #2112: Fix Thread.yield unfairness with busy threads yielding to each
|
|
other.
|
|
(Andrew Hunter, review by Jacques-Henri Jourdan, Spiros Eliopoulos, Stephen
|
|
Weeks, & Mark Shinwell)
|
|
|
|
- #7903, #2306: Make Thread.delay interruptible by signals again
|
|
(Xavier Leroy, review by Jacques-Henri Jourdan and Edwin Török)
|
|
|
|
- #2248: Unix alloc_sockaddr: Fix read of uninitialized memory for an
|
|
unbound Unix socket. Add support for receiving abstract (Linux) socket paths.
|
|
(Tim Cuthbertson, review by Sébastien Hinderer and Jérémie Dimino)
|
|
|
|
### Compiler user-interface and warnings:
|
|
|
|
* #2276: Remove support for compiler plugins and hooks (also adds
|
|
[Dynlink.unsafe_get_global_value])
|
|
(Mark Shinwell, Xavier Clerc, review by Nicolás Ojeda Bär,
|
|
Florian Angeletti, David Allsopp and Xavier Leroy)
|
|
|
|
- #2301: Hint on type error on int literal
|
|
(Jules Aguillon, review by Nicolás Ojeda Bär , Florian Angeletti,
|
|
Gabriel Scherer and Armaël Guéneau)
|
|
|
|
* #2314: Remove support for gprof profiling.
|
|
(Mark Shinwell, review by Xavier Clerc and Stephen Dolan)
|
|
|
|
- #2190: fix pretty printing (using Pprintast) of "lazy ..." patterns and
|
|
"fun (type t) -> ..." expressions.
|
|
(Nicolás Ojeda Bär, review by Gabriel Scherer)
|
|
|
|
- #2277: Use newtype names as type variable names
|
|
The inferred type of (fun (type t) (x : t) -> x)
|
|
is now printed as ('t -> 't) rather than ('a -> 'a).
|
|
(Matthew Ryan)
|
|
|
|
|
|
- #2309: New options -with-runtime and -without-runtime in ocamlopt/ocamlc
|
|
that control the inclusion of the runtime system in the generated program.
|
|
(Lucas Pluvinage, review by Daniel Bünzli, Damien Doligez, David Allsopp
|
|
and Florian Angeletti)
|
|
|
|
- #3819, #8546 more explanations and tests for illegal permutation
|
|
(Florian Angeletti, review by Gabriel Scherer)
|
|
|
|
- #8537: fix the -runtime-variant option for bytecode
|
|
(Damien Doligez, review by David Allsopp)
|
|
|
|
- #8541: Correctly print multi-lines locations
|
|
(Louis Roché, review by Gabriel Scherer)
|
|
|
|
- #8579: Better error message for private constructors
|
|
of an extensible variant type
|
|
(Guillaume Bury, review by many fine eyes)
|
|
|
|
### Code generation and optimizations:
|
|
|
|
- #2278: Remove native code generation support for 32-bit Intel macOS,
|
|
iOS and other Darwin targets.
|
|
(Mark Shinwell, review by Nicolás Ojeda Bär and Xavier Leroy)
|
|
|
|
- #8547: Optimize matches that are an affine function of the input.
|
|
(Stefan Muenzel, review by Alain Frisch, Gabriel Scherer)
|
|
|
|
|
|
- #1904, #7931: Add FreeBSD/aarch64 support
|
|
(Greg V, review by Sébastien Hinderer, Stephen Dolan, Damien Doligez
|
|
and Xavier Leroy)
|
|
|
|
- #8507: Shorten symbol names of anonymous functions in Flambda mode
|
|
(the directory portions are now hidden)
|
|
(Mark Shinwell, review by Nicolás Ojeda Bär)
|
|
|
|
- #8681, #8699, #8712: Fix code generation with nested let rec of functions.
|
|
(Stephen Dolan, Leo White, Gabriel Scherer and Pierre Chambart,
|
|
review by Gabriel Scherer, reports by Alexey Solovyev and Jonathan French)
|
|
|
|
### Manual and documentation:
|
|
|
|
- #7584, #8538: Document .cmt* files in the "overview" of ocaml{c,opt}
|
|
(Oxana Kostikova, rewiew by Florian Angeletti)
|
|
|
|
|
|
- #8757: Rename Pervasives to Stdlib in core library documentation.
|
|
(Ian Zimmerman, review by David Allsopp)
|
|
|
|
- #8515: manual, precise constraints on reexported types
|
|
(Florian Angeletti, review by Gabriel Scherer)
|
|
|
|
### Tools:
|
|
|
|
- #2221: ocamldep will now correctly allow a .ml file in an include directory
|
|
that appears first in the search order to shadow a .mli appearing in a later
|
|
include directory.
|
|
(Nicolás Ojeda Bär, review by Florian Angeletti)
|
|
|
|
### Internal/compiler-libs changes:
|
|
|
|
- #1579: Add a separate types for clambda primitives
|
|
(Pierre Chambart, review by Vincent Laviron and Mark Shinwell)
|
|
|
|
- #1965: remove loop constructors in Cmm and Mach
|
|
(Vincent Laviron)
|
|
|
|
- #1973: fix compilation of catches with multiple handlers
|
|
(Vincent Laviron)
|
|
|
|
- #2228, #8545: refactoring the handling of .cmi files
|
|
by moving the logic from Env to a new module Persistent_env
|
|
(Gabriel Scherer, review by Jérémie Dimino and Thomas Refis)
|
|
|
|
- #2229: Env: remove prefix_idents cache
|
|
(Thomas Refis, review by Frédéric Bour and Gabriel Scherer)
|
|
|
|
- #2237, #8582: Reorder linearisation of Trywith to avoid a call instruction
|
|
(Vincent Laviron and Greta Yorsh, additional review by Mark Shinwell;
|
|
fix in #8582 by Mark Shinwell, Xavier Leroy and Anil Madhavapeddy)
|
|
|
|
- #2265: Add bytecomp/opcodes.mli
|
|
(Mark Shinwell, review by Nicolás Ojeda Bär)
|
|
|
|
- #2268: Improve packing mechanism used for building compilerlibs modules
|
|
into the Dynlink libraries
|
|
(Mark Shinwell, Stephen Dolan, review by David Allsopp)
|
|
|
|
- #2280: Don't make more Clambda constants after starting Cmmgen
|
|
(Mark Shinwell, review by Vincent Laviron)
|
|
|
|
- #2281: Move some middle-end files around
|
|
(Mark Shinwell, review by Pierre Chambart and Vincent Laviron)
|
|
|
|
- #2283: Add [is_prefix] and [find_and_chop_longest_common_prefix] to
|
|
[Misc.Stdlib.List]
|
|
(Mark Shinwell, review by Alain Frisch and Stephen Dolan)
|
|
|
|
- #2284: Add various utility functions to [Misc] and remove functions
|
|
from [Misc.Stdlib.Option] that are now in [Stdlib.Option]
|
|
(Mark Shinwell, review by Thomas Refis)
|
|
|
|
- #2286: Functorise [Consistbl]
|
|
(Mark Shinwell, review by Gabriel Radanne)
|
|
|
|
- #2291: Add [Compute_ranges] pass
|
|
(Mark Shinwell, review by Vincent Laviron)
|
|
|
|
- #2292: Add [Proc.frame_required] and [Proc.prologue_required].
|
|
Move tail recursion label creation to [Linearize]. Correctly position
|
|
[Lprologue] relative to [Iname_for_debugger] operations.
|
|
(Mark Shinwell, review by Vincent Laviron)
|
|
|
|
- #2308: More debugging information on [Cmm] terms
|
|
(Mark Shinwell, review by Stephen Dolan)
|
|
|
|
- #7878, #8542: Replaced TypedtreeIter with tast_iterator
|
|
(Isaac "Izzy" Avram, review by Gabriel Scherer and Nicolás Ojeda Bär)
|
|
|
|
- #8598: Replace "not is_nonexpansive" by "maybe_expansive".
|
|
(Thomas Refis, review by David Allsopp, Florian Angeletti, Gabriel Radanne,
|
|
Gabriel Scherer and Xavier Leroy)
|
|
|
|
### Compiler distribution build system:
|
|
|
|
- #2267: merge generation of header programs, also fixing parallel build on
|
|
Cygwin.
|
|
(David Allsopp, review by Sébastien Hinderer)
|
|
|
|
- #8514: Use boot/ocamlc.opt for building, if available.
|
|
(Stephen Dolan, review by Gabriel Scherer)
|
|
|
|
### Bug fixes:
|
|
|
|
- #8864, #8865: Fix native compilation of left shift by (word_size - 1)
|
|
(Vincent Laviron, report by Murilo Giacometti Rocha, review by Xavier Leroy)
|
|
|
|
- #2296: Fix parsing of hexadecimal floats with underscores in the exponent.
|
|
(Hugo Heuzard and Xavier Leroy, review by Gabriel Scherer)
|
|
|
|
- #8800: Fix soundness bug in extension constructor inclusion
|
|
(Leo White, review by Jacques Garrigue)
|
|
|
|
- #8848: Fix x86 stack probe CFI information in caml_c_call and
|
|
caml_call_gc
|
|
(Tom Kelly, review by Xavier Leroy)
|
|
|
|
|
|
- #7156, #8594: make top level use custom printers if they are available
|
|
(Andrew Litteken, report by Martin Jambon, review by Nicolás Ojeda Bär,
|
|
Thomas Refis, Armaël Guéneau, Gabriel Scherer, David Allsopp)
|
|
|
|
- #3249: ocamlmklib should reject .cmxa files
|
|
(Xavier Leroy)
|
|
|
|
- #7937, #2287: fix uncaught Unify exception when looking for type
|
|
declaration
|
|
(Florian Angeletti, review by Jacques Garrigue)
|
|
|
|
- #8610, #8613: toplevel printing, consistent deduplicated name for types
|
|
(Florian Angeletti, review by Thomas Refis and Gabriel Scherer,
|
|
reported by Xavier Clerc)
|
|
|
|
- #8635, #8636: Fix a bad side-effect of the -allow-approx option of
|
|
ocamldep. It used to turn some errors into successes
|
|
(Jérémie Dimino)
|
|
|
|
- #8701, #8725: Variance of constrained parameters causes principality issues
|
|
(Jacques Garrigue, report by Leo White, review by Gabriel Scherer)
|
|
|
|
- #8777(partial): fix position information in some polymorphic variant
|
|
error messages about missing tags
|
|
(Florian Angeletti, review by Thomas Refis)
|
|
|
|
- #8779, more cautious variance computation to avoid missing cmis
|
|
(Florian Angeletti, report by Antonio Nuno Monteiro, review by Leo White)
|
|
|
|
- #8810: Env.lookup_module: don't allow creating loops
|
|
(Thomas Refis, report by Leo White, review by Jacques Garrigue)
|
|
|
|
- #8862, #8871: subst: preserve scopes
|
|
(Thomas Refis, report by Leo White, review by Jacques Garrigue)
|
|
|
|
- #8921, #8924: Fix stack overflow with Flambda
|
|
(Vincent Laviron, review by Pierre Chambart and Leo White,
|
|
report by Aleksandr Kuzmenko)
|
|
|
|
- #8944: Fix "open struct .. end" on clambda backend
|
|
(Thomas Refis, review by Leo White, report by Damon Wang and Mark Shinwell)
|
|
|
|
OCaml 4.08.1 (5 August 2019)
|
|
----------------------------
|
|
|
|
### Bug fixes:
|
|
|
|
- #7887: ensure frame table is 8-aligned on ARM64 and PPC64
|
|
(Xavier Leroy, report by Mark Hayden, review by Mark Shinwell
|
|
and Gabriel Scherer)
|
|
|
|
- #8751: fix bug that could result in misaligned data section when compiling to
|
|
native-code on amd64. (observed with the mingw64 compiler)
|
|
(Nicolás Ojeda Bär, review by David Allsopp)
|
|
|
|
- #8769, #8770: Fix assertion failure with -pack
|
|
(Leo White, review by Gabriel Scherer, report by Fabian @copy)
|
|
|
|
- #8816, #8818: fix loading of packed modules with Dynlink (regression in
|
|
#2176).
|
|
(Leo White, report by Andre Maroneze, review by Gabriel Scherer)
|
|
|
|
- #8830: configure script: fix tool prefix detection and Debian's armhf
|
|
detection
|
|
(Stéphane Glondu, review by David Allsopp)
|
|
|
|
- #8843, #8841: fix use of off_t on 32-bit systems.
|
|
(Stephen Dolan, report by Richard Jones, review by Xavier Leroy)
|
|
|
|
OCaml 4.08.0 (13 June 2019)
|
|
---------------------------
|
|
|
|
### Language features:
|
|
|
|
- #1947: Introduce binding operators (let*, let+, and* etc.)
|
|
(Leo White, review by Thomas Refis)
|
|
|
|
- #1892: Allow shadowing of items coming from an include
|
|
(Thomas Refis, review by Gabriel Radanne)
|
|
|
|
- #2122: Introduce local substitutions in signatures: "type t := type_expr"
|
|
and "module M := Extended(Module).Path"
|
|
(Thomas Refis, with help and review from Leo White, and Alain Frisch)
|
|
|
|
- #1804: New notion of "alerts" that generalizes the deprecated warning
|
|
[@@ocaml.alert deprecated "Please use bar instead!"]
|
|
[@@ocaml.alert unsafe "Please use safe_foo instead!"]
|
|
(Alain Frisch, review by Leo White and Damien Doligez)
|
|
|
|
- #6422, #7083, #305, #1568: Allow `exception` under or-patterns
|
|
(Thomas Refis, with help and review from Alain Frisch, Gabriel Scherer, Jeremy
|
|
Yallop, Leo White and Luc Maranget)
|
|
|
|
|
|
- #1705: Allow @@attributes on exception declarations.
|
|
(Hugo Heuzard, review by Gabriel Radanne and Thomas Refis)
|
|
|
|
- #1506, #2147, #2166, #2167: Extended `open` to arbitrary module
|
|
expression in structures and to applicative paths in signatures
|
|
(Runhang Li, review by Alain Frisch, Florian Angeletti, Jeremy Yallop,
|
|
Leo White and Thomas Refis)
|
|
|
|
* #2106: .~ is now a reserved keyword, and is no longer available
|
|
for use in extended indexing operators
|
|
(Jeremy Yallop, review by Gabriel Scherer, Florian Angeletti, and
|
|
Damien Doligez)
|
|
|
|
* #7841, #2041, #2235: allow modules from include directories
|
|
to shadow other ones, even in the toplevel; for a example, including
|
|
a directory that defines its own Result module will shadow the stdlib's.
|
|
(Jérémie Dimino, review by Alain Frisch and David Allsopp)
|
|
|
|
### Type system:
|
|
|
|
- #2110: Partial support for GADTs inside or-patterns;
|
|
The type equalities introduced by the GADT constructor are only
|
|
available inside the or-pattern; they cannot be used in the
|
|
right-hand-side of the clause, when both sides of the or-pattern
|
|
agree on it.
|
|
(Thomas Refis and Leo White, review by Jacques Garrigue)
|
|
|
|
- #1826: allow expanding a type to a private abbreviation instead of
|
|
abstracting when removing references to an identifier.
|
|
(Thomas Refis and Leo White, review by Jacques Garrigue)
|
|
|
|
- #1942, #2244: simplification of the static check
|
|
for recursive definitions
|
|
(Alban Reynaud and Gabriel Scherer,
|
|
review by Jeremy Yallop, Armaël Guéneau and Damien Doligez)
|
|
|
|
### Standard library:
|
|
|
|
- #2128: Add Fun module: `id, const, flip, negate, protect`
|
|
(protect is a "try_finally" combinator)
|
|
https://caml.inria.fr/pub/docs/manual-ocaml/libref/Fun.html
|
|
(Many fine eyes)
|
|
|
|
- #2010: Add Bool module
|
|
https://caml.inria.fr/pub/docs/manual-ocaml/libref/Bool.html
|
|
(Many fine eyes)
|
|
|
|
- #2011: Add Int module
|
|
https://caml.inria.fr/pub/docs/manual-ocaml/libref/Int.html
|
|
(Many fine eyes)
|
|
|
|
- #1940: Add Option module and Format.pp_print_option
|
|
`none, some, value, get, bind, join, map, fold, iter`, etc.
|
|
https://caml.inria.fr/pub/docs/manual-ocaml/libref/Option.html
|
|
(Many fine eyes)
|
|
|
|
- #1956: Add Result module and Format.pp_print_result
|
|
`ok, error, value, get_ok, bind, join, map, map_error`, etc.
|
|
https://caml.inria.fr/pub/docs/manual-ocaml/libref/Result.html
|
|
(Many fine eyes)
|
|
|
|
- #1855, #2118: Add `Fun.protect ~finally` for enforcing local
|
|
invariants whether a function raises or not, similar to
|
|
`unwind-protect` in Lisp and `FINALLY` in Modula-2. It is careful
|
|
about preserving backtraces and treating exceptions in finally as
|
|
errors.
|
|
(Marcello Seri and Guillaume Munch-Maccagnoni, review by Daniel
|
|
Bünzli, Gabriel Scherer, François Bobot, Nicolás Ojeda Bär, Xavier
|
|
Clerc, Boris Yakobowski, Damien Doligez, and Xavier Leroy)
|
|
|
|
* #1605: Deprecate Stdlib.Pervasives. Following #1010, Pervasives
|
|
is no longer needed and Stdlib should be used instead.
|
|
(Jérémie Dimino, review by Nicolás Ojeda Bär)
|
|
|
|
- #2185: Add `List.filter_map`
|
|
(Thomas Refis, review by Alain Frisch and Gabriel Scherer)
|
|
|
|
- #1957: Add Stack.{top_opt,pop_opt} and Queue.{peek_opt,take_opt}.
|
|
(Vladimir Keleshev, review by Nicolás Ojeda Bär and Gabriel Scherer)
|
|
|
|
- #1182: Add new Printf formats %#d %#Ld %#ld %#nd (idem for %i and %u) for
|
|
alternative integer formatting -- inserts '_' between blocks of digits.
|
|
(ygrek, review by Gabriel Scherer)
|
|
|
|
- #1959: Add Format.dprintf, a printing function which outputs a closure
|
|
usable with %t.
|
|
(Gabriel Radanne, request by Armaël Guéneau,
|
|
review by Florian Angeletti and Gabriel Scherer)
|
|
|
|
- #1986, #6450: Add Set.disjoint
|
|
(Nicolás Ojeda Bär, review by Gabriel Scherer)
|
|
|
|
- #7812, #2125: Add Filename.chop_suffix_opt
|
|
(Alain Frisch, review by Nicolás Ojeda Bär, suggestion by whitequark)
|
|
|
|
- #1864: Extend Bytes and Buffer with functions to read/write
|
|
binary representations of numbers
|
|
(Alain Frisch and Daniel Bünzli)
|
|
|
|
- #1458: Add unsigned operations unsigned_div, unsigned_rem, unsigned_compare
|
|
and unsigned_to_int to modules Int32, Int64, Nativeint.
|
|
(Nicolás Ojeda Bär, review by Daniel Bünzli, Alain Frisch and Max Mouratov)
|
|
|
|
- #2002: Add Format.pp_print_custom_break, a new more general kind of break
|
|
hint that can emit non-whitespace characters.
|
|
(Vladimir Keleshev and Pierre Weis, review by Josh Berdine, Gabriel Radanne)
|
|
|
|
- #1966: Add Format semantic tags using extensible sum types.
|
|
(Gabriel Radanne, review by Nicolás Ojeda Bär)
|
|
|
|
- #1794: Add constants zero, one, minus_one and functions succ,
|
|
pred, is_finite, is_infinite, is_nan, is_integer, trunc, round,
|
|
next_after, sign_bit, min, max, min_max, min_num, max_num,
|
|
min_max_num to module Float.
|
|
(Christophe Troestler, review by Alain Frisch, Xavier Clerc and Daniel Bünzli)
|
|
|
|
- #1354, #2177: Add fma support to Float module.
|
|
(Laurent Thévenoux, review by Alain Frisch, Jacques-Henri Jourdan,
|
|
Xavier Leroy)
|
|
|
|
|
|
|
|
- #5072, #6655, #1876: add aliases in Stdlib for built-in types
|
|
and exceptions.
|
|
(Jeremy Yallop, reports by Pierre Letouzey and David Sheets,
|
|
review by Valentin Gatien-Baron, Gabriel Scherer and Alain Frisch)
|
|
|
|
- #1731: Format, use raise_notrace to preserve backtraces.
|
|
(Frédéric Bour, report by Jules Villard, review by Gabriel Scherer)
|
|
|
|
- #6701, #1185, #1803: make float_of_string and string_of_float
|
|
locale-independent.
|
|
(ygrek, review by Xavier Leroy and Damien Doligez)
|
|
|
|
- #7795, #1782: Fix off-by-one error in Weak.create.
|
|
(KC Sivaramakrishnan, review by Gabriel Scherer and François Bobot)
|
|
|
|
- #7235: Format, flush err_formatter at exit.
|
|
(Pierre Weis, request by Jun Furuse)
|
|
|
|
- #1857, #7812: Remove Sort module, deprecated since 2000 and emitting
|
|
a deprecation warning since 4.02.
|
|
(whitequark)
|
|
|
|
- #1923: Arg module sometimes misbehaved instead of rejecting invalid
|
|
-keyword=arg inputs
|
|
(Valentin Gatien-Baron, review by Gabriel Scherer)
|
|
|
|
- #1959: Small simplification and optimization to Format.ifprintf
|
|
(Gabriel Radanne, review by Gabriel Scherer)
|
|
|
|
- #2119: clarify the documentation of Set.diff
|
|
(Gabriel Scherer, suggestion by John Skaller)
|
|
|
|
- #2145: Deprecate the mutability of Gc.control record fields
|
|
(Damien Doligez, review by Alain Frisch)
|
|
|
|
- #2159, #7874: annotate {String,Bytes}.equal as being [@@noalloc].
|
|
(Pierre-Marie Pédrot, review by Nicolás Ojeda Bär)
|
|
|
|
- #1936: Add module Float.Array
|
|
(Damien Doligez, review by Xavier Clerc and Alain Frisch)
|
|
|
|
- #2183: Fix segfault in Array.create_float with -no-flat-float-array
|
|
(Damien Doligez, review by Gabriel Scherer and Jeremy Yallop)
|
|
|
|
- #1525: Make function set_max_indent respect documentation
|
|
(Pierre Weis, Richard Bonichon, review by Florian Angeletti)
|
|
|
|
- #2202: Correct Hashtbl.MakeSeeded.{add_seq,replace_seq,of_seq} to use
|
|
functor hash function instead of default hash function. Hashtbl.Make.of_seq
|
|
shouldn't create randomized hash tables.
|
|
(David Allsopp, review by Alain Frisch)
|
|
|
|
### Other libraries:
|
|
|
|
- #2533, #1839, #1949: added Unix.fsync
|
|
(Francois Berenger, Nicolás Ojeda Bär, review by Daniel Bünzli, David Allsopp
|
|
and ygrek)
|
|
|
|
- #1792, #7794: Add Unix.open_process_args{,_in,_out,_full} similar to
|
|
Unix.open_process{,_in,_out,_full}, but passing an explicit argv array.
|
|
(Nicolás Ojeda Bär, review by Jérémie Dimino, request by Volker Diels-Grabsch)
|
|
|
|
- #1999: Add Unix.process{,_in,_out,_full}_pid to retrieve opened process's
|
|
pid.
|
|
(Romain Beauxis, review by Nicolás Ojeda Bär)
|
|
|
|
- #2222: Set default status in waitpid when pid is zero. Otherwise,
|
|
status value is undefined.
|
|
(Romain Beauxis and Xavier Leroy, review by Stephen Dolan)
|
|
|
|
* #2104, #2211, #4127, #7709: Fix Thread.sigmask. When
|
|
system threads are loaded, Unix.sigprocmask is now an alias for
|
|
Thread.sigmask. This changes the behavior at least on MacOS, where
|
|
Unix.sigprocmask used to change the masks of all threads.
|
|
(Jacques-Henri Jourdan, review by Jérémie Dimino)
|
|
|
|
- #1061: Add ?follow parameter to Unix.link. This allows hardlinking
|
|
symlinks.
|
|
(Christopher Zimmermann, review by Xavier Leroy, Damien Doligez, David
|
|
Allsopp, David Sheets)
|
|
|
|
- #2038: Deprecate vm threads.
|
|
OCaml supported both "native threads", based on pthreads,
|
|
and its own green-threads implementation, "vm threads". We are not
|
|
aware of any recent usage of "vm threads", and removing them simplifies
|
|
further maintenance.
|
|
(Jérémie Dimino)
|
|
|
|
* #4208, #4229, #4839, #6462, #6957, #6950, #1063, #2176,
|
|
#2297: Make (nat)dynlink sound by correctly failing when
|
|
dynlinked module names clash with other modules or interfaces.
|
|
(Mark Shinwell, Leo White, Nicolás Ojeda Bär, Pierre Chambart)
|
|
|
|
- #2263: Delete the deprecated Bigarray.*.map_file functions in
|
|
favour of `*_of_genarray (Unix.map_file ...)` functions instead. The
|
|
`Unix.map_file` function was introduced in OCaml 4.06.0 onwards.
|
|
(Jérémie Dimino, reviewed by David Allsopp and Anil Madhavapeddy)
|
|
|
|
### Compiler user-interface and warnings:
|
|
|
|
- #2096: Add source highlighting for errors & warnings in batch mode
|
|
(Armaël Guéneau, review by Gabriel Scherer and Jérémie Dimino)
|
|
|
|
- #2133: [@ocaml.warn_on_literal_pattern]: now warn on literal patterns
|
|
found anywhere in a constructor's arguments.
|
|
(Jeremy Yallop, review by Gabriel Scherer)
|
|
|
|
- #1720: Improve error reporting for missing 'rec' in let-bindings.
|
|
(Arthur Charguéraud and Armaël Guéneau, with help and advice
|
|
from Gabriel Scherer, Frédéric Bour, Xavier Clerc and Leo White)
|
|
|
|
- #7116, #1430: new -config-var option
|
|
to get the value of a single configuration variable in scripts.
|
|
(Gabriel Scherer, review by Sébastien Hinderer and David Allsopp,
|
|
request by Adrien Nader)
|
|
|
|
- #1733,1993,1998,2058,2094,2140: Typing error message improvements
|
|
- #1733, change the perspective of the unexpected existential error
|
|
message.
|
|
- #1993, expanded error messages for universal quantification failure
|
|
- #1998, more context for unbound type parameter error
|
|
- #2058, full explanation for unsafe cycles in recursive module
|
|
definitions (suggestion by Ivan Gotovchits)
|
|
- #2094, rewording for "constructor has no type" error
|
|
- #7565, #2140, more context for universal variable escape
|
|
in method type
|
|
(Florian Angeletti, reviews by Jacques Garrigue, Armaël Guéneau,
|
|
Gabriel Radanne, Gabriel Scherer and Jeremy Yallop)
|
|
|
|
- #1913: new flag -dump-into-file to print debug output like -dlambda into
|
|
a file named after the file being built, instead of on stderr.
|
|
(Valentin Gatien-Baron, review by Thomas Refis)
|
|
|
|
- #1921: in the compilation context passed to ppx extensions,
|
|
add more configuration options related to type-checking:
|
|
-rectypes, -principal, -alias-deps, -unboxed-types, -unsafe-string
|
|
(Gabriel Scherer, review by Gabriel Radanne, Xavier Clerc and Frédéric Bour)
|
|
|
|
- #1976: Better error messages for extension constructor type mismatches
|
|
(Thomas Refis, review by Gabriel Scherer)
|
|
|
|
- #1841, #7808: the environment variable OCAMLTOP_INCLUDE_PATH can now
|
|
specify a list of additional include directories for the ocaml toplevel.
|
|
(Nicolás Ojeda Bär, request by Daniel Bünzli, review by Daniel Bünzli and
|
|
Damien Doligez)
|
|
|
|
- #6638, #1110: introduced a dedicated warning to report
|
|
unused "open!" statements
|
|
(Alain Frisch, report by dwang, review by and design from Leo White)
|
|
|
|
- #1974: Trigger warning 5 in "let _ = e" and "ignore e" if e is of function
|
|
type and syntactically an application. (For the case of "ignore e" the warning
|
|
already existed, but used to be triggered even when e was not an application.)
|
|
(Nicolás Ojeda Bär, review by Alain Frisch and Jacques Garrigue)
|
|
|
|
- #7408, #7846, #2015: Check arity of primitives.
|
|
(Hugo Heuzard, review by Nicolás Ojeda Bär)
|
|
|
|
|
|
|
|
- #2091: Add a warning triggered by type declarations "type t = ()"
|
|
(Armaël Guéneau, report by linse, review by Florian Angeletti and Gabriel
|
|
Scherer)
|
|
|
|
- #2004: Use common standard library path `lib/ocaml` for Windows,
|
|
for consistency with OSX & Linux. Previously was located at `lib`.
|
|
(Bryan Phelps, Jordan Walke, review by David Allsopp)
|
|
|
|
- #6416, #1120: unique printed names for identifiers
|
|
(Florian Angeletti, review by Jacques Garrigue)
|
|
|
|
- #1691: add shared_libraries to ocamlc -config exporting
|
|
SUPPORTS_SHARED_LIBRARIES from Makefile.config.
|
|
(David Allsopp, review by Gabriel Scherer and Mark Shinwell)
|
|
|
|
- #6913, #1786: new -match-context-rows option
|
|
to control the degree of optimization in the pattern matching compiler.
|
|
(Dwight Guth, review by Gabriel Scherer and Luc Maranget)
|
|
|
|
- #1822: keep attributes attached to pattern variables from being discarded.
|
|
(Nicolás Ojeda Bär, review by Thomas Refis)
|
|
|
|
- #1845: new `-dcamlprimc` option to keep the generated C file containing
|
|
the information about primitives; pass `-fdebug-prefix-map` to the C compiler
|
|
when supported, for reproducible builds
|
|
(Xavier Clerc, review by Jérémie Dimino)
|
|
|
|
- #1856, #1869: use `BUILD_PATH_PREFIX_MAP` when compiling primitives
|
|
in order to make builds reproducible if code contains uses of
|
|
`__FILE__` or `__LOC__`
|
|
(Xavier Clerc, review by Gabriel Scherer and Sébastien Hinderer)
|
|
|
|
- #1906: the -unsafe option does not apply to marshalled ASTs passed
|
|
to the compiler directly or by a -pp preprocessor; add a proper
|
|
warning (64) instead of a simple stderr message
|
|
(Valentin Gatien-Baron)
|
|
|
|
- #1925: Print error locations more consistently between batch mode, toplevel
|
|
and expect tests
|
|
(Armaël Guéneau, review by Thomas Refis, Gabriel Scherer and François Bobot)
|
|
|
|
- #1930: pass the elements from `BUILD_PATH_PREFIX_MAP` to the assembler
|
|
(Xavier Clerc, review by Gabriel Scherer, Sébastien Hinderer, and
|
|
Xavier Leroy)
|
|
|
|
- #1945, #2032: new "-stop-after [parsing|typing]" option
|
|
to stop compilation after the parsing or typing pass
|
|
(Gabriel Scherer, review by Jérémie Dimino)
|
|
|
|
- #1953: Add locations to attributes in the parsetree.
|
|
(Hugo Heuzard, review by Gabriel Radanne)
|
|
|
|
- #1954: Add locations to toplevel directives.
|
|
(Hugo Heuzard, review by Gabriel Radanne)
|
|
|
|
* #1979: Remove support for TERM=norepeat when displaying errors
|
|
(Armaël Guéneau, review by Gabriel Scherer and Florian Angeletti)
|
|
|
|
- #1960: The parser keeps previous location when relocating ast node.
|
|
(Hugo Heuzard, review by Jérémie Dimino)
|
|
|
|
- #7864, #2109: remove duplicates from spelling suggestions.
|
|
(Nicolás Ojeda Bär, review by Armaël Guéneau)
|
|
|
|
### Manual and documentation:
|
|
|
|
- #7548: printf example in the tutorial part of the manual
|
|
(Kostikova Oxana, rewiew by Gabriel Scherer, Florian Angeletti,
|
|
Marcello Seri and Armaël Guéneau)
|
|
|
|
- #7546, #2020: preambles and introduction for compiler-libs.
|
|
(Florian Angeletti, review by Daniel Bünzli, Perry E. Metzger
|
|
and Gabriel Scherer)
|
|
|
|
- #7547, #2273: Tutorial on Lazy expressions and patterns in OCaml Manual
|
|
(Ulugbek Abdullaev, review by Florian Angeletti and Gabriel Scherer)
|
|
|
|
- #7720, #1596, precise the documentation
|
|
of the maximum indentation limit in Format.
|
|
(Florian Angeletti, review by Richard Bonichon and Pierre Weis)
|
|
|
|
- #7825: html manual split compilerlibs from stdlib in the html
|
|
index of modules
|
|
(Florian Angeletti, review by Perry E. Metzger and Gabriel Scherer)
|
|
|
|
- #1209, #2008: in the Extension section, use the caml_example environment
|
|
(uses the compiler to check the example code).
|
|
This change was made possible by a lot of tooling work from Florian Angeletti:
|
|
#1702, #1765, #1863, and Gabriel Scherer's #1903.
|
|
(Gabriel Scherer, review by Florian Angeletti)
|
|
|
|
- #1788, 1831, 2007, 2198, 2232, move language extensions to the core
|
|
chapters:
|
|
- #1788: quoted string description
|
|
- #1831: local exceptions and exception cases
|
|
- #2007: 32-bit, 64-bit and native integer literals
|
|
- #2198: lazy patterns
|
|
- #2232: short object copy notation
|
|
(Florian Angeletti, review by Xavier Clerc, Perry E. Metzger, Gabriel Scherer
|
|
and Jeremy Yallop)
|
|
|
|
- #1863: caml-tex2, move to compiler-libs
|
|
(Florian Angeletti, review by Sébastien Hinderer and Gabriel Scherer)
|
|
|
|
- #2105: Change verbatim to caml_example in documentation
|
|
(Maxime Flin, review by Florian Angeletti)
|
|
|
|
- #2114: ocamldoc, improved manpages for documentation inside modules
|
|
(Florian Angeletti, review by Gabriel Scherer)
|
|
|
|
- #2117: stdlib documentation, duplicate the operator precedence table
|
|
from the manual inside a separate "OCaml_operators" module.
|
|
(Florian Angeletti, review by Daniel Bünzli, Perry E. Metzger
|
|
and Gabriel Scherer)
|
|
|
|
- #2187: document "exception A | pat" patterns
|
|
(Florian Angeletti, review by Perry E. Metzger and Jeremy Yallop)
|
|
|
|
- #8508: refresh \moduleref macro
|
|
(Florian Angeletti, review by Gabriel Scherer)
|
|
|
|
### Code generation and optimizations:
|
|
|
|
- #7725, #1754: improve AFL instrumentation for objects and lazy values.
|
|
(Stephen Dolan)
|
|
|
|
- #1631: AMD64 code generator: emit shorter instruction sequences for the
|
|
sign-extension operations.
|
|
(LemonBoy, review by Alain Frisch and Xavier Leroy)
|
|
|
|
- #7246, #2146: make a few int64 primitives use [@@unboxed]
|
|
stubs on 32bits
|
|
(Jérémie Dimino)
|
|
|
|
- #1917: comballoc: ensure object allocation order is preserved
|
|
(Stephen Dolan)
|
|
|
|
- #6242, #2143, #8558, #8559: Optimize some local functions.
|
|
Local functions that do not escape and whose calls all have
|
|
the same continuation are lowered into a static-catch handler.
|
|
(Alain Frisch, review by Gabriel Scherer)
|
|
|
|
- #2082: New options [-insn-sched] and [-no-insn-sched] to control
|
|
instruction scheduling.
|
|
(Mark Shinwell, review by Damien Doligez)
|
|
|
|
- #2239: Fix match miscompilation with flambda
|
|
(Leo White, review by Alain Frisch)
|
|
|
|
### Runtime system:
|
|
|
|
- #7198, #7750, #1738: add a function (caml_alloc_custom_mem)
|
|
and three GC parameters to give the user better control of the
|
|
out-of-heap memory retained by custom values; use the function to
|
|
allocate bigarrays and I/O channels.
|
|
(Damien Doligez, review by Alain Frisch)
|
|
|
|
- #1793: add the -m and -M command-line options to ocamlrun.
|
|
Option -m prints the magic number of the bytecode executable passed
|
|
as argument, -M prints the magic number expected by ocamlrun.
|
|
(Sébastien Hinderer, review by Xavier Clerc and Damien Doligez)
|
|
|
|
- #1867: Remove the C plugins mechanism.
|
|
(Xavier Leroy, review by David Allsopp, Damien Doligez, Sébastien Hinderer)
|
|
|
|
- #8627: Require SSE2 for 32-bit mingw port to generate correct code
|
|
for caml_round with GCC 7.4.
|
|
(David Allsopp, review by Xavier Leroy)
|
|
|
|
- #7676, #2144: Remove old GC heuristic
|
|
(Damien Doligez, report and review by Alain Frisch)
|
|
|
|
* #1683: Change Marshal format to make Custom_tag objects store their
|
|
length. Old versions of OCaml will no longer be able to parse new marshalled
|
|
files containing custom blocks, but old files will still parse.
|
|
(Stephen Dolan)
|
|
|
|
- #1723: Remove internal Meta.static_{alloc,free} primitives.
|
|
(Stephen Dolan, review by Gabriel Scherer)
|
|
|
|
- #1895: Printexc.get_callstack would return only one frame in native
|
|
code in threads other then the initial one
|
|
(Valentin Gatien-Baron, review by Xavier Leroy)
|
|
|
|
- #1900, #7814: avoid exporting non-prefixed identifiers in the debug
|
|
and instrumented runtimes.
|
|
(Damien Doligez, report by Gabriel Scherer)
|
|
|
|
- #2079: Avoid page table lookup in Pervasives.compare with
|
|
no-naked-pointers
|
|
(Sam Goldman, review by Gabriel Scherer, David Allsopp, Stephen Dolan)
|
|
|
|
- #7829, #8585: Fix pointer comparisons in freelist.c (for 32-bit platforms)
|
|
(David Allsopp and Damien Doligez)
|
|
|
|
- #8567, #8569: on ARM64, use 32-bit loads to access caml_backtrace_active
|
|
(Xavier Leroy, review by Mark Shinwell and Greta Yorsh)
|
|
|
|
- #8568: Fix a memory leak in mmapped bigarrays
|
|
(Damien Doligez, review by Xavier Leroy and Jérémie Dimino)
|
|
|
|
### Tools
|
|
|
|
- #2182: Split Emacs caml-mode as an independent project.
|
|
(Christophe Troestler, review by Gabriel Scherer)
|
|
|
|
- #1865: support dark themes in Emacs, and clean up usage of
|
|
deprecated Emacs APIs
|
|
(Wilfred Hughes, review by Clément Pit-Claudel)
|
|
|
|
- #1590: ocamllex-generated lexers can be instructed not to update
|
|
their lex_curr_p/lex_start_p fields, resulting in a significant
|
|
performance gain when those fields are not required.
|
|
(Alain Frisch, review by Jérémie Dimino)
|
|
|
|
- #7843, #2013: ocamldoc, better handling of {{!label}text} in the latex
|
|
backend.
|
|
(Florian Angeletti, review by Nicolás Ojeda Bär and Gabriel Scherer)
|
|
|
|
- #7844, #2040: Emacs, use built-in detection of comments,
|
|
fixes an imenu crash.
|
|
(Wilfred Hughes, review by Christophe Troestler)
|
|
|
|
- #7850: Emacs, use symbol boundaries in regular expressions,
|
|
fixes an imenu crash.
|
|
(Wilfred Hughes, review by Christophe Troestler)
|
|
|
|
- #1711: the new 'open' flag in OCAMLPARAM takes a comma-separated list of
|
|
modules to open as if they had been passed via the command line -open flag.
|
|
(Nicolás Ojeda Bär, review by Mark Shinwell)
|
|
|
|
- #2000: ocamdoc, extended support for "include module type of ..."
|
|
(Florian Angeletti, review by Jérémie Dimino)
|
|
|
|
- #2045: ocamlmklib now supports options -args and -args0 to provide extra
|
|
command-line arguments in a file.
|
|
(Nicolás Ojeda Bär, review by Gabriel Scherer and Daniel Bünzli)
|
|
|
|
- #2189: change ocamldep Makefile-output to print each dependency
|
|
on a new line, for more readable diffs of versioned dependencies.
|
|
(Gabriel Scherer, review by Nicolás Ojeda Bär)
|
|
|
|
- #2223: ocamltest: fix the "bsd" and "not-bsd" built-in actions to
|
|
recognize all BSD variants
|
|
(Damien Doligez, review by Sébastien Hinderer and David Allsopp)
|
|
|
|
### Compiler distribution build system:
|
|
|
|
- #1776: add -no-install-bytecode-programs and related configure options to
|
|
control (non-)installation of ".byte" executables.
|
|
(Mark Shinwell, review by Sébastien Hinderer and Gabriel Scherer)
|
|
|
|
- #1777: add -no-install-source-artifacts and related configure options to
|
|
control installation of .cmt, .cmti, .mli and .ml files.
|
|
(Mark Shinwell, review by Nicolás Ojeda Bär and Sébastien Hinderer)
|
|
|
|
- #1781: cleanup of the manual's build process.
|
|
(steinuil, review by Marcello Seri, Gabriel Scherer and Florian Angeletti)
|
|
|
|
- #1797: remove the deprecated Makefile.nt files.
|
|
(Sébastien Hinderer, review by Nicolás Ojeda Bär)
|
|
|
|
- #1805: fix the bootstrap procedure and its documentation.
|
|
(Sébastien Hinderer, Xavier Leroy and Damien Doligez; review by
|
|
Gabriel Scherer)
|
|
|
|
- #1840: build system enhancements.
|
|
(Sébastien Hinderer, review by David Allsopp, Xavier Leroy and
|
|
Damien Doligez)
|
|
|
|
- #1852: merge runtime directories
|
|
(Sébastien Hinderer, review by Xavier Leroy and Damien Doligez)
|
|
|
|
- #1854: remove the no longer defined BYTECCCOMPOPTS build variable.
|
|
(Sébastien Hinderer, review by Damien Doligez)
|
|
|
|
- #2024: stop supporting obsolete platforms: Rhapsody (old beta
|
|
version of MacOS X, BeOS, alpha*-*-linux*, mips-*-irix6*,
|
|
alpha*-*-unicos, powerpc-*-aix, *-*-solaris2*, mips*-*-irix[56]*,
|
|
i[3456]86-*-darwin[89].*, i[3456]86-*-solaris*, *-*-sunos* *-*-unicos.
|
|
(Sébastien Hinderer, review by Xavier Leroy, Damien Doligez, Gabriel
|
|
Scherer and Armaël Guéneau)
|
|
|
|
- #2053: allow unix, vmthreads and str not to be built.
|
|
(David Allsopp, review by Sébastien Hinderer)
|
|
|
|
* #2059: stop defining OCAML_STDLIB_DIR in s.h.
|
|
(Sébastien Hinderer, review by David Allsopp and Damien Doligez)
|
|
|
|
* #2066: remove the standard_runtime configuration variable.
|
|
(Sébastien Hinderer, review by Xavier Leroy, Stephen Dolan and
|
|
Damien Doligez)
|
|
|
|
* #2139: use autoconf to generate the compiler's configuration script
|
|
(Sébastien Hinderer, review by Damien Doligez and David Allsopp)
|
|
|
|
- #2148: fix a parallel build bug involving CamlinternalLazy.
|
|
(Stephen Dolan, review by Gabriel Scherer and Nicolás Ojeda Bär)
|
|
|
|
- #2264, #7904: the configure script now sets the Unicode handling mode
|
|
under Windows according to the value of the variable WINDOWS_UNICODE_MODE. If
|
|
WINDOWS_UNICODE_MODE is "ansi" then it is assumed to be the current code page
|
|
encoding. If WINDOWS_UNICODE_MODE is "compatible" or empty or not set at all,
|
|
then encoding is UTF-8 with code page fallback.
|
|
(Nicolás Ojeda Bär, review by Sébastien Hinderer and David Allsopp)
|
|
|
|
- #2266: ensure Cygwin ports configure with `EXE=.exe`, or the compiler is
|
|
unable to find the camlheader files (subtle regression of #2139/2041)
|
|
(David Allsopp, report and review by Sébastien Hinderer)
|
|
|
|
- #7919, #2311: Fix assembler detection in configure
|
|
(Sébastien Hinderer, review by David Allsopp)
|
|
|
|
- #2295: Restore support for bytecode target XLC/AIX/Power
|
|
(Konstantin Romanov, review by Sébastien Hinderer and David Allsopp)
|
|
|
|
- #8528: get rid of the direct call to the C preprocessor in the testsuite
|
|
(Sébastien Hinderer, review by David Allsopp)
|
|
|
|
- #7938, #8532: Fix alignment detection for ints on 32-bits platforms
|
|
(Sébastien Hinderer, review by Xavier Leroy)
|
|
|
|
* #8533: Remove some unused configure tests
|
|
(Stephen Dolan, review by David Allsopp and Sébastien Hinderer)
|
|
|
|
- #2207, #8604: Add opam files to allow pinning
|
|
(Leo White, Greta Yorsh, review by Gabriel Radanne)
|
|
|
|
- #8616: configure: use variables rather than arguments for a few options
|
|
(Sébastien Hinderer, review by David Allsopp, Gabriel Scherer and
|
|
Damien Doligez)
|
|
|
|
- #8632: Correctly propagate flags for --with-pic in configure.
|
|
(David Allsopp, review by Sébastien Hinderer and Damien Doligez)
|
|
|
|
- #8673: restore SpaceTime and libunwind support in configure script
|
|
(Sébastien Hinderer, review by Damien Doligez)
|
|
|
|
### Internal/compiler-libs changes:
|
|
|
|
- #7918, #1703, #1944, #2213, #2257: Add the module
|
|
Compile_common, which factorizes the common part in Compile and
|
|
Optcompile. This also makes the pipeline more modular.
|
|
(Gabriel Radanne, help from Gabriel Scherer and Valentin
|
|
Gatien-Baron, review by Mark Shinwell and Gabriel Radanne,
|
|
regression spotted by Clément Franchini)
|
|
|
|
- #292: use Menhir as the parser generator for the OCaml parser.
|
|
Satellite GPRs: #1844, #1846, #1853, #1850, #1934, #2151,
|
|
#2174
|
|
(Gabriel Scherer, Nicolás Ojeda Bär, Frédéric Bour, Thomas Refis
|
|
and François Pottier,
|
|
review by Nicolás Ojeda Bär, Leo White and David Allsopp)
|
|
|
|
- #374: use Misc.try_finally for resource cleanup in the compiler
|
|
codebase. This should fix the problem of catch-and-reraise `try .. with`
|
|
blocks destroying backtrace information -- in the compiler.
|
|
(François Bobot, help from Gabriel Scherer and Nicolás Ojeda Bär,
|
|
review by Gabriel Scherer)
|
|
|
|
- #1148, #1287, #1288, #1874: significant improvements
|
|
of the tools/check-typo script used over the files of the whole repository;
|
|
contributors are now expected to check that check-typo passes on their
|
|
pull requests; see CONTRIBUTING.md for more details.
|
|
(David Allsopp, review by Damien Doligez and Sébastien Hinderer)
|
|
|
|
- #1610, #2252: Remove positions from paths
|
|
(Leo White, review by Frédéric Bour and Thomas Refis)
|
|
|
|
- #1745: do not generalize the type of every sub-pattern,
|
|
only of variables. (preliminary work for GADTs in or-patterns)
|
|
(Thomas Refis, review by Leo White)
|
|
|
|
- #1909: unsharing pattern types (preliminary work for GADTs in or-patterns)
|
|
(Thomas Refis, with help from Leo White, review by Jacques Garrigue)
|
|
|
|
- #1748: do not error when instantiating polymorphic fields in patterns.
|
|
(Thomas Refis, review by Gabriel Scherer)
|
|
|
|
- #2317: type_let: be more careful generalizing parts of the pattern
|
|
(Thomas Refis and Leo White, review by Jacques Garrigue)
|
|
|
|
- #1746: remove unreachable error variant: Make_seltype_nongen.
|
|
(Florian Angeletti, review by Gabriel Radanne)
|
|
|
|
- #1747: type_cases: always propagate (preliminary work
|
|
for GADTs in or-patterns)
|
|
(Thomas Refis, review by Jacques Garrigue)
|
|
|
|
- #1811: shadow the polymorphic comparison in the middle-end
|
|
(Xavier Clerc, review by Pierre Chambart)
|
|
|
|
- #1833: allow non-val payloads in CMM Ccatch handlers
|
|
(Simon Fowler, review by Xavier Clerc)
|
|
|
|
- #1866: document the release process
|
|
(Damien Doligez and Gabriel Scherer, review by Sébastien Hinderer,
|
|
Perry E. Metzger, Xavier Leroy and David Allsopp)
|
|
|
|
- #1886: move the Location.absname reference to Clflags.absname
|
|
(Armaël Guéneau, review by Jérémie Dimino)
|
|
|
|
- #1894: generalize highlight_dumb in location.ml to handle highlighting
|
|
several locations
|
|
(Armaël Guéneau, review by Gabriel Scherer)
|
|
|
|
- #1903: parsetree, add locations to all nodes with attributes
|
|
(Gabriel Scherer, review by Thomas Refis)
|
|
|
|
- #1905: add check-typo-since to check the files changed
|
|
since a given git reference
|
|
(Gabriel Scherer, review by David Allsopp)
|
|
|
|
- #1910: improve the check-typo use of .gitattributes
|
|
(Gabriel Scherer, review by David Allsopp and Damien Doligez)
|
|
|
|
- #1938: always check ast invariants after preprocessing
|
|
(Florian Angeletti, review by Alain Frisch and Gabriel Scherer)
|
|
|
|
- #1941: refactor the command line parsing of ocamlcp and ocamloptp
|
|
(Valentin Gatien-Baron, review by Florian Angeletti)
|
|
|
|
- #1948: Refactor Stdlib.Format. Notably, use Stdlib.Stack and Stdlib.Queue,
|
|
and avoid exceptions for control flow.
|
|
(Vladimir Keleshev, review by Nicolás Ojeda Bär and Gabriel Scherer)
|
|
|
|
* #1952: refactor the code responsible for displaying errors and warnings
|
|
`Location.report_error` is removed, use `Location.print_report` instead
|
|
(Armaël Guéneau, review by Thomas Refis)
|
|
|
|
- #7835, #1980, #8548, #8586: separate scope from stamp in idents and explicitly
|
|
rescope idents when substituting signatures.
|
|
(Thomas Refis, review by Jacques Garrigue and Leo White)
|
|
|
|
- #1996: expose Pprintast.longident to help compiler-libs users print
|
|
Longident.t values.
|
|
(Gabriel Scherer, review by Florian Angeletti and Thomas Refis)
|
|
|
|
- #2030: makefile targets to build AST files of sources
|
|
for parser testing. See parsing/HACKING.adoc.
|
|
(Gabriel Scherer, review by Nicolás Ojeda Bär)
|
|
|
|
* #2041: add a cache for looking up files in the load path
|
|
(Jérémie Dimino, review by Alain Frisch and David Allsopp)
|
|
|
|
- #2047, #2269: a new type for unification traces
|
|
(Florian Angeletti, report by Leo White (#2269),
|
|
review by Thomas Refis and Gabriel Scherer)
|
|
|
|
- #2055: Add [Linearize.Lprologue].
|
|
(Mark Shinwell, review by Pierre Chambart)
|
|
|
|
- #2056: Use [Backend_var] rather than [Ident] from [Clambda] onwards;
|
|
use [Backend_var.With_provenance] for variables in binding position.
|
|
(Mark Shinwell, review by Pierre Chambart)
|
|
|
|
- #2060: "Phantom let" support for the Clambda language.
|
|
(Mark Shinwell, review by Vincent Laviron)
|
|
|
|
- #2065: Add [Proc.destroyed_at_reloadretaddr].
|
|
(Mark Shinwell, review by Damien Doligez)
|
|
|
|
- #2070: "Phantom let" support for the Cmm language.
|
|
(Mark Shinwell, review by Vincent Laviron)
|
|
|
|
- #2072: Always associate a scope to a type
|
|
(Thomas Refis, review by Jacques Garrigue and Leo White)
|
|
|
|
- #2074: Correct naming of record field inside [Ialloc] terms.
|
|
(Mark Shinwell, review by Jérémie Dimino)
|
|
|
|
- #2076: Add [Targetint.print].
|
|
(Mark Shinwell)
|
|
|
|
- #2080: Add [Proc.dwarf_register_numbers] and
|
|
[Proc.stack_ptr_dwarf_register_number].
|
|
(Mark Shinwell, review by Bernhard Schommer)
|
|
|
|
- #2088: Add [Clambda.usymbol_provenance].
|
|
(Mark Shinwell, review by Damien Doligez)
|
|
|
|
- #2152, #2517: refactorize the fixpoint to compute type-system
|
|
properties of mutually-recursive type declarations.
|
|
(Gabriel Scherer and Rodolphe Lepigre, review by Armaël Guéneau)
|
|
|
|
- #2156: propagate more type information through Lambda and Clambda
|
|
intermediate language, as a preparation step for more future optimizations
|
|
(Pierre Chambart and Alain Frisch, cross-reviewed by themselves)
|
|
|
|
- #2160: restore --disable-shared support and ensure testsuite runs correctly
|
|
when compiled without shared library support.
|
|
(David Allsopp, review by Damien Doligez and Sébastien Hinderer)
|
|
|
|
* #2173: removed TypedtreeMap
|
|
(Thomas Refis, review by Gabriel Scherer)
|
|
|
|
- #7867: Fix #mod_use raising an exception for filenames with no
|
|
extension.
|
|
(Geoff Gole)
|
|
|
|
- #2100: Fix Unix.getaddrinfo when called on strings containing
|
|
null bytes; it would crash the GC later on.
|
|
(Armaël Guéneau, report and fix by Joe, review by Sébastien Hinderer)
|
|
|
|
- #7847, #2019: Fix an infinite loop that could occur when the
|
|
(Menhir-generated) parser encountered a syntax error in a certain
|
|
specific state.
|
|
(François Pottier, report by Stefan Muenzel,
|
|
review by Frédéric Bour, Thomas Refis, Gabriel Scherer)
|
|
|
|
- #1626: Do not allow recursive modules in `with module`
|
|
(Leo White, review by Gabriel Radanne)
|
|
|
|
- #7726, #1676: Recursive modules, equi-recursive types and stack overflow
|
|
(Jacques Garrigue, report by Jeremy Yallop, review by Leo White)
|
|
|
|
- #7723, #1698: Ensure `with module` and `with type` do not weaken
|
|
module aliases.
|
|
(Leo White, review by Gabriel Radanne and Jacques Garrigue)
|
|
|
|
- #1719: fix Pervasives.LargeFile functions under Windows.
|
|
(Alain Frisch)
|
|
|
|
- #1739: ensure ocamltest waits for child processes to terminate on Windows.
|
|
(David Allsopp, review by Sébastien Hinderer)
|
|
|
|
- #7554, #1751: Lambda.subst: also update debug event environments
|
|
(Thomas Refis, review by Gabriel Scherer)
|
|
|
|
- #7238, #1825: in Unix.in_channel_of_descr and Unix.out_channel_of_descr,
|
|
raise an error if the given file description is not suitable for
|
|
character-oriented I/O, for example if it is a block device or a
|
|
datagram socket.
|
|
(Xavier Leroy, review by Jérémie Dimino and Perry E. Metzger)
|
|
|
|
- #7799, #1820: fix bug where Scanf.format_from_string could fail when
|
|
the argument string contained characters that require escaping.
|
|
(Gabriel Scherer and Nicolás Ojeda Bär, report by Guillaume Melquiond, review
|
|
by Gabriel Scherer)
|
|
|
|
- #1843: ocamloptp was doing the wrong thing with option -inline-max-unroll.
|
|
(Github user @poechsel, review by Nicolás Ojeda Bär).
|
|
|
|
- #1890: remove last use of Ctype.unroll_abbrev
|
|
(Thomas Refis, report by Leo White, review by Jacques Garrigue)
|
|
|
|
- #1893: dev-branch only, warning 40(name not in scope) triggered spurious
|
|
warnings 49(missing cmi) with -no-alias-deps.
|
|
(Florian Angeletti, report by Valentin Gatien-Baron,
|
|
review by Gabriel Scherer)
|
|
|
|
- #1912: Allow quoted strings, octal/unicode escape sequences and identifiers
|
|
containing apostrophes in ocamllex actions and comments.
|
|
(Pieter Goetschalckx, review by Damien Doligez)
|
|
|
|
- #7828, #1935: correct the conditions that generate warning 61,
|
|
Unboxable_type_in_prim_decl
|
|
(Stefan Muenzel)
|
|
|
|
- #1958: allow [module M(_:S) = struct end] syntax
|
|
(Hugo Heuzard, review by Gabriel Scherer)
|
|
|
|
- #1970: fix order of floatting documentation comments in classes
|
|
(Hugo Heuzard, review by Nicolás Ojeda Bär)
|
|
|
|
- #1977: [@@ocaml.warning "..."] attributes attached to type declarations are
|
|
no longer ignored.
|
|
(Nicolás Ojeda Bär, review by Gabriel Scherer)
|
|
|
|
- #7830, #1987: fix ocamldebug crash when printing a value in the scope of
|
|
an `open` statement for which the `.cmi` is not available.
|
|
(Nicolás Ojeda Bär, report by Jocelyn Sérot, review by Gabriel Scherer)
|
|
|
|
- #7854, #2062: fix an issue where the wrong locale may be used when using
|
|
the legacy ANSI encoding under Windows.
|
|
(Nicolás Ojeda Bär, report by Tiphaine Turpin)
|
|
|
|
- #2083: Fix excessively aggressive float unboxing and introduce similar fix
|
|
as a preventative measure for boxed int unboxing.
|
|
(Thomas Refis, Mark Shinwell, Leo White)
|
|
|
|
- #2130: fix printing of type variables with a quote in their name
|
|
(Alain Frisch, review by Armaël Guéneau and Gabriel Scherer,
|
|
report by Hugo Heuzard)
|
|
|
|
- #2131: fix wrong calls to Env.normalize_path on non-module paths
|
|
(Alain Frisch, review by Jacques Garrigue)
|
|
|
|
- #2175: Apply substitution to all modules when packing
|
|
(Leo White, review by Gabriel Scherer)
|
|
|
|
- #2220: Remove duplicate process management code in
|
|
otherlibs/threads/unix.ml
|
|
(Romain Beauxis, review by Gabriel Scherer and Alain Frisch)
|
|
|
|
- #2231: Env: always freshen persistent signatures before using them
|
|
(Thomas Refis and Leo White, review by Gabriel Radanne)
|
|
|
|
- #7851, #8570: Module type of allows to transform a malformed
|
|
module type into a vicious signature, breaking soundness
|
|
(Jacques Garrigue, review by Leo White)
|
|
|
|
- #7923, #2259: fix regression in FlexDLL bootstrapped build caused by
|
|
refactoring the root Makefile for Dune in #2093)
|
|
(David Allsopp, report by Marc Lasson)
|
|
|
|
- #7929, #2261: Subst.signature: call cleanup_types exactly once
|
|
(Thomas Refis, review by Gabriel Scherer and Jacques Garrigue,
|
|
report by Daniel Bünzli and Jon Ludlam)
|
|
|
|
- #8550, #8552: Soundness issue with class generalization
|
|
(Jacques Garrigue, review by Leo White and Thomas Refis,
|
|
report by Jeremy Yallop)
|
|
|
|
OCaml 4.07.1 (4 October 2018)
|
|
-----------------------------
|
|
|
|
### Bug fixes:
|
|
|
|
- #7815, #1896: major GC crash with first-fit policy
|
|
(Stephen Dolan and Damien Doligez, report by Joris Giovannangeli)
|
|
|
|
* #7818, #2051: Remove local aliases in functor argument types,
|
|
to prevent the aliasing of their target.
|
|
(Jacques Garrigue, report by mandrykin, review by Leo White)
|
|
|
|
- #7820, #1897: Fix Array.of_seq. This function used to apply a circular
|
|
permutation of one cell to the right on the sequence.
|
|
(Thierry Martinez, review by Nicolás Ojeda Bär)
|
|
|
|
- #7821, #1908: make sure that the compilation of extension
|
|
constructors doesn't cause the compiler to load more cmi files
|
|
(Jérémie Dimino, review by Gabriel Scherer)
|
|
|
|
- #7824, #1914: subtype_row: filter out absent fields when row is closed
|
|
(Leo White and Thomas Refis, report by talex, review by Jacques Garrigue)
|
|
|
|
- #1915: rec_check.ml is too permissive for certain class declarations.
|
|
(Alban Reynaud with Gabriel Scherer, review by Jeremy Yallop)
|
|
|
|
- #7833, #1946: typecore: only 1k existential per match, not 100k
|
|
(Thomas Refis, report by Jerome Simeon, review by Jacques Garrigue)
|
|
|
|
- #7838: -principal causes assertion failure in type checker
|
|
(Jacques Garrigue, report by Markus Mottl, review by Thomas Refis)
|
|
|
|
OCaml 4.07.0 (10 July 2018)
|
|
---------------------------
|
|
|
|
(Changes that can break existing programs are marked with a "*")
|
|
|
|
### Language features:
|
|
|
|
- #6023, #1648: Allow type-based selection of GADT constructors.
|
|
(Thomas Refis and Leo White, review by Jacques Garrigue and Gabriel Scherer)
|
|
|
|
- #1546: Allow empty variants.
|
|
(Runhang Li, review by Gabriel Radanne and Jacques Garrigue)
|
|
|
|
### Standard library:
|
|
|
|
- #4170, #1674: add the constant `Float.pi`.
|
|
(Christophe Troestler, review by Damien Doligez)
|
|
|
|
- #6139, #1685: Move the Bigarray module to the standard library. Keep the
|
|
bigarray library as on overlay adding the deprecated map_file functions.
|
|
(Jérémie Dimino, review by Mark Shinwell)
|
|
|
|
- #7528, #1500: add a Format.pp_set_geometry function to avoid memory
|
|
effects in set_margin and set_max_indent.
|
|
(Florian Angeletti, review by Richard Bonichon, Gabriel Radanne,
|
|
Gabiel Scherer and Pierre Weis)
|
|
|
|
- #7690, #1528: fix the float_of_string function for hexadecimal floats
|
|
with very large values of the exponent.
|
|
(Olivier Andrieu)
|
|
|
|
- #1002: add a new `Seq` module defining a list-of-thunks style iterator.
|
|
Also add `{to,of}_seq` to several standard modules.
|
|
(Simon Cruanes, review by Alain Frisch and François Bobot)
|
|
|
|
* #1010: pack all standard library modules into a single module Stdlib
|
|
which is the default opened module (Stdlib itself includes Pervasives) to free
|
|
up the global namespace for other standard libraries, while still allowing any
|
|
OCaml standard library module to be referred to as Stdlib.Module). This is
|
|
implemented efficiently using module aliases (prefixing all modules with
|
|
Stdlib__, e.g. Stdlib__string).
|
|
(Jérémie Dimino, David Allsopp and Florian Angeletti, review by David Allsopp
|
|
and Gabriel Radanne)
|
|
|
|
- #1637: String.escaped is faster and does not allocate when called with a
|
|
string that does not contain any characters needing to be escaped.
|
|
(Alain Frisch, review by Xavier Leroy and Gabriel Scherer)
|
|
|
|
- #1638: add a Float module.
|
|
(Nicolás Ojeda Bär, review by Alain Frisch and Jeremy Yallop)
|
|
|
|
- #1697: Tune [List.init] tailrec threshold so that it does not stack
|
|
overflow when compiled with the Js_of_ocaml backend.
|
|
(Hugo Heuzard, reviewed by Gabriel Scherer)
|
|
|
|
### Other libraries:
|
|
|
|
- #7745, #1629: Graphics.open_graph displays the correct window title on
|
|
Windows again (fault introduced by 4.06 Unicode changes).
|
|
(David Allsopp)
|
|
|
|
* #1406: Unix.isatty now returns true in the native Windows ports when
|
|
passed a file descriptor connected to a Cygwin PTY. In particular, compiler
|
|
colors for the native Windows ports now work under Cygwin/MSYS2.
|
|
(Nicolás Ojeda Bär, review by Gabriel Scherer, David Allsopp, Xavier Leroy)
|
|
|
|
- #1451: [getpwuid], [getgrgid], [getpwnam], [getgrnam] now raise Unix error
|
|
instead of returning [Not_found] when interrupted by a signal.
|
|
(Arseniy Alekseyev, review by Mark Shinwell and Xavier Leroy)
|
|
|
|
- #1477: raw_spacetime_lib can now be used in bytecode.
|
|
(Nicolás Ojeda Bär, review by Mark Shinwell)
|
|
|
|
- #1533: (a) The implementation of Thread.yield for system thread
|
|
now uses nanosleep(1) for enabling better preemption.
|
|
(b) Thread.delay is now an alias for Unix.sleepf.
|
|
(Jacques-Henri Jourdan, review by Xavier Leroy and David Allsopp)
|
|
|
|
### Compiler user-interface and warnings:
|
|
|
|
- #7663, #1694: print the whole cycle and add a reference to the manual in
|
|
the unsafe recursive module evaluation error message.
|
|
(Florian Angeletti, report by Matej Košík, review by Gabriel Scherer)
|
|
|
|
- #1166: In OCAMLPARAM, an alternative separator can be specified as
|
|
first character (instead of comma) in the set ":|; ,"
|
|
(Fabrice Le Fessant)
|
|
|
|
- #1358: Fix usage warnings with no mli file.
|
|
(Leo White, review by Alain Frisch)
|
|
|
|
- #1428: give a non dummy location for warning 49 (no cmi found).
|
|
(Valentin Gatien-Baron)
|
|
|
|
- #1491: Improve error reporting for ill-typed applicative functor
|
|
types, F(M).t.
|
|
(Valentin Gatien-Baron, review by Florian Angeletti and Gabriel Radanne)
|
|
|
|
- #1496: Refactor the code printing explanation for unification type errors,
|
|
in order to avoid duplicating pattern matches.
|
|
(Armaël Guéneau, review by Florian Angeletti and Gabriel Scherer)
|
|
|
|
- #1505: Add specific error messages for unification errors involving
|
|
functions of type "unit -> _".
|
|
(Arthur Charguéraud and Armaël Guéneau, with help from Leo White, review by
|
|
Florian Angeletti and Gabriel Radanne)
|
|
|
|
- #1510: Add specific explanation for unification errors caused by type
|
|
constraints propagated by keywords (such as if, while, for...).
|
|
(Armaël Guéneau and Gabriel Scherer, original design by Arthur Charguéraud,
|
|
review by Frédéric Bour, Gabriel Radanne and Alain Frisch)
|
|
|
|
- #1515: honor the BUILD_PATH_PREFIX_MAP environment variable
|
|
to enable reproducible builds.
|
|
(Gabriel Scherer, with help from Ximin Luo, review by Damien Doligez)
|
|
|
|
- #1534: Extend the warning printed when (*) is used, adding a hint to
|
|
suggest using ( * ) instead.
|
|
(Armaël Guéneau, with help and review from Florian Angeletti and Gabriel
|
|
Scherer)
|
|
|
|
- #1552, #1577: do not warn about ambiguous variables in guards
|
|
(warning 57) when the ambiguous values have been filtered by
|
|
a previous clause.
|
|
(Gabriel Scherer and Thomas Refis, review by Luc Maranget)
|
|
|
|
- #1554: warnings 52 and 57: fix reference to manual detailed explanation.
|
|
(Florian Angeletti, review by Thomas Refis and Gabriel Scherer)
|
|
|
|
- #1618: add the -dno-unique-ids and -dunique-ids compiler flags.
|
|
(Sébastien Hinderer, review by Leo White and Damien Doligez)
|
|
|
|
- #1649: change compilation order of toplevel definitions, so that some
|
|
warnings emitted by the bytecode compiler appear more in-order than before.
|
|
(Luc Maranget, advice and review by Damien Doligez)
|
|
|
|
- #1806: add linscan to OCAMLPARAM options.
|
|
(Raja Boujbel)
|
|
|
|
### Code generation and optimizations:
|
|
|
|
- #7630, #1401: Faster compilation of large modules with Flambda.
|
|
(Pierre Chambart, report by Emilio Jesús Gallego Arias,
|
|
Pierre-Marie Pédrot and Paul Steckler, review by Gabriel Scherer
|
|
and Leo White)
|
|
|
|
- #7630, #1455: Disable CSE for the initialization function.
|
|
(Pierre Chambart, report by Emilio Jesús Gallego Arias,
|
|
review by Gabriel Scherer and Xavier Leroy)
|
|
|
|
- #1370: Fix code duplication in Cmmgen.
|
|
(Vincent Laviron, with help from Pierre Chambart,
|
|
reviews by Gabriel Scherer and Luc Maranget)
|
|
|
|
- #1486: ARM 32-bit port: add support for ARMv8 in 32-bit mode,
|
|
a.k.a. AArch32.
|
|
For this platform, avoid ITE conditional instruction blocks and use
|
|
simpler IT blocks instead.
|
|
(Xavier Leroy, review by Mark Shinwell)
|
|
|
|
- #1487: Treat negated float comparisons more directly.
|
|
(Leo White, review by Xavier Leroy)
|
|
|
|
- #1573: emitcode: merge events after instructions reordering.
|
|
(Thomas Refis and Leo White, with help from David Allsopp, review by Frédéric
|
|
Bour)
|
|
|
|
- #1606: Simplify the semantics of Lambda.free_variables and Lambda.subst,
|
|
including some API changes in bytecomp/lambda.mli.
|
|
(Pierre Chambart, review by Gabriel Scherer)
|
|
|
|
- #1613: ensure that set-of-closures are processed first so that other
|
|
entries in the let-rec symbol do not get dummy approximations.
|
|
(Leo White and Xavier Clerc, review by Pierre Chambart)
|
|
|
|
* #1617: Make string/bytes distinguishable in the bytecode.
|
|
(Hugo Heuzard, reviewed by Nicolás Ojeda Bär)
|
|
|
|
- #1627: Reduce cmx sizes by sharing variable names (Flambda only).
|
|
(Fuyong Quah, Leo White, review by Xavier Clerc)
|
|
|
|
- #1665: reduce the size of cmx files in classic mode by dropping the
|
|
bodies of functions that will not be inlined.
|
|
(Fuyong Quah, review by Leo White and Pierre Chambart)
|
|
|
|
- #1666: reduce the size of cmx files in classic mode by dropping the
|
|
bodies of functions that cannot be reached from the module block.
|
|
(Fuyong Quah, review by Leo White and Pierre Chambart)
|
|
|
|
- #1686: Turn off by default flambda invariants checks.
|
|
(Pierre Chambart)
|
|
|
|
- #1707: Add [Closure_origin.t] to trace inlined functions to prevent
|
|
infinite loops from repeatedly inlining copies of the same function.
|
|
(Fu Yong Quah)
|
|
|
|
- #1740: make sure startup.o is always linked in when using
|
|
"-output-complete-obj". Previously, it was always linked in only on some
|
|
platforms, making this option unusable on platforms where it wasn't.
|
|
(Jérémie Dimino, review by Sébastien Hinderer and Xavier Leroy)
|
|
|
|
### Runtime system:
|
|
|
|
- #515 #676 #7173: Add a public C API for weak arrays and
|
|
ephemerons. Update the documentation for a 4.03 change: finalisation
|
|
functions are now run before the erasure of the corresponding
|
|
values.
|
|
(François Bobot and Jacques-Henri Jourdan, review by Mark Shinwell,
|
|
Damien Doligez and Frédéric Bour)
|
|
|
|
- #6411, #1535: don't compile everything with -static-libgcc on mingw32,
|
|
only dllbigarray.dll and libbigarray.a. Allows the use of C++ libraries which
|
|
raise exceptions.
|
|
(David Allsopp)
|
|
|
|
- #7100, #1476: trigger a minor GC when custom blocks accumulate
|
|
in minor heap.
|
|
(Alain Frisch, report by talex, review by Damien Doligez, Leo White,
|
|
Gabriel Scherer)
|
|
|
|
- #1431: remove ocamlrun dependencies on curses/terminfo/termcap C library.
|
|
(Xavier Leroy, review by Daniel Bünzli)
|
|
|
|
- #1478: The Spacetime profiler now works under Windows (but it is not yet
|
|
able to collect profiling information from C stubs).
|
|
(Nicolás Ojeda Bär, review by Xavier Leroy, Mark Shinwell)
|
|
|
|
- #1483: fix GC freelist accounting for chunks larger than the maximum block
|
|
size.
|
|
(David Allsopp and Damien Doligez)
|
|
|
|
- #1526: install the debug and instrumented runtimes
|
|
(lib{caml,asm}run{d,i}.a).
|
|
(Gabriel Scherer, reminded by Julia Lawall)
|
|
|
|
- #1563: simplify implementation of LSRINT and ASRINT.
|
|
(Max Mouratov, review by Frédéric Bour)
|
|
|
|
- #1644: remove caml_alloc_float_array from the bytecode primitives list
|
|
(it's a native code primitive).
|
|
(David Allsopp)
|
|
|
|
- #1701: fix missing root bug in #1476.
|
|
(Mark Shinwell)
|
|
|
|
- #1752: do not alias function arguments to sigprocmask.
|
|
(Anil Madhavapeddy)
|
|
|
|
- #1753: avoid potential off-by-one overflow in debugger socket path length.
|
|
(Anil Madhavapeddy)
|
|
|
|
### Tools:
|
|
|
|
- #7643, #1377: ocamldep, fix an exponential blowup in presence of nested
|
|
structures and signatures, e.g. "include struct … include(struct … end) … end"
|
|
(Florian Angeletti, review by Gabriel Scherer, report by Christophe Raffalli)
|
|
|
|
- #7687, #1653: deprecate -thread option,
|
|
which is equivalent to -I +threads.
|
|
(Nicolás Ojeda Bär, report by Daniel Bünzli)
|
|
|
|
- #7710: `ocamldep -sort` should exit with nonzero code in case of
|
|
cyclic dependencies.
|
|
(Xavier Leroy, report by Mantis user baileyparker)
|
|
|
|
- #1537: boot/ocamldep is no longer included in the source distribution;
|
|
boot/ocamlc -depend can be used in its place.
|
|
(Nicolás Ojeda Bär, review by Xavier Leroy and Damien Doligez)
|
|
|
|
- #1585: optimize output of "ocamllex -ml".
|
|
(Alain Frisch, review by Frédéric Bour and Gabriel Scherer)
|
|
|
|
- #1667: add command-line options -no-prompt, -no-version, -no-time,
|
|
-no-breakpoint-message and -topdirs-path to ocamldebug.
|
|
(Sébastien Hinderer, review by Damien Doligez)
|
|
|
|
- #1695: add the -null-crc command-line option to ocamlobjinfo.
|
|
(Sébastien Hinderer, review by David Allsopp and Gabriel Scherer)
|
|
|
|
- #1710: ocamldoc, improve the 'man' rendering of subscripts and
|
|
superscripts.
|
|
(Gabriel Scherer)
|
|
|
|
- #1771: ocamldebug, avoid out of bound access.
|
|
(Thomas Refis)
|
|
|
|
### Manual and documentation:
|
|
|
|
- #7613: minor rewording of the "refutation cases" paragraph.
|
|
(Florian Angeletti, review by Jacques Garrigue)
|
|
|
|
- #7647, #1384: emphasize ocaml.org website and forum in README.
|
|
(Yawar Amin, review by Gabriel Scherer)
|
|
|
|
- #7698, #1545: improve wording in OCaml manual in several places,
|
|
mostly in Chapter 1. This addresses the easier changes suggested in the PR.
|
|
(Jim Fehrle, review by Florian Angeletti and David Allsopp)
|
|
|
|
- #1540: manual, decouple verbatim and toplevel style in code examples.
|
|
(Florian Angeletti, review by Gabriel Scherer)
|
|
|
|
- #1556: manual, add a consistency test for manual references inside
|
|
the compiler source code.
|
|
(Florian Angeletti, review by Gabriel Scherer)
|
|
|
|
- #1647: manual, subsection on record and variant disambiguation.
|
|
(Florian Angeletti, review by Alain Frisch and Gabriel Scherer)
|
|
|
|
- #1702: manual, add a signature mode for code examples.
|
|
(Florian Angeletti, review by Gabriel Scherer)
|
|
|
|
- #1741: manual, improve typesetting and legibility in HTML output.
|
|
(steinuil, review by Gabriel Scherer)
|
|
|
|
- #1757: style the html manual, changing type and layout.
|
|
(Charles Chamberlain, review by Florian Angeletti, Xavier Leroy,
|
|
Gabriel Radanne, Perry E. Metzger, and Gabriel Scherer)
|
|
|
|
- #1765: manual, ellipsis in code examples.
|
|
(Florian Angeletti, review and suggestion by Gabriel Scherer)
|
|
|
|
- #1767: change html manual to use relative font sizes.
|
|
(Charles Chamberlain, review by Daniel Bünzli, Perry E. Metzger,
|
|
Josh Berdine, and Gabriel Scherer)
|
|
|
|
- #1779: integrate the Bigarray documentation into the main manual.
|
|
(Perry E. Metzger, review by Florian Angeletti and Xavier Clerc)
|
|
|
|
### Type system:
|
|
|
|
- #7611, #1491: reject the use of generative functors as applicative.
|
|
(Valentin Gatien-Baron)
|
|
|
|
- #7706, #1565: in recursive value declarations, track
|
|
static size of locally-defined variables.
|
|
(Gabriel Scherer, review by Jeremy Yallop and Leo White, report by Leo White)
|
|
|
|
- #7717, #1593: in recursive value declarations, don't treat
|
|
unboxed constructor size as statically known.
|
|
(Jeremy Yallop, report by Pierre Chambart, review by Gabriel Scherer)
|
|
|
|
- #7767, #1712: restore legacy treatment of partially-applied
|
|
labeled functions in 'let rec' bindings.
|
|
(Jeremy Yallop, report by Ivan Gotovchits, review by Gabriel Scherer)
|
|
|
|
* #7787, #1652, #1743: Don't remove module aliases in `module type of`
|
|
and `with module`.
|
|
The old behaviour can be obtained using the `[@remove_aliases]` attribute.
|
|
(Leo White and Thomas Refis, review by Jacques Garrigue)
|
|
|
|
- #1468: Do not enrich type_decls with incoherent manifests.
|
|
(Thomas Refis and Leo White, review by Jacques Garrigue)
|
|
|
|
- #1469: Use the information from [@@immediate] annotations when
|
|
computing whether a type can be [@@unboxed].
|
|
(Damien Doligez, report by Stephan Muenzel, review by Alain Frisch)
|
|
|
|
- #1513: Allow compilation units to shadow sub-modules of Pervasives.
|
|
For instance users can now use a largeFile.ml file in their project.
|
|
(Jérémie Dimino, review by Nicolás Ojeda Bär, Alain Frisch and Gabriel
|
|
Radanne)
|
|
|
|
- #1516: Allow float array construction in recursive bindings
|
|
when configured with -no-flat-float-array.
|
|
(Jeremy Yallop, report by Gabriel Scherer)
|
|
|
|
- #1583: propagate refined ty_arg to Parmatch checks.
|
|
(Thomas Refis, review by Jacques Garrigue)
|
|
|
|
- #1609: Changes to ambivalence scope tracking.
|
|
(Thomas Refis and Leo White, review by Jacques Garrigue)
|
|
|
|
- #1628: Treat reraise and raise_notrace as nonexpansive.
|
|
(Leo White, review by Alain Frisch)
|
|
|
|
* #1778: Fix Soundness bug with non-generalized type variable and
|
|
local modules. This is the same bug as #7414, but using local
|
|
modules instead of non-local ones.
|
|
(Leo White, review by Jacques Garrigue)
|
|
|
|
### Compiler distribution build system:
|
|
|
|
- #5219, #1680, #1877: use 'install' instead of 'cp'
|
|
in install scripts.
|
|
(Gabriel Scherer, review by Sébastien Hinderer and Valentin Gatien-Baron)
|
|
|
|
- #7679: make sure .a files are erased before calling ar rc, otherwise
|
|
leftover .a files from an earlier compilation may contain unwanted modules.
|
|
(Xavier Leroy)
|
|
|
|
- #1571: do not perform architecture tests on 32-bit platforms, allowing
|
|
64-bit back-ends to use 64-bit specific constructs.
|
|
(Xavier Clerc, review by Damien Doligez)
|
|
|
|
### Internal/compiler-libs changes:
|
|
|
|
- #7738, #1624: Asmlink.reset also resets lib_ccobjs/ccopts.
|
|
(Cedric Cellier, review by Gabriel Scherer)
|
|
|
|
- #1488, #1560: Refreshing parmatch.
|
|
(Gabriel Scherer and Thomas Refis, review by Luc Maranget)
|
|
|
|
- #1502: more command line options for expect tests.
|
|
(Florian Angeletti, review by Gabriel Scherer)
|
|
|
|
- #1511: show code at error location in expect-style tests,
|
|
using new Location.show_code_at_location function.
|
|
(Gabriel Scherer and Armaël Guéneau,
|
|
review by Valentin Gatien-Baron and Damien Doligez)
|
|
|
|
- #1519, #1532, #1570: migrate tests to ocamltest.
|
|
(Sébastien Hinderer, review by Gabriel Scherer, Valentin Gatien-Baron
|
|
and Nicolás Ojeda Bär)
|
|
|
|
- #1520: more robust implementation of Misc.no_overflow_mul.
|
|
(Max Mouratov, review by Xavier Leroy)
|
|
|
|
- #1557: Organise and simplify translation of primitives.
|
|
(Leo White, review by François Bobot and Nicolás Ojeda Bär)
|
|
|
|
- #1567: register all idents relevant for reraise.
|
|
(Thomas Refis, review by Alain Frisch and Frédéric Bour)
|
|
|
|
- #1586: testsuite: 'make promote' for ocamltest tests.
|
|
(The new "-promote" option for ocamltest is experimental
|
|
and subject to change/removal).
|
|
(Gabriel Scherer)
|
|
|
|
- #1619: expect_test: print all the exceptions, even the unexpected ones.
|
|
(Thomas Refis, review by Jérémie Dimino)
|
|
|
|
- #1621: expect_test: make sure to not use the installed stdlib.
|
|
(Jérémie Dimino, review by Thomas Refis)
|
|
|
|
- #1646: add ocamldoc test to ocamltest and
|
|
migrate ocamldoc tests to ocamltest.
|
|
(Florian Angeletti, review by Sébastien Hinderer)
|
|
|
|
- #1663: refactor flambda specialise/inlining handling.
|
|
(Leo White and Xavier Clerc, review by Pierre Chambart)
|
|
|
|
- #1679: remove Pbittest from primitives in lambda.
|
|
(Hugo Heuzard, review by Mark Shinwell)
|
|
|
|
* #1704: Make Ident.t abstract and immutable.
|
|
(Gabriel Radanne, review by Mark Shinwell)
|
|
|
|
- #1699: Clean up Maps and Sets throughout the compiler.
|
|
Remove the Tbl module in favor of dedicated Maps.
|
|
(Gabriel Radanne, review by Mark Shinwell)
|
|
|
|
### Bug fixes:
|
|
|
|
- #4499, #1479: Use native Windows API to implement Sys.getenv,
|
|
Unix.getenv and Unix.environment under Windows.
|
|
(Nicolás Ojeda Bär, report by Alain Frisch, review by David Allsopp, Xavier
|
|
Leroy)
|
|
|
|
- #5250, #1435: on Cygwin, when ocamlrun searches the path
|
|
for a bytecode executable file, skip directories and other
|
|
non-regular files, like other Unix variants do.
|
|
(Xavier Leroy)
|
|
|
|
- #6394, #1425: fix fatal_error from Parmatch.get_type_path.
|
|
(Virgile Prevosto, review by David Allsopp, Thomas Refis and Jacques Garrigue)
|
|
|
|
* #6604, #931: Only allow directives with filename and at the beginning of
|
|
the line.
|
|
(Tadeu Zagallo, report by Roberto Di Cosmo,
|
|
review by Hongbo Zhang, David Allsopp, Gabriel Scherer, Xavier Leroy)
|
|
|
|
- #7138, #7701, #1693: Keep documentation comments
|
|
even in empty structures and signatures.
|
|
(Leo White, Florian Angeletti, report by Anton Bachin)
|
|
|
|
- #7178, #7253, #7796, #1790: Make sure a function
|
|
registered with "at_exit" is executed only once when the program exits.
|
|
(Nicolás Ojeda Bär and Xavier Leroy, review by Max Mouratov)
|
|
|
|
- #7391, #1620: Do not put a dummy method in object types.
|
|
(Thomas Refis, review by Jacques Garrigue)
|
|
|
|
- #7660, #1445: Use native Windows API to implement Unix.utimes in order to
|
|
avoid unintended shifts of the argument timestamp depending on DST setting.
|
|
(Nicolás Ojeda Bär, review by David Allsopp, Xavier Leroy)
|
|
|
|
- #7668: -principal is broken with polymorphic variants.
|
|
(Jacques Garrigue, report by Jun Furuse)
|
|
|
|
- #7680, #1497: Incorrect interaction between Matching.for_let and
|
|
Simplif.simplify_exits.
|
|
(Alain Frisch, report and review by Vincent Laviron)
|
|
|
|
- #7682, #1495: fix [@@unboxed] for records with 1 polymorphic field.
|
|
(Alain Frisch, report by Stéphane Graham-Lengrand, review by Gabriel Scherer)
|
|
|
|
- #7695, #1541: Fatal error: exception Ctype.Unify(_) with field override
|
|
(Jacques Garrigue, report by Nicolás Ojeda Bär)
|
|
|
|
- #7704, #1564: use proper variant tag in non-exhaustiveness warning.
|
|
(Jacques Garrigue, report by Thomas Refis)
|
|
|
|
- #7711, #1581: Internal typechecker error triggered by a constraint on
|
|
self type in a class type.
|
|
(Jacques Garrigue, report and review by Florian Angeletti)
|
|
|
|
- #7712, #1576: assertion failure with type abbreviations.
|
|
(Thomas Refis, report by Michael O'Connor, review by Jacques Garrigue)
|
|
|
|
- #7747: Type checker can loop infinitely and consume all computer memory.
|
|
(Jacques Garrigue, report by kantian)
|
|
|
|
- #7751, #1657: The toplevel prints some concrete types as abstract.
|
|
(Jacques Garrigue, report by Matej Kosik)
|
|
|
|
- #7765, #1718: When unmarshaling bigarrays, protect against integer
|
|
overflows in size computations.
|
|
(Xavier Leroy, report by Maximilian Tschirschnitz,
|
|
review by Gabriel Scherer)
|
|
|
|
- #7760, #1713: Exact selection of lexing engine, that is
|
|
correct "Segfault in ocamllex-generated code using 'shortest'".
|
|
(Luc Maranget, Frédéric Bour, report by Stephen Dolan,
|
|
review by Gabriel Scherer)
|
|
|
|
- #7769, #1714: calls to Stream.junk could, under some conditions, be
|
|
ignored when used on streams based on input channels.
|
|
(Nicolás Ojeda Bär, report by Michael Perin, review by Gabriel Scherer)
|
|
|
|
- #7793, #1766: the toplevel #use directive now accepts sequences of ';;'
|
|
tokens. This fixes a bug in which certain files accepted by the compiler were
|
|
rejected by ocamldep.
|
|
(Nicolás Ojeda Bär, report by Hugo Heuzard, review by Hugo Heuzard)
|
|
|
|
- #1517: More robust handling of type variables in mcomp.
|
|
(Leo White and Thomas Refis, review by Jacques Garrigue)
|
|
|
|
- #1530, #1574: testsuite, fix 'make parallel' and 'make one DIR=...'
|
|
to work on ocamltest-based tests.
|
|
(Runhang Li and Sébastien Hinderer, review by Gabriel Scherer)
|
|
|
|
- #1550, #1555: Make pattern matching warnings more robust
|
|
to ill-typed columns.
|
|
(Thomas Refis, with help from Gabriel Scherer and Luc Maranget)
|
|
|
|
- #1614: consider all bound variables when inlining, fixing a compiler
|
|
fatal error.
|
|
(Xavier Clerc, review by Pierre Chambart, Leo White)
|
|
|
|
- #1622: fix bug in the expansion of command-line arguments under Windows
|
|
which could result in some elements of Sys.argv being truncated in some cases.
|
|
(Nicolás Ojeda Bär, review by Sébastien Hinderer)
|
|
|
|
- #1623: Segfault on Windows 64 bits when expanding wildcards in arguments.
|
|
(Marc Lasson, review by David Allsopp, Alain Frisch, Sébastien Hinderer,
|
|
Xavier Leroy, Nicolás Ojeda Bär)
|
|
|
|
- #1661: more precise principality warning regarding record fields
|
|
disambiguation.
|
|
(Thomas Refis, review by Leo White)
|
|
|
|
- #1687: fix bug in the printing of short functor types "(S1 -> S2) -> S3".
|
|
(Pieter Goetschalckx, review by Gabriel Scherer)
|
|
|
|
- #1722: Scrape types in Typeopt.maybe_pointer.
|
|
(Leo White, review by Thomas Refis)
|
|
|
|
- #1755: ensure that a bigarray is never collected while reading complex
|
|
values.
|
|
(Xavier Clerc, Mark Shinwell and Leo White, report by Chris Hardin,
|
|
reviews by Stephen Dolan and Xavier Leroy)
|
|
|
|
- #1764: in byterun/memory.c, struct pool_block, use C99 flexible arrays
|
|
if available.
|
|
(Xavier Leroy, review by Max Mouratov)
|
|
|
|
- #1774: ocamlopt for ARM could generate VFP loads and stores with bad
|
|
offsets, rejected by the assembler.
|
|
(Xavier Leroy, review by Mark Shinwell)
|
|
|
|
- #1808: handle `[@inlined]` attributes under a module constraint.
|
|
(Xavier Clerc, review by Leo White)
|
|
|
|
- #1810: use bit-pattern comparison when meeting float approximations.
|
|
(Xavier Clerc, report by Christophe Troestler, review by Nicolás Ojeda Bär
|
|
and Gabriel Scherer)
|
|
|
|
- #1835: Fix off-by-one errors in Weak.get_copy and Weak.blit.
|
|
(KC Sivaramakrishnan)
|
|
|
|
- #1849: bug in runtime function generic_final_minor_update()
|
|
that could lead to crashes when Gc.finalise_last is used.
|
|
(report and fix by Yuriy Vostrikov, review by François Bobot)
|
|
|
|
|
|
OCaml 4.06.1 (16 Feb 2018):
|
|
---------------------------
|
|
|
|
### Bug fixes:
|
|
|
|
- #7661, #1459: fix faulty compilation of patterns
|
|
using extensible variants constructors
|
|
(Luc Maranget, review by Thomas Refis and Gabriel Scherer, report
|
|
by Abdelraouf Ouadjaout and Thibault Suzanne)
|
|
|
|
- #7702, #1553: refresh raise counts when inlining a function
|
|
(Vincent Laviron, Xavier Clerc, report by Cheng Sun)
|
|
|
|
- #7704, #1559: Soundness issue with private rows and pattern-matching
|
|
(Jacques Garrigue, report by Jeremy Yallop, review by Thomas Refis)
|
|
|
|
- #7705, #1558: add missing bounds check in Bigarray.Genarray.nth_dim.
|
|
(Nicolás Ojeda Bär, report by Jeremy Yallop, review by Gabriel Scherer)
|
|
|
|
- #7713, #1587: Make pattern matching warnings more robust
|
|
to ill-typed columns; this is a backport of #1550 from 4.07+dev
|
|
(Thomas Refis, review by Gabriel Scherer, report by Andreas Hauptmann)
|
|
|
|
- #1470: Don't commute negation with float comparison
|
|
(Leo White, review by Xavier Leroy)
|
|
|
|
- #1538: Make pattern matching compilation more robust to ill-typed columns
|
|
(Gabriel Scherer and Thomas Refis, review by Luc Maranget)
|
|
|
|
OCaml 4.06.0 (3 Nov 2017):
|
|
--------------------------
|
|
|
|
(Changes that can break existing programs are marked with a "*")
|
|
|
|
### Language features:
|
|
|
|
- #6271, #7529, #1249: Support "let open M in ..."
|
|
in class expressions and class type expressions.
|
|
(Alain Frisch, reviews by Thomas Refis and Jacques Garrigue)
|
|
|
|
- #792: fix limitations of destructive substitutions, by
|
|
allowing "S with type t := type-expr",
|
|
"S with type M.t := type-expr", "S with module M.N := path"
|
|
(Valentin Gatien-Baron, review by Jacques Garrigue and Leo White)
|
|
|
|
* #1064, #1392: extended indexing operators, add a new class of
|
|
user-defined indexing operators, obtained by adding at least
|
|
one operator character after the dot symbol to the standard indexing
|
|
operators: e,g ".%()", ".?[]", ".@{}<-":
|
|
let ( .%() ) = List.nth in [0; 1; 2].%(1)
|
|
After this change, functions or methods with an explicit polymorphic type
|
|
annotation and of which the first argument is optional now requires a space
|
|
between the dot and the question mark,
|
|
e.g. "<f:'a.?opt:int->unit>" must now be written "<f:'a. ?opt:int->unit>".
|
|
(Florian Angeletti, review by Damien Doligez and Gabriel Radanne)
|
|
|
|
- #1118: Support inherited field in object type expression
|
|
type t = < m : int >
|
|
type u = < n : int; t; k : int >
|
|
(Runhang Li, review by Jeremy Yallop, Leo White, Jacques Garrigue,
|
|
and Florian Angeletti)
|
|
|
|
* #1232: Support Unicode character escape sequences in string
|
|
literals via the \u{X+} syntax. These escapes are substituted by the
|
|
UTF-8 encoding of the Unicode character.
|
|
(Daniel Bünzli, review by Damien Doligez, Alain Frisch, Xavier
|
|
Leroy and Leo White)
|
|
|
|
- #1247: M.(::) construction for expressions
|
|
and patterns (plus fix printing of (::) in the toplevel)
|
|
(Florian Angeletti, review by Alain Frisch, Gabriel Scherer)
|
|
|
|
* #1252: The default mode is now safe-string, can be overridden
|
|
at configure time or at compile time.
|
|
(See #1386 below for the configure-time options)
|
|
This breaks the code that uses the 'string' type as mutable
|
|
strings (instead of Bytes.t, introduced by 4.02 in 2014).
|
|
(Damien Doligez)
|
|
|
|
* #1253: Private extensible variants
|
|
This change breaks code relying on the undocumented ability to export
|
|
extension constructors for abstract type in signature. Briefly,
|
|
module type S = sig
|
|
type t
|
|
type t += A
|
|
end
|
|
must now be written
|
|
module type S = sig
|
|
type t = private ..
|
|
type t += A
|
|
end
|
|
(Leo White, review by Alain Frisch)
|
|
|
|
- #1333: turn off warning 40 by default
|
|
(Constructor or label name used out of scope)
|
|
(Leo White)
|
|
|
|
- #1348: accept anonymous type parameters in `with` constraints:
|
|
S with type _ t = int
|
|
(Valentin Gatien-Baron, report by Jeremy Yallop)
|
|
|
|
### Type system
|
|
|
|
- #2642, #1225: unique names for weak type variables
|
|
# ref [];;
|
|
- : '_weak1 list ref = {contents = []}
|
|
(Florian Angeletti, review by Frédéric Bour, Jacques Garrigue,
|
|
Gabriel Radanne and Gabriel Scherer)
|
|
|
|
* #6738, #7215, #7231, #556: Add a new check that 'let rec'
|
|
bindings are well formed.
|
|
(Jeremy Yallop, reviews by Stephen Dolan, Gabriel Scherer, Leo
|
|
White, and Damien Doligez)
|
|
|
|
- #1142: Mark assertions nonexpansive, so that 'assert false'
|
|
can be used as a placeholder for a polymorphic function.
|
|
(Stephen Dolan)
|
|
|
|
### Standard library:
|
|
|
|
- #8223, #7309, #1026: Add update to maps. Allows to update a
|
|
binding in a map or create a new binding if the key had no binding
|
|
val update: key -> ('a option -> 'a option) -> 'a t -> 'a t
|
|
(Sébastien Briais, review by Daniel Bünzli, Alain Frisch and
|
|
Gabriel Scherer)
|
|
|
|
- #7515, #1147: Arg.align now optionally uses the tab character '\t' to
|
|
separate the "unaligned" and "aligned" parts of the documentation string. If
|
|
tab is not present, then space is used as a fallback. Allows to have spaces in
|
|
the unaligned part, which is useful for Tuple options.
|
|
(Nicolás Ojeda Bär, review by Alain Frisch and Gabriel Scherer)
|
|
|
|
* #615: Format, add symbolic formatters that output symbolic
|
|
pretty-printing items. New fields have been added to the
|
|
formatter_out_functions record, thus this change will break any code building
|
|
such record from scratch.
|
|
When building Format.formatter_out_functions values redefining the out_spaces
|
|
field, "{ fmt_out_funs with out_spaces = f; }" should be replaced by
|
|
"{ fmt_out_funs with out_spaces = f; out_indent = f; }" to maintain the old
|
|
behavior.
|
|
(Richard Bonichon and Pierre Weis, review by Alain Frisch, original request by
|
|
Spiros Eliopoulos in #506)
|
|
|
|
* #943: Fixed the divergence of the Pervasives module between the stdlib
|
|
and threads implementations. In rare circumstances this can change the
|
|
behavior of existing applications: the implementation of Pervasives.close_out
|
|
used when compiling with thread support was inconsistent with the manual.
|
|
It will now not suppress exceptions escaping Pervasives.flush anymore.
|
|
Developers who want the old behavior should use Pervasives.close_out_noerr
|
|
instead. The stdlib implementation, used by applications not compiled
|
|
with thread support, will now only suppress Sys_error exceptions in
|
|
Pervasives.flush_all. This should allow exceedingly unlikely assertion
|
|
exceptions to escape, which could help reveal bugs in the standard library.
|
|
(Markus Mottl, review by Hezekiah M. Carty, Jérémie Dimino, Damien Doligez,
|
|
Alain Frisch, Xavier Leroy, Gabriel Scherer and Mark Shinwell)
|
|
|
|
- #1034: List.init : int -> (int -> 'a) -> 'a list
|
|
(Richard Degenne, review by David Allsopp, Thomas Braibant, Florian
|
|
Angeletti, Gabriel Scherer, Nathan Moreau, Alain Frisch)
|
|
|
|
- #1091 Add the Uchar.{bom,rep} constants.
|
|
(Daniel Bünzli, Alain Frisch)
|
|
|
|
- #1091: Add Buffer.add_utf_{8,16le,16be}_uchar to encode Uchar.t
|
|
values to the corresponding UTF-X transformation formats in Buffer.t
|
|
values.
|
|
(Daniel Bünzli, review by Damien Doligez, Max Mouratov)
|
|
|
|
- #1175: Bigarray, add a change_layout function to each Array[N]
|
|
submodules.
|
|
(Florian Angeletti)
|
|
|
|
* #1306: In the MSVC and Mingw ports, "Sys.rename src dst" no longer fails if
|
|
file "dst" exists, but replaces it with file "src", like in the other ports.
|
|
(Xavier Leroy)
|
|
|
|
- #1314: Format, use the optional width information
|
|
when formatting a boolean: "%8B", "%-8B" for example
|
|
(Xavier Clerc, review by Gabriel Scherer)
|
|
|
|
- c9cc0f25138ce58e4f4e68c4219afe33e2a9d034: Resurrect tabulation boxes
|
|
in module Format. Rewrite/extend documentation of tabulation boxes.
|
|
(Pierre Weis)
|
|
|
|
### Other libraries:
|
|
|
|
- #7564, #1211: Allow forward slashes in the target of symbolic links
|
|
created by Unix.symlink under Windows.
|
|
(Nicolás Ojeda Bär, review by David Allsopp)
|
|
|
|
* #7640, #1414: reimplementation of Unix.execvpe to fix issues
|
|
with the 4.05 implementation. The main issue is that the current
|
|
directory was always searched (last), even if the current directory
|
|
is not listed in the PATH.
|
|
(Xavier Leroy, report by Louis Gesbert and Arseniy Alekseyev,
|
|
review by Ivan Gotovchits)
|
|
|
|
- #997, #1077: Deprecate Bigarray.*.map_file and add Unix.map_file as a
|
|
first step towards moving Bigarray to the stdlib
|
|
(Jérémie Dimino and Xavier Leroy)
|
|
|
|
* #1178: remove the Num library for arbitrary-precision arithmetic.
|
|
It now lives as a separate project https://github.com/ocaml/num
|
|
with an OPAM package called "num".
|
|
(Xavier Leroy)
|
|
|
|
- #1217: Restrict Unix.environment in privileged contexts; add
|
|
Unix.unsafe_environment.
|
|
(Jeremy Yallop, review by Mark Shinwell, Nicolás Ojeda Bär,
|
|
Damien Doligez and Hannes Mehnert)
|
|
|
|
- #1321: Reimplement Unix.isatty on Windows. It no longer returns true for
|
|
the null device.
|
|
(David Allsopp)
|
|
|
|
### Compiler user-interface and warnings:
|
|
|
|
- #7361, #1248: support "ocaml.warning" in all attribute contexts, and
|
|
arrange so that "ocaml.ppwarning" is correctly scoped by surrounding
|
|
"ocaml.warning" attributes
|
|
(Alain Frisch, review by Florian Angeletti and Thomas Refis)
|
|
|
|
- #7444, #1138: trigger deprecation warning when a "deprecated"
|
|
attribute is hidden by signature coercion
|
|
(Alain Frisch, report by bmillwood, review by Leo White)
|
|
|
|
- #7472: ensure .cmi files are created atomically,
|
|
to avoid corruption of .cmi files produced simultaneously by a run
|
|
of ocamlc and a run of ocamlopt.
|
|
(Xavier Leroy, from a suggestion by Gerd Stolpmann)
|
|
|
|
* #7514, #1152: add -dprofile option, similar to -dtimings but
|
|
also displays memory allocation and consumption.
|
|
The corresponding addition of a new compiler-internal
|
|
Profile module may affect some users of
|
|
compilers-libs/ocamlcommon (by creating module conflicts).
|
|
(Valentin Gatien-Baron, report by Gabriel Scherer)
|
|
|
|
- #7620, #1317: Typecore.force_delayed_checks does not run with -i option
|
|
(Jacques Garrigue, report by Jun Furuse)
|
|
|
|
- #7624: handle warning attributes placed on let bindings
|
|
(Xavier Clerc, report by dinosaure, review by Alain Frisch)
|
|
|
|
- #896: "-compat-32" is now taken into account when building .cmo/.cma
|
|
(Hugo Heuzard)
|
|
|
|
- #948: the compiler now reports warnings-as-errors by prefixing
|
|
them with "Error (warning ..):", instead of "Warning ..:" and
|
|
a trailing "Error: Some fatal warnings were triggered" message.
|
|
(Valentin Gatien-Baron, review by Alain Frisch)
|
|
|
|
- #1032: display the output of -dtimings as a hierarchy
|
|
(Valentin Gatien-Baron, review by Gabriel Scherer)
|
|
|
|
- #1114, #1393, #1429: refine the (ocamlc -config) information
|
|
on C compilers: the variables `{bytecode,native}_c_compiler` are deprecated
|
|
(the distinction is now mostly meaningless) in favor of a single
|
|
`c_compiler` variable combined with `ocaml{c,opt}_cflags`
|
|
and `ocaml{c,opt}_cppflags`.
|
|
(Sébastien Hinderer, Jeremy Yallop, Gabriel Scherer, review by
|
|
Adrien Nader and David Allsopp)
|
|
|
|
* #1189: allow MSVC ports to use -l option in ocamlmklib
|
|
(David Allsopp)
|
|
|
|
- #1332: fix ocamlc handling of "-output-complete-obj"
|
|
(François Bobot)
|
|
|
|
- #1336: -thread and -vmthread option information is propagated to
|
|
PPX rewriters.
|
|
(Jun Furuse, review by Alain Frisch)
|
|
|
|
### Code generation and optimizations:
|
|
|
|
- #5324, #375: An alternative Linear Scan register allocator for
|
|
ocamlopt, activated with the -linscan command-line flag. This
|
|
allocator represents a trade-off between worse generated code
|
|
performance for higher compilation speed (especially interesting in
|
|
some cases graph coloring is necessarily quadratic).
|
|
(Marcell Fischbach and Benedikt Meurer, adapted by Nicolás Ojeda Bär, review
|
|
by Nicolás Ojeda Bär and Alain Frisch)
|
|
|
|
- #6927, #988: On macOS, when compiling bytecode stubs, plugins,
|
|
and shared libraries through -output-obj, generate dylibs instead of
|
|
bundles.
|
|
(whitequark)
|
|
|
|
- #7447, #995: incorrect code generation for nested recursive bindings
|
|
(Leo White and Jeremy Yallop, report by Stephen Dolan)
|
|
|
|
- #7501, #1089: Consider arrays of length zero as constants
|
|
when using Flambda.
|
|
(Pierre Chambart, review by Mark Shinwell and Leo White)
|
|
|
|
- #7531, #1162: Erroneous code transformation at partial applications
|
|
(Mark Shinwell)
|
|
|
|
- #7614, #1313: Ensure that inlining does not depend on the order
|
|
of symbols (flambda)
|
|
(Leo White, Xavier Clerc, report by Alex, review by Gabriel Scherer
|
|
and Pierre Chambart)
|
|
|
|
- #7616, #1339: don't warn on mutation of zero size blocks.
|
|
(Leo White)
|
|
|
|
- #7631, #1355: "-linscan" option crashes ocamlopt
|
|
(Xavier Clerc, report by Paul Steckler)
|
|
|
|
- #7642, #1411: ARM port: wrong register allocation for integer
|
|
multiply on ARMv4 and ARMv5; possible wrong register allocation for
|
|
floating-point multiply and add on VFP and for floating-point
|
|
negation and absolute value on soft FP emulation.
|
|
(Xavier Leroy, report by Stéphane Glondu and Ximin Luo,
|
|
review and additional sightings by Mark Shinwell)
|
|
|
|
* #659: Remove support for SPARC native code generation
|
|
(Mark Shinwell)
|
|
|
|
- #850: Optimize away some physical equality
|
|
(Pierre Chambart, review by Mark Shinwell and Leo White)
|
|
|
|
- #856: Register availability analysis
|
|
(Mark Shinwell, Thomas Refis, review by Pierre Chambart)
|
|
|
|
- #1143: tweaked several allocation functions in the runtime by
|
|
checking for likely conditions before unlikely ones and eliminating
|
|
some redundant checks.
|
|
(Markus Mottl, review by Alain Frisch, Xavier Leroy, Gabriel Scherer,
|
|
Mark Shinwell and Leo White)
|
|
|
|
- #1183: compile curried functors to multi-argument functions
|
|
earlier in the compiler pipeline; correctly propagate [@@inline]
|
|
attributes on such functors; mark functor coercion veneers as
|
|
stubs.
|
|
(Mark Shinwell, review by Pierre Chambart and Leo White)
|
|
|
|
- #1195: Merge functions based on partiality rather than
|
|
Parmatch.irrefutable.
|
|
(Leo White, review by Thomas Refis, Alain Frisch and Gabriel Scherer)
|
|
|
|
- #1215: Improve compilation of short-circuit operators
|
|
(Leo White, review by Frédéric Bour and Mark Shinwell)
|
|
|
|
- #1250: illegal ARM64 assembly code generated for large combined allocations
|
|
(report and initial fix by Steve Walk, review and final fix by Xavier Leroy)
|
|
|
|
- #1271: Don't generate Ialloc instructions for closures that exceed
|
|
Max_young_wosize; instead allocate them on the major heap. (Related
|
|
to #1250.)
|
|
(Mark Shinwell)
|
|
|
|
- #1294: Add a configure-time option to remove the dynamic float array
|
|
optimization and add a floatarray type to let the user choose when to
|
|
flatten float arrays. Note that float-only records are unchanged: they
|
|
are still optimized by unboxing their fields.
|
|
(Damien Doligez, review by Alain Frisch and Mark Shinwell)
|
|
|
|
- #1304: Mark registers clobbered by PLT stubs as destroyed across
|
|
allocations.
|
|
(Mark Shinwell, Xavier Clerc, report and initial debugging by
|
|
Valentin Gatien-Baron)
|
|
|
|
- #1323: make sure that frame tables are generated in the data
|
|
section and not in the read-only data section, as was the case
|
|
before in the PPC and System-Z ports. This avoids relocations in
|
|
the text segment of shared libraries and position-independent
|
|
executables generated by ocamlopt.
|
|
(Xavier Leroy, review by Mark Shinwell)
|
|
|
|
- #1330: when generating dynamically-linkable code on AArch64, always
|
|
reference symbols (even locally-defined ones) through the GOT.
|
|
(Mark Shinwell, review by Xavier Leroy)
|
|
|
|
### Tools:
|
|
|
|
- #8395, #973: tools/check-symbol-names checks for globally
|
|
linked names not namespaced with caml_
|
|
(Stephen Dolan)
|
|
|
|
- #6928, #1103: ocamldoc, do not introduce an empty <h1> in index.html
|
|
when no -title has been provided
|
|
(Pierre Boutillier)
|
|
|
|
- #7048: ocamldoc, in -latex mode, don't escape Latin-1 accented letters
|
|
(Xavier Leroy, report by Hugo Herbelin)
|
|
|
|
* #7351: ocamldoc, use semantic tags rather than <br> tags in the html
|
|
backend
|
|
(Florian Angeletti, request and review by Daniel Bünzli )
|
|
|
|
* #7352, #7353: ocamldoc, better paragraphs in html output
|
|
(Florian Angeletti, request by Daniel Bünzli)
|
|
|
|
* #7363, #830: ocamldoc, start heading levels at {1 not {2 or {6.
|
|
This change modifies the mapping between ocamldoc heading level and
|
|
html heading level, breaking custom css style for ocamldoc.
|
|
(Florian Angeletti, request and review by Daniel Bünzli)
|
|
|
|
* #7478, #1037: ocamldoc, do not use as a module preamble documentation
|
|
comments that occur after the first module element. This change may break
|
|
existing documentation. In particular, module preambles must now come before
|
|
any `open` statement.
|
|
(Florian Angeletti, review by David Allsopp and report by Daniel Bünzli)
|
|
|
|
- #7521, #1159: ocamldoc, end generated latex file with a new line
|
|
(Florian Angeletti)
|
|
|
|
- #7575, #1219: Switch compilers from -no-keep-locs
|
|
to -keep-locs by default: produced .cmi files will contain locations.
|
|
This provides better error messages. Note that, as a consequence,
|
|
.cmi digests now depend on the file path as given to the compiler.
|
|
(Daniel Bünzli)
|
|
|
|
- #7610, #1346: caml.el (the Emacs editing mode) was cleaned up
|
|
and made compatible with Emacs 25.
|
|
(Stefan Monnier, Christophe Troestler)
|
|
|
|
- #7635, #1383: ocamldoc, add an identifier to module
|
|
and module type elements
|
|
(Florian Angeletti, review by Yawar Amin and Gabriel Scherer)
|
|
|
|
- #681, #1426: Introduce ocamltest, a new test driver for the
|
|
OCaml compiler testsuite
|
|
(Sébastien Hinderer, review by Damien Doligez)
|
|
|
|
- #1012: ocamlyacc, fix parsing of raw strings and nested comments, as well
|
|
as the handling of ' characters in identifiers.
|
|
(Demi Obenour)
|
|
|
|
- #1045: ocamldep, add a "-shared" option to generate dependencies
|
|
for native plugin files (i.e. .cmxs files)
|
|
(Florian Angeletti, suggestion by Sébastien Hinderer)
|
|
|
|
- #1078: add a subcommand "-depend" to "ocamlc" and "ocamlopt",
|
|
to behave as ocamldep. Should be used mostly to replace "ocamldep" in the
|
|
"boot" directory to reduce its size in the future.
|
|
(Fabrice Le Fessant)
|
|
|
|
- #1036: ocamlcmt (tools/read_cmt) is installed, converts .cmt to .annot
|
|
(Fabrice Le Fessant)
|
|
|
|
- #1180: Add support for recording numbers of direct and indirect
|
|
calls over the lifetime of a program when using Spacetime profiling
|
|
(Mark Shinwell)
|
|
|
|
- #1457, ocamldoc: restore label for exception in the latex backend
|
|
(omitted since 4.04.0)
|
|
(Florian Angeletti, review by Gabriel Scherer)
|
|
|
|
### Toplevel:
|
|
|
|
- #7570: remove unusable -plugin option from the toplevel
|
|
(Florian Angeletti)
|
|
|
|
- #1041: -nostdlib no longer ignored by toplevel.
|
|
(David Allsopp, review by Xavier Leroy)
|
|
|
|
- #1231: improved printing of unicode texts in the toplevel,
|
|
unless OCAMLTOP_UTF_8 is set to false.
|
|
(Florian Angeletti, review by Daniel Bünzli, Xavier Leroy and
|
|
Gabriel Scherer)
|
|
|
|
- #1688: Fix printing of -0.
|
|
(Nicolás Ojeda Bär, review by Jérémie Dimino)
|
|
|
|
### Runtime system:
|
|
|
|
* #3771, #153, #1200, #1357, #1362, #1363, #1369, #1398,
|
|
#1446, #1448: Unicode support for the Windows runtime.
|
|
(ygrek, Nicolás Ojeda Bär, review by Alain Frisch, David Allsopp, Damien
|
|
Doligez)
|
|
|
|
* #7594, #1274, #1368: String_val now returns 'const char*', not
|
|
'char*' when -safe-string is enabled at configure time. New macro Bytes_val
|
|
for accessing bytes values.
|
|
(Jeremy Yallop, reviews by Mark Shinwell and Xavier Leroy)
|
|
|
|
- #71: The runtime can now be shut down gracefully by means of the new
|
|
caml_shutdown and caml_startup_pooled functions. The new 'c' flag in
|
|
OCAMLRUNPARAM enables shutting the runtime properly on process exit.
|
|
(Max Mouratov, review and discussion by Damien Doligez, Gabriel Scherer,
|
|
Mark Shinwell, Thomas Braibant, Stephen Dolan, Pierre Chambart,
|
|
François Bobot, Jacques Garrigue, David Allsopp, and Alain Frisch)
|
|
|
|
- #938, #1170, #1289: Stack overflow detection on 64-bit Windows
|
|
(Olivier Andrieu, tweaked by David Allsopp)
|
|
|
|
- #1070, #1295: enable gcc typechecking for caml_alloc_sprintf,
|
|
caml_gc_message. Make caml_gc_message a variadic function. Fix many
|
|
caml_gc_message format strings.
|
|
(Olivier Andrieu, review and 32bit fix by David Allsopp)
|
|
|
|
- #1073: Remove statically allocated compare stack.
|
|
(Stephen Dolan)
|
|
|
|
- #1086: in Sys.getcwd, just fail instead of calling getwd()
|
|
if HAS_GETCWD is not set.
|
|
(Report and first fix by Sebastian Markbåge, final fix by Xavier Leroy,
|
|
review by Mark Shinwell)
|
|
|
|
- #1269: Remove 50ms delay at exit for programs using threads
|
|
(Valentin Gatien-Baron, review by Stephen Dolan)
|
|
|
|
* #1309: open files with O_CLOEXEC (or equivalent) in caml_sys_open, thus
|
|
unifying the semantics between Unix and Windows and also eliminating race
|
|
condition on Unix.
|
|
(David Allsopp, report by Andreas Hauptmann)
|
|
|
|
- #1326: Enable use of CFI directives in AArch64 and ARM runtime
|
|
systems' assembly code (asmrun/arm64.S). Add CFI directives to enable
|
|
unwinding through [caml_c_call] and [caml_call_gc] with correct termination
|
|
of unwinding at [main].
|
|
(Mark Shinwell, review by Xavier Leroy and Gabriel Scherer, with thanks
|
|
to Daniel Bünzli and Fu Yong Quah for testing)
|
|
|
|
- #1338: Add "-g" for bytecode runtime system compilation
|
|
(Mark Shinwell)
|
|
|
|
* #1416, #1444: switch the Windows 10 Console to UTF-8 encoding.
|
|
(David Allsopp, reviews by Nicolás Ojeda Bär and Xavier Leroy)
|
|
|
|
### Manual and documentation:
|
|
|
|
- #6548: remove obsolete limitation in the description of private
|
|
type abbreviations
|
|
(Florian Angeletti, suggestion by Leo White)
|
|
|
|
- #6676, #1110: move record notation to tutorial
|
|
(Florian Angeletti, review by Gabriel Scherer)
|
|
|
|
- #6676, #1112: move local opens to tutorial
|
|
(Florian Angeletti)
|
|
|
|
- #6676, #1153: move overriding class definitions to reference
|
|
manual and tutorial
|
|
(Florian Angeletti)
|
|
|
|
- #6709: document the associativity and precedence level of
|
|
pervasive operators
|
|
(Florian Angeletti, review by David Allsopp)
|
|
|
|
- #7254, #1096: Rudimentary documentation of ocamlnat
|
|
(Mark Shinwell)
|
|
|
|
- #7281, #1259: fix .TH macros in generated manpages
|
|
(Olaf Hering)
|
|
|
|
- #7507: Align the description of the printf conversion
|
|
specification "%g" with the ISO C90 description.
|
|
(Florian Angeletti, suggestion by Armaël Guéneau)
|
|
|
|
- #7551, #1194 : make the final ";;" potentially optional in
|
|
caml_example
|
|
(Florian Angeletti, review and suggestion by Gabriel Scherer)
|
|
|
|
- #7588, #1291: make format documentation predictable
|
|
(Florian Angeletti, review by Gabriel Radanne)
|
|
|
|
- #7604: Minor Ephemeron documentation fixes
|
|
(Miod Vallat, review by Florian Angeletti)
|
|
|
|
- #594: New chapter on polymorphism troubles:
|
|
weakly polymorphic types, polymorphic recursion,and higher-ranked
|
|
polymorphism.
|
|
(Florian Angeletti, review by Damien Doligez, Gabriel Scherer,
|
|
and Gerd Stolpmann)
|
|
|
|
- #1187: Minimal documentation for compiler plugins
|
|
(Florian Angeletti)
|
|
|
|
- #1202: Fix Typos in comments as well as basic grammar errors.
|
|
(JP Rodi, review and suggestions by David Allsopp, Max Mouratov,
|
|
Florian Angeletti, Xavier Leroy, Mark Shinwell and Damien Doligez)
|
|
|
|
- #1220: Fix "-keep-docs" option in ocamlopt manpage
|
|
(Etienne Millon)
|
|
|
|
### Compiler distribution build system:
|
|
|
|
- #6373, #1093: Suppress trigraph warnings from macOS assembler
|
|
(Mark Shinwell)
|
|
|
|
- #7639, #1371: fix configure script for correct detection of
|
|
int64 alignment on Mac OS X 10.13 (High Sierra) and above; fix bug in
|
|
configure script relating to such detection.
|
|
(Mark Shinwell, report by John Whitington, review by Xavier Leroy)
|
|
|
|
- #558: enable shared library and natdynlink support on more Linux
|
|
platforms
|
|
(Felix Janda, Mark Shinwell)
|
|
|
|
* #1104: remove support for the NeXTStep platform
|
|
(Sébastien Hinderer)
|
|
|
|
- #1130: enable detection of IBM XL C compiler (one need to run configure
|
|
with "-cc <path to xlc compiler>"). Enable shared library support for
|
|
bytecode executables on AIX/xlc (tested on AIX 7.1, XL C 12).
|
|
To enable 64-bit, run both "configure" and "make world" with OBJECT_MODE=64.
|
|
(Konstantin Romanov, Enrique Naudon)
|
|
|
|
- #1203: speed up the manual build by using ocamldoc.opt
|
|
(Gabriel Scherer, review by Florian Angeletti)
|
|
|
|
- #1214: harden config/Makefile against '#' characters in PREFIX
|
|
(Gabriel Scherer, review by David Allsopp and Damien Doligez)
|
|
|
|
- #1216: move Compplugin and friends from BYTECOMP to COMP
|
|
(Leo White, review by Mark Shinwell)
|
|
|
|
* #1242: disable C plugins loading by default
|
|
(Alexey Egorov)
|
|
|
|
- #1275: correct configure test for Spacetime availability
|
|
(Mark Shinwell)
|
|
|
|
- #1278: discover presence of <sys/shm.h> during configure for afl runtime
|
|
(Hannes Mehnert)
|
|
|
|
- #1386: provide configure-time options to fine-tune the safe-string
|
|
options and default settings changed by #1252.
|
|
|
|
The previous configure option -safe-string is now
|
|
renamed -force-safe-string.
|
|
|
|
At configure-time, -force-safe-string forces all module to use
|
|
immutable strings (this disables the per-file, compile-time
|
|
-unsafe-string option). The new default-(un)safe-string options
|
|
let you set the default choice for the per-file compile-time
|
|
option. (The new #1252 behavior corresponds to having
|
|
-default-safe-string, while 4.05 and older had
|
|
-default-unsafe-string).
|
|
|
|
(Gabriel Scherer, review by Kate Deplaix and Damien Doligez)
|
|
|
|
- #1409: Fix to enable NetBSD/powerpc to work.
|
|
(Håvard Eidnes)
|
|
|
|
### Internal/compiler-libs changes:
|
|
|
|
- #6826, #828, #834: improve compilation time for open
|
|
(Alain Frisch, review by Frédéric Bour and Jacques Garrigue)
|
|
|
|
- #7127, #454, #1058: in toplevel, print bytes and strip
|
|
strings longer than the size specified by the "print_length" directive
|
|
(Fabrice Le Fessant, initial PR by Junsong Li)
|
|
|
|
- #406: remove polymorphic comparison for Types.constructor_tag in compiler
|
|
(Dwight Guth, review by Gabriel Radanne, Damien Doligez, Gabriel Scherer,
|
|
Pierre Chambart, Mark Shinwell)
|
|
|
|
- #1119: Change Set (private) type to inline records.
|
|
(Albin Coquereau)
|
|
|
|
* #1127: move config/{m,s}.h to byterun/caml and install them.
|
|
User code should not have to include them directly since they are
|
|
included by other header files.
|
|
Previously {m,s}.h were not installed but they were substituted into
|
|
caml/config.h; they are now just #include-d by this file. This may
|
|
break some scripts relying on the (unspecified) presence of certain
|
|
#define in config.h instead of m.h and s.h -- they can be rewritten
|
|
to try to grep those files if they exist.
|
|
(Sébastien Hinderer)
|
|
|
|
- #1281: avoid formatter flushes inside exported printers in Location
|
|
(Florian Angeletti, review by Gabriel Scherer)
|
|
|
|
### Bug fixes:
|
|
|
|
- #5927: Type equality broken for conjunctive polymorphic variant tags
|
|
(Jacques Garrigue, report by Leo White)
|
|
|
|
- #6329, #1437: Introduce padding word before "data_end" symbols
|
|
to ensure page table tests work correctly on an immediately preceding
|
|
block of zero size.
|
|
(Mark Shinwell, review by Xavier Leroy)
|
|
|
|
- #6587: only elide Pervasives from printed type paths in unambiguous context
|
|
(Florian Angeletti and Jacques Garrigue)
|
|
|
|
- #6934: nonrec misbehaves with GADTs
|
|
(Jacques Garrigue, report by Markus Mottl)
|
|
|
|
- #7070, #1139: Unexported values can cause non-generalisable variables
|
|
error
|
|
(Leo White)
|
|
|
|
- #7261: Warn on type constraints in GADT declarations
|
|
(Jacques Garrigue, report by Fabrice Le Botlan)
|
|
|
|
- #7321: Private type in signature clashes with type definition via
|
|
functor instantiation
|
|
(Jacques Garrigue, report by Markus Mottl)
|
|
|
|
- #7372, #834: fix type-checker bug with GADT and inline records
|
|
(Alain Frisch, review by Frédéric Bour and Jacques Garrigue)
|
|
|
|
- #7344: Inconsistent behavior with type annotations on let
|
|
(Jacques Garrigue, report by Leo White)
|
|
|
|
- #7468: possible GC problem in caml_alloc_sprintf
|
|
(Xavier Leroy, discovery by Olivier Andrieu)
|
|
|
|
- #7496: Fixed conjunctive polymorphic variant tags do not unify
|
|
with themselves
|
|
(Jacques Garrigue, report by Leo White)
|
|
|
|
- #7506: pprintast ignores attributes in tails of a list
|
|
(Alain Frisch, report by Kenichi Asai and Gabriel Scherer)
|
|
|
|
- #7513: List.compare_length_with mishandles negative numbers / overflow
|
|
(Fabrice Le Fessant, report by Jeremy Yallop)
|
|
|
|
- #7519: Incorrect rejection of program due to faux scope escape
|
|
(Jacques Garrigue, report by Markus Mottl)
|
|
|
|
- #7540, #1179: Fixed setting of breakpoints within packed modules
|
|
for ocamldebug
|
|
(Hugo Herbelin, review by Gabriel Scherer, Damien Doligez)
|
|
|
|
- #7543: short-paths printtyp can fail on packed type error messages
|
|
(Florian Angeletti)
|
|
|
|
- #7553, #1191: Prevent repeated warnings with recursive modules.
|
|
(Leo White, review by Josh Berdine and Alain Frisch)
|
|
|
|
- #7563, #1210: code generation bug when a module alias and
|
|
an extension constructor have the same name in the same module
|
|
(Gabriel Scherer, report by Manuel Fähndrich,
|
|
review by Jacques Garrigue and Leo White)
|
|
|
|
- #7591, #1257: on x86-64, frame table is not 8-aligned
|
|
(Xavier Leroy, report by Mantis user "voglerr", review by Gabriel Scherer)
|
|
|
|
- #7601, #1320: It seems like a hidden non-generalized type variable
|
|
remains in some inferred signatures, which leads to strange errors
|
|
(Jacques Garrigue, report by Mandrikin)
|
|
|
|
- #7609: use-after-free memory corruption if a program debugged
|
|
under ocamldebug calls Pervasives.flush_all
|
|
(Xavier Leroy, report by Paul Steckler, review by Gabriel Scherer)
|
|
|
|
- #7612, #1345: afl-instrumentation bugfix for classes.
|
|
(Stephen Dolan, review by Gabriel Scherer and David Allsopp)
|
|
|
|
- #7617, #7618, #1318: Ambiguous (mistakenly) type escaping the
|
|
scope of its equation
|
|
(Jacques Garrigue, report by Thomas Refis)
|
|
|
|
- #7619, #1387: position of the optional last semi-column not included
|
|
in the position of the expression (same behavior as for lists)
|
|
(Christophe Raffalli, review by Gabriel Scherer)
|
|
|
|
- #7638: in the Windows Mingw64 port, multithreaded programs compiled
|
|
to bytecode could crash when raising an exception from C code.
|
|
This looks like a Mingw64 issue, which we work around with GCC builtins.
|
|
(Xavier Leroy)
|
|
|
|
- #7656, #1423: false 'unused type/constructor/value' alarms
|
|
in the 4.06 development version
|
|
(Alain Frisch, review by Jacques Garrigue, report by Kate Deplaix)
|
|
|
|
- #7657, #1424: ensures correct call-by-value semantics when
|
|
eta-expanding functions to eliminate optional arguments
|
|
(Alain Frisch, report by sliquister, review by Leo White and Jacques
|
|
Garrigue)
|
|
|
|
- #7658, #1439: Fix Spacetime runtime system compilation with
|
|
-force-safe-string
|
|
(Mark Shinwell, report by Christoph Spiel, review by Gabriel Scherer)
|
|
|
|
- #1155: Fix a race condition with WAIT_NOHANG on Windows
|
|
(Jérémie Dimino and David Allsopp)
|
|
|
|
- #1199: Pretty-printing formatting cleanup in pprintast
|
|
(Ethan Aubin, suggestion by Gabriel Scherer, review by David Allsopp,
|
|
Florian Angeletti, and Gabriel Scherer)
|
|
|
|
- #1223: Fix corruption of the environment when using -short-paths
|
|
with the toplevel.
|
|
(Leo White, review by Alain Frisch)
|
|
|
|
- #1243: Fix pprintast for #... infix operators
|
|
(Alain Frisch, report by Omar Chebib)
|
|
|
|
- #1324: ensure that flambda warning are printed only once
|
|
(Xavier Clerc)
|
|
|
|
- #1329: Prevent recursive polymorphic variant names
|
|
(Jacques Garrigue, fix suggested by Leo White)
|
|
|
|
- #1308: Only treat pure patterns as inactive
|
|
(Leo White, review by Alain Frisch and Gabriel Scherer)
|
|
|
|
- #1390: fix the [@@unboxed] type check to accept parametrized types
|
|
(Leo White, review by Damien Doligez)
|
|
|
|
- #1407: Fix raw_spacetime_lib
|
|
(Leo White, review by Gabriel Scherer and Damien Doligez)
|
|
|
|
OCaml 4.05.0 (13 Jul 2017):
|
|
---------------------------
|
|
|
|
(Changes that can break existing programs are marked with a "*")
|
|
|
|
### Language features:
|
|
|
|
### Code generation and optimizations:
|
|
|
|
- #7201, #954: Correct wrong optimisation of "0 / <expr>"
|
|
and "0 mod <expr>" in the case when <expr> was a non-constant
|
|
evaluating to zero
|
|
(Mark Shinwell, review by Gabriel Scherer, Leo White and Xavier Leroy)
|
|
|
|
- #7357, #832: Improve compilation time for toplevel
|
|
include(struct ... end : sig ... end)
|
|
(Alain Frisch, report by Hongbo Zhang, review by Jacques Garrigue)
|
|
|
|
- #7533, #1173: Correctly perform side effects for certain
|
|
cases of "/" and "mod"
|
|
(Mark Shinwell, report by Jan Mitgaard)
|
|
|
|
- #504: Instrumentation support for fuzzing with afl-fuzz.
|
|
(Stephen Dolan, review by Alain Frisch, Pierre Chambart, Mark
|
|
Shinwell, Gabriel Scherer and Damien Doligez)
|
|
|
|
- #863, #1068, #1069: Optimise matches with constant
|
|
results to lookup tables.
|
|
(Stephen Dolan, review by Gabriel Scherer, Pierre Chambart,
|
|
Mark Shinwell, and bug report by Gabriel Scherer)
|
|
|
|
- #1150: Fix typo in arm64 assembler directives
|
|
(KC Sivaramakrishnan)
|
|
|
|
### Runtime system:
|
|
|
|
- #2784, #953: Add caml_startup_exn
|
|
(Mark Shinwell)
|
|
|
|
- #7423, #946: expose new exception-raising functions
|
|
`void caml_{failwith,invalid_argument}_value(value msg)`
|
|
in addition to
|
|
`void caml_{failwith,invalid_argument}(char const *msg)`.
|
|
The previous functions would not free their message argument, so
|
|
were inconvient for dynamically-allocated messages; the messages
|
|
passed to the new functions are handled by the garbage collector.
|
|
(Gabriel Scherer, review by Mark Shinwell, request by Immanuel Litzroth)
|
|
|
|
- #7557, #1213: More security for getenv
|
|
(Damien Doligez, reports by Seth Arnold and Eric Milliken, review by
|
|
Xavier Leroy, David Allsopp, Stephen Dolan, Hannes Mehnert)
|
|
|
|
- #795: remove 256-character limitation on Sys.executable_name
|
|
(Xavier Leroy)
|
|
|
|
- #891: Use -fno-builtin-memcmp when building runtime with gcc.
|
|
(Leo White)
|
|
|
|
### Type system:
|
|
|
|
- #6608, #901: unify record types when overriding all fields
|
|
(Tadeu Zagallo and Gabriel Scherer, report by Jeremy Yallop,
|
|
review by David Allsopp, Jacques Garrigue)
|
|
|
|
* #7414, #929: Soundness bug with non-generalized type variables and
|
|
functors.
|
|
(compatibility: some code using module-global mutable state will
|
|
fail at compile-time and is fixed by adding extra annotations;
|
|
see the Mantis and Github discussions.)
|
|
(Jacques Garrigue, report by Leo White)
|
|
|
|
### Compiler user-interface and warnings:
|
|
|
|
- #7050, #748 #843 #864: new `-args/-args0 <file>` parameters to
|
|
provide extra command-line arguments in a file -- see documentation.
|
|
User programs may implement similar options using the new `Expand`
|
|
constructor of the `Arg` module.
|
|
(Bernhard Schommer, review by Jérémie Dimino, Gabriel Scherer
|
|
and Damien Doligez, discussion with Alain Frisch and Xavier Leroy,
|
|
feature request from the Coq team)
|
|
|
|
- #7137, #960: "-open" command line flag now accepts
|
|
a module path (not a module name)
|
|
(Arseniy Alekseyev and Leo White)
|
|
|
|
- #7172, #970: add extra (ocamlc -config) options
|
|
int_size, word_size, ext_exe
|
|
(Gabriel Scherer, request by Daniel Bünzli)
|
|
|
|
- #7315, #736: refine some error locations
|
|
(Gabriel Scherer and Alain Frisch, report by Matej Košík)
|
|
|
|
- #7473, #1025: perform proper globbing for command-line arguments on
|
|
Windows
|
|
(Jonathan Protzenko)
|
|
|
|
- #7479: make sure "ocamlc -pack" is only given .cmo and .cmi files,
|
|
and that "ocamlopt -pack" is only given .cmx and .cmi files.
|
|
(Xavier Leroy)
|
|
|
|
- #796: allow compiler plugins to declare their own arguments.
|
|
(Fabrice Le Fessant)
|
|
|
|
- #829: better error when opening a module aliased to a functor
|
|
(Alain Frisch)
|
|
|
|
- #911: ocamlc/ocamlopt do not pass warnings-related options to C
|
|
compiler when called to compile third-party C source files
|
|
(Sébastien Hinderer, review by Adrien Nader and David Allsopp)
|
|
|
|
- #915: fix -dsource (pprintast.ml) bugs
|
|
(Runhang Li, review by Alain Frisch)
|
|
|
|
* #933: ocamlopt -p now reports an error on platforms that do not
|
|
support profiling with gprof; dummy profiling libraries are no longer
|
|
installed on such platforms.
|
|
This can be tested with ocamlopt -config
|
|
(Sébastien Hinderer)
|
|
|
|
- #1009: "ocamlc -c -linkall" and "ocamlopt -c -linkall" can now be used
|
|
to set the "always link" flag on individual compilation units. This
|
|
controls linking with finer granularity than "-a -linkall", which sets
|
|
the "always link" flag on all units of the given library.
|
|
(Xavier Leroy)
|
|
|
|
- #1015: add option "-plugin PLUGIN" to ocamldep too. Use compilerlibs
|
|
to build ocamldep. Add option "-depend" to ocamlc/ocamlopt to behave
|
|
as ocamldep. Remove any use of ocamldep to build the distribution.
|
|
(Fabrice Le Fessant)
|
|
|
|
- #1027: various improvements to -dtimings, mostly including time
|
|
spent in subprocesses like preprocessors
|
|
(Valentin Gatien-Baron, review by Gabriel Scherer)
|
|
|
|
- #1098: the compiler now takes the boolean "OCAML_COLOR" environment
|
|
variable into account if "-color" is not provided. This allows users
|
|
to override the default behaviour without modifying invocations of ocaml
|
|
manually.
|
|
(Hannes Mehnert, Guillaume Bury,
|
|
review by Daniel Bünzli, Gabriel Scherer, Damien Doligez)
|
|
|
|
### Standard library:
|
|
|
|
- #6975, #902: Truncate function added to stdlib Buffer module
|
|
(Dhruv Makwana, review by Alain Frisch and Gabriel Scherer)
|
|
|
|
- #7279, #710: `Weak.get_copy` `Ephemeron.*_copy` doesn't copy
|
|
custom blocks anymore
|
|
(François Bobot, Alain Frisch, bug reported by Martin R. Neuhäußer,
|
|
review by Thomas Braibant and Damien Doligez)
|
|
|
|
* #7500, #1081: Remove Uchar.dump
|
|
(Daniel Bünzli)
|
|
|
|
- #760: Add a functions List.compare_lengths and
|
|
List.compare_length_with to avoid full list length computations
|
|
(Fabrice Le Fessant, review by Leo White, Josh Berdine and Gabriel Scherer)
|
|
|
|
- #778: Arg: added option Expand that allows to expand a string
|
|
argument to a string array of new arguments
|
|
(Bernhard Schommer, review by Gabriel Scherer and Jérémie Dimino)
|
|
|
|
- #849: Expose a Spacetime.enabled value
|
|
(Leo White)
|
|
|
|
- #885: Option-returning variants of stdlib functions
|
|
(Alain Frisch, review by David Allsopp and Bart Jacobs)
|
|
|
|
- #869: Add find_first, find_first_opt, find_last, find_last_opt to
|
|
maps and sets. Find the first or last binding or element
|
|
satisfying a monotonic predicate.
|
|
(Gabriel de Perthuis, with contributions from Alain Frisch, review by
|
|
Hezekiah M. Carty and Simon Cruanes, initial report by Gerd Stolpmann)
|
|
|
|
- #875: Add missing functions to ArrayLabels, BytesLabels,
|
|
ListLabels, MoreLabels, StringLabels so they are compatible with
|
|
non-labeled counterparts. Also add missing @@ocaml.deprecated attributes
|
|
in StringLabels and BytesLabels.
|
|
(Roma Sokolov, review by Gabriel Scherer, Jacques Garrigue,
|
|
Gabriel Radanne, Alain Frisch)
|
|
|
|
- #999: Arg, do not repeat the usage message thrice when reporting an error
|
|
(this was a regression in 4.03)
|
|
(Florian Angeletti, review by Gabriel Scherer)
|
|
|
|
- #1042: Fix escaping of command-line arguments in
|
|
Unix.create_process{,_env} under Windows. Arguments with tabs should now
|
|
be received verbatim by the child process.
|
|
(Nicolás Ojeda Bär, Andreas Hauptmann review by Xavier Leroy)
|
|
|
|
### Debugging and profiling:
|
|
|
|
- #7258: ocamldebug's "install_printer" command had problems with
|
|
module aliases
|
|
(Xavier Leroy)
|
|
|
|
- #378: Add [Printexc.raise_with_backtrace] to raise an exception using
|
|
an explicit backtrace
|
|
(François Bobot, review by Gabriel Scherer, Xavier Leroy, Damien Doligez,
|
|
Frédéric Bour)
|
|
|
|
### Manual and documentation:
|
|
|
|
- #6597, #1030: add forward references to language extensions
|
|
that extend non-terminal symbols in the language reference section.
|
|
(Florian Angeletti, review by Gabriel Scherer)
|
|
|
|
- #7497, #1095: manual, enable numbering for table of contents
|
|
(Florian Angeletti, request by Daniel Bünzli)
|
|
|
|
- #7539, #1181: manual, update dead links in ocamldoc chapter
|
|
(Florian Angeletti)
|
|
|
|
- #633: manpage and manual documentation for the `-opaque` option
|
|
(Konstantin Romanov, Gabriel Scherer, review by Mark Shinwell)
|
|
|
|
- #751, #925: add a HACKING.adoc file to contain various
|
|
tips and tricks for people hacking on the repository. See also
|
|
CONTRIBUTING.md for advice on sending contributions upstream.
|
|
(Gabriel Scherer and Gabriel Radanne, review by David Allsopp,
|
|
inspired by John Whitington)
|
|
|
|
- #916: new tool lintapidiff, use it to update the manual with
|
|
@since annotations for API changes introduced between 4.00-4.05.
|
|
(Edwin Török, review by Gabriel Scherer, discussion with Alain Frisch,
|
|
David Allsopp, Sébastien Hinderer, Damien Doligez and Xavier Leroy)
|
|
|
|
- #939: activate the caml_example environment in the language
|
|
extensions section of the manual. Convert some existing code
|
|
examples to this format.
|
|
(Florian Angeletti)
|
|
|
|
- #1082: clarify that the use of quoted string for preprocessed
|
|
foreign quotations still requires the use of an extension node
|
|
[%foo ...] to mark non-standard interpretation.
|
|
(Gabriel Scherer, request by Matthew Wahab in #1066,
|
|
review by Florian Angeletti)
|
|
|
|
### Other libraries:
|
|
|
|
- #7158: Event.sync, Mutex.create, Condition.create cause too many GCs.
|
|
The fix is to no longer consider mutexes and condition variables
|
|
as rare kernel resources.
|
|
(Xavier Leroy)
|
|
|
|
- #7264: document the different behaviors of Unix.lockf under POSIX
|
|
and under Win32.
|
|
(Xavier Leroy, report by David Allsopp)
|
|
|
|
- #7339, #787: Support the '0 dimension' case for bigarrays
|
|
(see Bigarray documentation)
|
|
(Laurent Mazare,
|
|
review by Gabriel Scherer, Alain Frisch and Hezekiah M. Carty)
|
|
|
|
* #7342, #797: fix Unix.read on pipes with no data left on Windows
|
|
it previously raised an EPIPE error, it now returns 0 like other OSes
|
|
(Jonathan Protzenko, review by Andreas Hauptmann and Damien Doligez)
|
|
|
|
- #650: in the Unix library, add `?cloexec:bool` optional arguments to
|
|
functions that create file descriptors (`dup`, `dup2`, `pipe`, `socket`,
|
|
`socketpair`, `accept`). Implement these optional arguments in the
|
|
most atomic manner provided by the operating system to set (or clear)
|
|
the close-on-exec flag at the same time the file descriptor is created,
|
|
reducing the risk of race conditions with `exec` or `create_process`
|
|
calls running in other threads, and improving security. Also: add a
|
|
`O_KEEPEXEC` flag for `openfile` by symmetry with `O_CLOEXEC`.
|
|
(Xavier Leroy, review by Mark Shinwell, David Allsopp and Alain Frisch,
|
|
request by Romain Beauxis)
|
|
|
|
- #996: correctly update caml_top_of_stack in systhreads
|
|
(Fabrice Le Fessant)
|
|
|
|
- #997, #1077: Deprecate Bigarray.*.map_file and add Unix.map_file as a
|
|
first step towards moving Bigarray to the stdlib
|
|
(Jérémie Dimino and Xavier Leroy)
|
|
|
|
### Toplevel:
|
|
|
|
- #7060, #1035: Print exceptions in installed custom printers
|
|
(Tadeu Zagallo, review by David Allsopp)
|
|
|
|
### Tools:
|
|
|
|
- #5163: ocamlobjinfo, dump globals defined by bytecode executables
|
|
(Stéphane Glondu)
|
|
|
|
- #7333: ocamldoc, use the first sentence of text file as
|
|
a short description in overviews.
|
|
(Florian Angeletti)
|
|
|
|
- #848: ocamldoc, escape link targets in HTML output
|
|
(Etienne Millon, review by Gabriel Scherer, Florian Angeletti and
|
|
Daniel Bünzli)
|
|
|
|
- #986: ocamldoc, use relative paths in error message
|
|
to solve ocamlbuild+doc usability issue (ocaml/ocamlbuild#79)
|
|
(Gabriel Scherer, review by Florian Angeletti, discussion with Daniel Bünzli)
|
|
|
|
- #1017: ocamldoc, add an option to detect code fragments that could be
|
|
transformed into a cross-reference to a known element.
|
|
(Florian Angeletti, review and suggestion by David Allsopp)
|
|
|
|
- clarify ocamldoc text parsing error messages
|
|
(Gabriel Scherer)
|
|
|
|
### Compiler distribution build system:
|
|
|
|
- #7377: remove -std=gnu99 for newer gcc versions
|
|
(Damien Doligez, report by ygrek)
|
|
|
|
- #7452, #1228: tweak GCC options to try to avoid the
|
|
Skylake/Kaby lake bug
|
|
(Damien Doligez, review by David Allsopp, Xavier Leroy and Mark Shinwell)
|
|
|
|
- #693: fail on unexpected errors or warnings within caml_example
|
|
environment.
|
|
(Florian Angeletti)
|
|
|
|
- #803: new ocamllex-based tool to extract bytecode compiler
|
|
opcode information from C headers.
|
|
(Nicolás Ojeda Bär)
|
|
|
|
- #827: install missing mli and cmti files, new make target
|
|
install-compiler-sources for installation of compiler-libs ml files
|
|
(Hendrik Tews)
|
|
|
|
- #887: allow -with-frame-pointers if clang is used as compiler on Linux
|
|
(Bernhard Schommer)
|
|
|
|
- #898: fix locale-dependence of primitive list order,
|
|
detected through reproducible-builds.org.
|
|
(Hannes Mehnert, review by Gabriel Scherer and Ximin Luo)
|
|
|
|
- #907: Remove unused variable from the build system
|
|
(Sébastien Hinderer, review by whitequark, Gabriel Scherer, Adrien Nader)
|
|
|
|
- #911: Clarify the use of C compiler related variables in the build system.
|
|
(Sébastien Hinderer, review by Adrien Nader, Alain Frisch, David Allsopp)
|
|
|
|
- #919: use clang as preprocessor assembler if clang is used as compiler
|
|
(Bernhard Schommer)
|
|
|
|
- #927: improve the detection of hashbang support in the configure script
|
|
(Armaël Guéneau)
|
|
|
|
- #932: install ocaml{c,lex}->ocaml{c,lex}.byte symlink correctly
|
|
when the opt target is built but opt.opt target is not.
|
|
(whitequark, review by Gabriel Scherer)
|
|
|
|
- #935: allow build in Android's termux
|
|
(ygrek, review by Gabriel Scherer)
|
|
|
|
- #984: Fix compilation of compiler distribution when Spacetime
|
|
enabled
|
|
(Mark Shinwell)
|
|
|
|
- #991: On Windows, fix installation when native compiler is not
|
|
built
|
|
(Sébastien Hinderer, review by David Allsopp)
|
|
|
|
- #1033: merge Unix and Windows build systems in the root directory
|
|
(Sébastien Hinderer, review by Damien Doligez and Adrien Nader)
|
|
|
|
- #1047: Make .depend files generated for C sources more portable
|
|
(Sébastien Hinderer, review by Xavier Leroy and David Allsopp)
|
|
|
|
- #1076: Simplify ocamlyacc's build system
|
|
(Sébastien Hinderer, review by David Allsopp)
|
|
|
|
### Compiler distribution build system: Makefile factorization
|
|
|
|
The compiler distribution build system (the set of Makefiles used to
|
|
build the compiler distribution) traditionally had separate Makefiles
|
|
for Unix and Windows, which lead to some amount of duplication and
|
|
subtle differences and technical debt in general -- for people working
|
|
on the compiler distribution, but also cross-compilation or porting to
|
|
new systems. During the 4.05 development period, Sébastien Hinderer
|
|
worked on harmonizing the build rules and merging the two build
|
|
systems.
|
|
|
|
* Some changes were made to the config/Makefile file which
|
|
is exported as $(ocamlc -where)/Makefile.config, and on
|
|
which some advanced users might rely. The changes are
|
|
as follows:
|
|
- a BYTERUN variable was added that points to the installed ocamlrun
|
|
- the PARTIALLD variable was removed (PACKLD is more complete)
|
|
- the always-empty DLLCCCOMPOPTS was removed
|
|
- the SHARED variable was removed; its value is "shared" or "noshared",
|
|
which duplicates the existing and more convenient
|
|
SUPPORTS_SHARED_LIBRARIES variable whose value is "true" or "false".
|
|
|
|
Note that Makefile.config may change further in the future and relying
|
|
on it is a bit fragile. We plan to make `ocamlc -config` easier to use
|
|
for scripting purposes, and have a stable interface there. If you rely
|
|
on Makefile.config, you may want to get in touch with Sébastien Hinderer
|
|
or participate to #7116 (Allow easy retrieval of Makefile.config's values)
|
|
or #7172 (More information in ocamlc -config).
|
|
|
|
The complete list of changes is listed below.
|
|
|
|
- #705: update Makefile.nt so that ocamlnat compiles
|
|
for non-Cygwin Windows ports.
|
|
(Sébastien Hinderer, review by Alain Frisch)
|
|
|
|
- #729: Make sure ocamlnat is built with a $(EXE) extension, merge
|
|
rules between Unix and Windows Makefiles
|
|
(Sébastien Hinderer, review by Alain Frisch)
|
|
|
|
- #762: Merge build systems in the yacc/ directory.
|
|
(Sébastien Hinderer, review by David Allsopp, Alain Frisch)
|
|
|
|
- #764: Merge build systems in the debugger/ directory.
|
|
(Sébastien Hinderer, review by Alain Frisch)
|
|
|
|
- #785: Merge build systems in otherlibs/systhreads/
|
|
(Sébastien Hinderer, review by Alain Frisch, David Allsopp,
|
|
testing and regression fix by Jérémie Dimino)
|
|
|
|
- #788: Merge build systems in subdirectories of otherlibs/.
|
|
(Sébastien Hinderer, review by Alain Frisch)
|
|
|
|
- #808, #906: Merge Unix and Windows build systems
|
|
in the ocamldoc/ directory
|
|
(Sébastien Hinderer, review by Alain Frisch)
|
|
|
|
- #812: Merge build systems in the tools/ subdirectory
|
|
(Sébastien Hinderer, review by Alain Frisch)
|
|
|
|
- #866: Merge build systems in the stdlib/ directory
|
|
(Sébastien Hinderer, review by David Allsopp and Adrien Nader)
|
|
|
|
- #941: Merge Unix and Windows build systems in the asmrun/ directory
|
|
(Sébastien Hinderer, review by Mark Shinwell, Adrien Nader,
|
|
Xavier Leroy, David Allsopp, Damien Doligez)
|
|
|
|
- #981: Merge build systems in the byterun/ directory
|
|
(Sébastien Hinderer, review by Adrien Nader)
|
|
|
|
- #1033, #1048: Merge build systems in the root directory
|
|
(Sébastien Hinderer, review by Adrien Nader and Damien Doligez,
|
|
testing and regression fix by Andreas Hauptmann)
|
|
|
|
### Internal/compiler-libs changes:
|
|
|
|
- #673: distinguish initialization of block fields from mutation in lambda.
|
|
(Frédéric Bour, review by Xavier Leroy, Stephen Dolan and Mark Shinwell)
|
|
|
|
- #744, #781: fix duplicate self-reference in imported cmi_crcs
|
|
list in .cmti files + avoid rebuilding cmi_info record when creating
|
|
.cmti files
|
|
(Alain Frisch, report by Daniel Bünzli, review by Jérémie Dimino)
|
|
|
|
- #881: change `Outcometree.out_variant` to be more general.
|
|
`Ovar_name of out_ident * out_type list` becomes `Ovar_type of out_type`.
|
|
(Valentin Gatien-Baron, review by Leo White)
|
|
|
|
- #908: refactor PIC-handling in the s390x backend
|
|
(Gabriel Scherer, review by Xavier Leroy and Mark Shinwell)
|
|
|
|
### Bug fixes:
|
|
|
|
- #5115: protect all byterun/fail.c functions against
|
|
uninitialized caml_global_data (only changes the bytecode behavior)
|
|
(Gabriel Scherer, review by Xavier Leroy)
|
|
|
|
- #6136, #967: Fix Closure so that overapplication evaluation order
|
|
matches the bytecode compiler and Flambda.
|
|
(Mark Shinwell, report by Jeremy Yallop, review by Frédéric Bour)
|
|
|
|
- #6550, #1094: Allow creation of empty .cmxa files on macOS
|
|
(Mark Shinwell)
|
|
|
|
- #6594, #955: Remove "Istore_symbol" specific operation on x86-64.
|
|
This is more robust and in particular avoids assembly failures on Win64.
|
|
(Mark Shinwell, review by Xavier Leroy, testing by David Allsopp and
|
|
Olivier Andrieu)
|
|
|
|
- #6903: Unix.execvpe doesn't change environment on Cygwin
|
|
(Xavier Leroy, report by Adrien Nader)
|
|
|
|
- #6987: Strange error message probably caused by
|
|
universal variable escape (with polymorphic variants)
|
|
(Jacques Garrigue, report by Mikhail Mandrykin and Leo White)
|
|
|
|
- #7216, #949: don't require double parens in Functor((val x))
|
|
(Jacques Garrigue, review by Valentin Gatien-Baron)
|
|
|
|
- #7331: ocamldoc, avoid infinite loop in presence of self alias,
|
|
i.e. module rec M:sig end = M
|
|
(Florian Angeletti, review Gabriel Scherer)
|
|
|
|
- #7346, #966: Fix evaluation order problem whereby expressions could
|
|
be incorrectly re-ordered when compiling with Flambda. This also fixes one
|
|
example of evaluation order in the native code compiler not matching the
|
|
bytecode compiler (even when not using Flambda)
|
|
(Mark Shinwell, Leo White, code review by Pierre Chambart)
|
|
|
|
- #7348: Private row variables can escape their scope
|
|
(Jacques Garrigue, report by Leo White)
|
|
|
|
- #7407: Two not-quite-standard C idioms rejected by SUNWSPro compilers
|
|
(Xavier Leroy)
|
|
|
|
- #7421: Soundness bug with GADTs and lazy
|
|
(Jacques Garrigue, report by Leo White)
|
|
|
|
- #7424: Typechecker diverges on unboxed type declaration
|
|
(Jacques Garrigue, report by Stephen Dolan)
|
|
|
|
- #7426, #965: Fix fatal error during object compilation (also
|
|
introduces new [Pfield_computed] and [Psetfield_computed] primitives)
|
|
(Mark Shinwell, report by Ulrich Singer)
|
|
|
|
- #7427, #959: Don't delete let bodies in Cmmgen
|
|
(Mark Shinwell, report by Valentin Gatien-Baron)
|
|
|
|
- #7432: Linking modules compiled with -labels and -nolabels is not safe
|
|
(Jacques Garrigue, report by Jeremy Yallop)
|
|
|
|
- #7437: typing assert failure with nonrec priv
|
|
(Jacques Garrigue, report by Anil Madhavapeddy)
|
|
|
|
- #7438: warning +34 exposes #row with private types
|
|
(Alain Frisch, report by Anil Madhavapeddy)
|
|
|
|
- #7443, #990: spurious unused open warning with local open in patterns
|
|
(Florian Angeletti, report by Gabriel Scherer)
|
|
|
|
- #7456, #1092: fix slow compilation on source files containing a lot
|
|
of similar debugging information location entries
|
|
(Mark Shinwell)
|
|
|
|
- #7504: fix warning 8 with unconstrained records
|
|
(Florian Angeletti, report by John Whitington)
|
|
|
|
- #7511, #1133: Unboxed type with unboxed argument should not be accepted
|
|
(Damien Doligez, review by Jeremy Yallop and Leo White)
|
|
|
|
- #805, #815, #833: check for integer overflow in String.concat
|
|
(Jeremy Yallop,
|
|
review by Damien Doligez, Alain Frisch, Daniel Bünzli, Fabrice Le Fessant)
|
|
|
|
- #881: short-paths did not apply to some polymorphic variants
|
|
(Valentin Gatien-Baron, review by Leo White)
|
|
|
|
- #886: Fix Ctype.moregeneral's handling of row_name
|
|
(Leo White, review by Jacques Garrigue)
|
|
|
|
- #934: check for integer overflow in Bytes.extend
|
|
(Jeremy Yallop, review by Gabriel Scherer)
|
|
|
|
- #956: Keep possibly-effectful expressions when optimizing multiplication
|
|
by zero.
|
|
(Jeremy Yallop, review by Nicolás Ojeda Bär, Xavier Leroy and Mark Shinwell)
|
|
|
|
- #977: Catch Out_of_range in ocamldebug's "list" command
|
|
(Yunxing Dai)
|
|
|
|
- #983: Avoid removing effectful expressions in Closure, and
|
|
eliminate more non-effectful ones
|
|
(Alain Frisch, review by Mark Shinwell and Gabriel Scherer)
|
|
|
|
- #987: alloc_sockaddr: don't assume a null terminator. It is not inserted
|
|
on macOS by system calls that fill in a struct sockaddr (e.g. getsockname).
|
|
(Anton Bachin)
|
|
|
|
- #998: Do not delete unused closures in un_anf.ml.
|
|
(Leo White, review by Mark Shinwell and Pierre Chambart)
|
|
|
|
- #1019: Fix fatal error in Flambda mode "[functions] does not map set of
|
|
closures ID"
|
|
(Pierre Chambart, code review by Mark Shinwell and Leo White)
|
|
|
|
- #1075: Ensure that zero-sized float arrays have zero tags.
|
|
(Mark Shinwell, Leo White, review by Xavier Leroy)
|
|
|
|
* #1088: Gc.minor_words now returns accurate numbers.
|
|
(compatibility: the .mli declaration of `Gc.minor_words`
|
|
and `Gc.get_minor_free` changed, which may break libraries
|
|
re-exporting these values.)
|
|
(Stephen Dolan, review by Pierre Chambart and Xavier Leroy)
|
|
|
|
OCaml 4.04.2 (23 Jun 2017):
|
|
---------------------------
|
|
|
|
### Security fix:
|
|
|
|
- #7557: Local privilege escalation issue with ocaml binaries.
|
|
(Damien Doligez, report by Eric Milliken, review by Xavier Leroy)
|
|
|
|
OCaml 4.04.1 (14 Apr 2017):
|
|
---------------------------
|
|
|
|
### Standard library:
|
|
|
|
- #7403, #894: fix a bug in Set.map as introduced in 4.04.0
|
|
(Gabriel Scherer, report by Thomas Leonard)
|
|
|
|
### Tools:
|
|
|
|
- #7411: ocamldoc, avoid nested <pre> tags in module description.
|
|
(Florian Angeletti, report by user 'kosik')
|
|
|
|
- #7488: ocamldoc, wrong Latex output for variant types
|
|
with constructors without arguments.
|
|
(Florian Angeletti, report by Xavier Leroy)
|
|
|
|
### Build system:
|
|
|
|
- #7373, #1023: New flexlink target in Makefile.nt to bootstrap the
|
|
flexlink binary only, rather than the flexlink binary and the FlexDLL C
|
|
objects.
|
|
(David Allsopp)
|
|
|
|
### Bug fixes:
|
|
|
|
- #7369: Str.regexp raises "Invalid_argument: index out of bounds"
|
|
(Damien Doligez, report by John Whitington)
|
|
|
|
- #7373, #1023: Fix ocamlmklib with bootstrapped FlexDLL. Bootstrapped
|
|
FlexDLL objects are now installed to a subdirectory flexdll of the Standard
|
|
Library which allows the compilers to pick them up explicitly and also
|
|
ocamlmklib to include them without unnecessarily adding the entire Standard
|
|
Library.
|
|
(David Allsopp)
|
|
|
|
- #7385, #1057: fix incorrect timestamps returned by Unix.stat on Windows
|
|
when either TZ is set or system date is in DST.
|
|
(David Allsopp, report and initial fix by Nicolás Ojeda Bär, review and
|
|
superior implementation suggestion by Xavier Leroy)
|
|
|
|
- #7405, #903: s390x: Fix address of caml_raise_exn in native dynlink
|
|
modules.
|
|
(Richard Jones, review by Xavier Leroy)
|
|
|
|
- #7417, #930: ensure 16 byte stack alignment inside caml_allocN on x86-64
|
|
for ocaml build with WITH_FRAME_POINTERS defined
|
|
(Christoph Cullmann)
|
|
|
|
- #7456, #1092: fix slow compilation on source files containing a lot
|
|
of similar debugging information location entries
|
|
(Mark Shinwell)
|
|
|
|
- #7457: a case of double free in the systhreads library (POSIX
|
|
implementation).
|
|
(Xavier Leroy, report by Chet Murthy)
|
|
|
|
- #7460, #1011: catch uncaught exception when unknown files are passed
|
|
as argument (regression in 4.04.0)
|
|
(Bernhard Schommer, review by Florian Angeletti and Gabriel Scherer,
|
|
report by Stephen Dolan)
|
|
|
|
- #7505: Memory cannot be released after calling
|
|
Bigarray.Genarray.change_layout.
|
|
(Damien Doligez and Xavier Leroy, report by Liang Wang)
|
|
|
|
- #912: Fix segfault in Unix.create_process on Windows caused by wrong header
|
|
configuration.
|
|
(David Allsopp)
|
|
|
|
- #980: add dynlink options to ocamlbytecomp.cmxa to allow ocamlopt.opt
|
|
to load plugins. See http://github.com/OCamlPro/ocamlc-plugins for examples.
|
|
(Fabrice Le Fessant, review by David Allsopp)
|
|
|
|
- #992: caml-types.el: Fix missing format argument, so that it can show kind
|
|
of call at point correctly.
|
|
(Chunhui He)
|
|
|
|
- #1043: Allow Windows CRLF line-endings in ocamlyacc on Unix and Cygwin.
|
|
(David Allsopp, review by Damien Doligez and Xavier Leroy)
|
|
|
|
- #1072: Fix segfault in Sys.runtime_parameters when exception backtraces
|
|
are enabled.
|
|
(Olivier Andrieu)
|
|
|
|
OCaml 4.04.0 (4 Nov 2016):
|
|
--------------------------
|
|
|
|
(Changes that can break existing programs are marked with a "*")
|
|
|
|
### Language features:
|
|
|
|
- #7233: Support GADT equations on non-local abstract types
|
|
(Jacques Garrigue)
|
|
|
|
- #187, #578: Local opening of modules in a pattern.
|
|
Syntax: "M.(p)", "M.[p]","M.[| p |]", "M.{p}"
|
|
(Florian Angeletti, Jacques Garrigue, review by Alain Frisch)
|
|
|
|
- #301: local exception declarations "let exception ... in"
|
|
(Alain Frisch)
|
|
|
|
- #508: Allow shortcut for extension on semicolons: ;%foo
|
|
(Jérémie Dimino)
|
|
|
|
- #606: optimized representation for immutable records with a single
|
|
field, and concrete types with a single constructor with a single argument.
|
|
This is triggered with a [@@unboxed] attribute on the type definition.
|
|
Currently mutually recursive datatypes are not well supported, this
|
|
limitation should be lifted in the future (see #7364).
|
|
(Damien Doligez)
|
|
|
|
### Compiler user-interface and warnings:
|
|
|
|
* #6475, #464: interpret all command-line options before compiling any
|
|
files, changes (improves) the semantics of repeated -o options or -o
|
|
combined with -c see the super-detailed commit message at
|
|
https://github.com/ocaml/ocaml/commit/da56cf6dfdc13c09905c2e07f1d4849c8346eec8
|
|
(whitequark)
|
|
|
|
- #7139: clarify the wording of Warning 38
|
|
(Unused exception or extension constructor)
|
|
(Gabriel Scherer)
|
|
|
|
* #7147, #475: add colors when reporting errors generated by ppx rewriters.
|
|
Remove the `Location.errorf_prefixed` function which is no longer relevant
|
|
(Simon Cruanes, Jérémie Dimino)
|
|
|
|
- #7169, #501: clarify the wording of Warning 8
|
|
(Non-exhaustivity warning for pattern matching)
|
|
(Florian Angeletti, review and report by Gabriel Scherer)
|
|
|
|
* #591: Improve support for OCAMLPARAM: (i) do not use objects
|
|
files with -a, -pack, -shared; (ii) use "before" objects in the toplevel
|
|
(but not "after" objects); (iii) use -I dirs in the toplevel,
|
|
(iv) fix bug where -I dirs were ignored when using threads
|
|
(Marc Lasson, review by Damien Doligez and Alain Frisch)
|
|
|
|
- #648: New -plugin option for ocamlc and ocamlopt, to dynamically extend
|
|
the compilers at runtime.
|
|
(Fabrice Le Fessant)
|
|
|
|
- #684: Detect unused module declarations
|
|
(Alain Frisch)
|
|
|
|
- #706: Add a settable Env.Persistent_signature.load function so
|
|
that cmi files can be loaded from other sources. This can be used to
|
|
create self-contained toplevels.
|
|
(Jérémie Dimino)
|
|
|
|
### Standard library:
|
|
|
|
- #6279, #553: implement Set.map
|
|
(Gabriel Scherer)
|
|
|
|
- #6820, #560: Add Obj.reachable_words to compute the
|
|
"transitive" heap size of a value
|
|
(Alain Frisch, review by Mark Shinwell and Damien Doligez)
|
|
|
|
- #473: Provide `Sys.backend_type` so that user can write backend-specific
|
|
code in some cases (for example, code generator).
|
|
(Hongbo Zhang)
|
|
|
|
- #589: Add a non-allocating function to recover the number of
|
|
allocated minor words.
|
|
(Pierre Chambart, review by Damien Doligez and Gabriel Scherer)
|
|
|
|
- #626: String.split_on_char
|
|
(Alain Frisch)
|
|
|
|
- #669: Filename.extension and Filename.remove_extension
|
|
(Alain Frisch, request by Edgar Aroutiounian, review by Daniel Bünzli
|
|
and Damien Doligez)
|
|
|
|
- #674: support unknown Sys.os_type in Filename, defaulting to Unix
|
|
(Filename would previously fail at initialization time for
|
|
Sys.os_type values other than "Unix", "Win32" and "Cygwin";
|
|
mirage-os uses "xen")
|
|
(Anil Madhavapeddy)
|
|
|
|
- #772 %string_safe_set and %string_unsafe_set are deprecated aliases
|
|
for %bytes_safe_set and %bytes_unsafe_set.
|
|
(Hongbo Zhang and Damien Doligez)
|
|
|
|
### Other libraries
|
|
|
|
- #4834, #592: Add a Biggarray.Genarray.change_layout function
|
|
to switch bigarrays between C and fortran layouts.
|
|
(Guillaume Hennequin, review by Florian Angeletti)
|
|
|
|
### Code generation and optimizations:
|
|
|
|
- #4747, #328: Optimize Hashtbl by using in-place updates of its
|
|
internal bucket lists. All operations run in constant stack size
|
|
and are usually faster, except Hashtbl.copy which can be much
|
|
slower
|
|
(Alain Frisch)
|
|
|
|
- #6217, #538: Optimize performance of record update:
|
|
no more performance cliff when { foo with t1 = ..; t2 = ...; ... }
|
|
hits 6 updated fields
|
|
(Olivier Nicole, review by Thomas Braibant and Pierre Chambart)
|
|
|
|
- #7023, #336: Better unboxing strategy
|
|
(Alain Frisch, Pierre Chambart)
|
|
|
|
- #7244, #840: Ocamlopt + flambda requires a lot of memory
|
|
to compile large array literal expressions
|
|
(Pierre Chambart, review by Mark Shinwell)
|
|
|
|
- #7291, #780: Handle specialisation of recursive function that does
|
|
not always preserve the arguments
|
|
(Pierre Chambart, Mark Shinwell, report by Simon Cruanes)
|
|
|
|
- #7328, #702: Do not eliminate boxed int divisions by zero and
|
|
avoid checking twice if divisor is zero with flambda.
|
|
(Pierre Chambart, report by Jeremy Yallop)
|
|
|
|
- #427: Obj.is_block is now an inlined OCaml function instead of a
|
|
C external. This should be faster.
|
|
(Demi Obenour)
|
|
|
|
- #580: Optimize immutable float records
|
|
(Pierre Chambart, review by Mark Shinwell)
|
|
|
|
- #602: Do not generate dummy code to force module linking
|
|
(Pierre Chambart, reviewed by Jacques Garrigue)
|
|
|
|
- #703: Optimize some constant string operations when the "-safe-string"
|
|
configure time option is enabled.
|
|
(Pierre Chambart)
|
|
|
|
- #707: Load cross module information during a meet
|
|
(Pierre Chambart, report by Leo White, review by Mark Shinwell)
|
|
|
|
- #709: Share a few more equal switch branches
|
|
(Pierre Chambart, review by Gabriel Scherer)
|
|
|
|
- #712: Small improvements to type-based optimizations for array
|
|
and lazy
|
|
(Alain Frisch, review by Pierre Chambart)
|
|
|
|
- #714: Prevent warning 59 from triggering on Lazy of constants
|
|
(Pierre Chambart, review by Leo White)
|
|
|
|
- #723 Sort emitted functions according to source location
|
|
(Pierre Chambart, review by Mark Shinwell)
|
|
|
|
- Lack of type normalization lead to missing simple compilation for "lazy x"
|
|
(Alain Frisch)
|
|
|
|
### Runtime system:
|
|
|
|
- #7203, #534: Add a new primitive caml_alloc_float_array to allocate an
|
|
array of floats
|
|
(Thomas Braibant)
|
|
|
|
- #7210, #562: Allows to register finalisation function that are
|
|
called only when a value will never be reachable anymore. The
|
|
drawbacks compared to the existing one is that the finalisation
|
|
function is not called with the value as argument. These finalisers
|
|
are registered with `GC.finalise_last`
|
|
(François Bobot reviewed by Damien Doligez and Leo White)
|
|
|
|
- #247: In previous OCaml versions, inlining caused stack frames to
|
|
disappear from stacktraces. This made debugging harder in presence of
|
|
optimizations, and flambda was going to make this worse. The debugging
|
|
information produced by the compiler now enables the reconstruction of the
|
|
original backtrace. Use `Printexc.get_raw_backtrace_next_slot` to traverse
|
|
the list of inlined stack frames.
|
|
(Frédéric Bour, review by Mark Shinwell and Xavier Leroy)
|
|
|
|
- #590: Do not perform compaction if the real overhead is less than expected
|
|
(Thomas Braibant)
|
|
|
|
### Tools:
|
|
|
|
- #7189: toplevel #show, follow chains of module aliases
|
|
(Gabriel Scherer, report by Daniel Bünzli, review by Thomas Refis)
|
|
|
|
- #7248: have ocamldep interpret -open arguments in left-to-right order
|
|
(Gabriel Scherer, report by Anton Bachin)
|
|
|
|
- #7272, #798: ocamldoc, missing line breaks in type_*.html files
|
|
(Florian Angeletti)
|
|
|
|
- #7290: ocamldoc, improved support for inline records
|
|
(Florian Angeletti)
|
|
|
|
- #7323, #750: ensure "ocamllex -ml" works with -safe-string
|
|
(Hongbo Zhang)
|
|
|
|
- #7350, #806: ocamldoc, add viewport metadata to generated html pages
|
|
(Florian Angeletti, request by Daniel Bünzli)
|
|
|
|
- #452: Make the output of ocamldep more stable
|
|
(Alain Frisch)
|
|
|
|
- #548: empty documentation comments
|
|
(Florian Angeletti)
|
|
|
|
- #575: Add the -no-version option to the toplevel
|
|
(Sébastien Hinderer)
|
|
|
|
- #598: Add a --strict option to ocamlyacc treat conflicts as errors
|
|
(this option is now used for the compiler's parser)
|
|
(Jeremy Yallop)
|
|
|
|
- #613: make ocamldoc use -open arguments
|
|
(Florian Angeletti)
|
|
|
|
- #718: ocamldoc, fix order of extensible variant constructors
|
|
(Florian Angeletti)
|
|
|
|
### Debugging and profiling:
|
|
|
|
- #585: Spacetime, a new memory profiler (Mark Shinwell, Leo White)
|
|
|
|
### Manual and documentation:
|
|
|
|
- #7007, #7311: document the existence of OCAMLPARAM and
|
|
ocaml_compiler_internal_params
|
|
(Damien Doligez, reports by Wim Lewis and Gabriel Scherer)
|
|
|
|
- #7243: warn users against using WinZip to unpack the source archive
|
|
(Damien Doligez, report by Shayne Fletcher)
|
|
|
|
- #7245, #565: clarification to the wording and documentation
|
|
of Warning 52 (fragile constant pattern)
|
|
(Gabriel Scherer, William, Adrien Nader, Jacques Garrigue)
|
|
|
|
- #PR7265, #769: Restore 4.02.3 behaviour of Unix.fstat, if the
|
|
file descriptor doesn't wrap a regular file (win32unix only)
|
|
(Andreas Hauptmann, review by David Allsopp)
|
|
|
|
- #7288: flatten : Avoid confusion
|
|
(Damien Doligez, report by user 'tormen')
|
|
|
|
- #7355: Gc.finalise and lazy values
|
|
(Jeremy Yallop)
|
|
|
|
- #842: Document that [Store_field] must not be used to populate
|
|
arrays of values declared using [CAMLlocalN] (Mark Shinwell)
|
|
|
|
### Compiler distribution build system:
|
|
|
|
- #324: Compiler developers: Adding new C primitives to the
|
|
standard runtime doesn't require anymore to run `make bootstrap`
|
|
(François Bobot)
|
|
|
|
- #384: Fix compilation using old Microsoft C Compilers not
|
|
supporting secure CRT functions (SDK Visual Studio 2005 compiler and
|
|
earlier) and standard 64-bit integer literals (Visual Studio .NET
|
|
2002 and earlier)
|
|
(David Allsopp)
|
|
|
|
- #507: More sharing between Unix and Windows makefiles
|
|
(whitequark, review by Alain Frisch)
|
|
|
|
* #512, #587: Installed `ocamlc`, `ocamlopt`, and `ocamllex` are
|
|
now the native-code versions of the tools, if those versions were
|
|
built.
|
|
(Demi Obenour)
|
|
|
|
- #525: fix build on OpenIndiana
|
|
(Sergey Avseyev, review by Damien Doligez)
|
|
|
|
- #687: "./configure -safe-string" to get a system where
|
|
"-unsafe-string" is not allowed, thus giving stronger non-local
|
|
guarantees about immutability of strings
|
|
(Alain Frisch, review by Hezekiah M. Carty)
|
|
|
|
### Bug fixes:
|
|
|
|
* #6505: Missed Type-error leads to a segfault upon record access.
|
|
(Jacques Garrigue, extra report by Stephen Dolan)
|
|
Proper fix required a more restrictive approach to recursive types:
|
|
mutually recursive types are seen as abstract types (i.e. non-contractive)
|
|
when checking the well-foundedness of the recursion.
|
|
|
|
* #6752: Nominal types and scope escaping.
|
|
Revert to strict scope for non-generalizable type variables, cf. Mantis.
|
|
Note that this is actually stricter than the behavior before 4.03,
|
|
cf. #7313, meaning that you may sometimes need to add type annotations
|
|
to explicitly instantiate non-generalizable type variables.
|
|
(Jacques Garrigue, following discussion with Jeremy Yallop,
|
|
Nicolás Ojeda Bär and Alain Frisch)
|
|
|
|
- #7112: Aliased arguments ignored for equality of module types
|
|
(Jacques Garrigue, report by Leo White)
|
|
|
|
- #7134: compiler forcing aliases it shouldn't while reporting type errors
|
|
(Jacques Garrigue, report and suggestion by sliquister)
|
|
|
|
- #7153: document that Unix.SOCK_SEQPACKET is not really usable.
|
|
|
|
- #7165, #494: uncaught exception on invalid lexer directive
|
|
(Gabriel Scherer, report by KC Sivaramakrishnan using afl-fuzz)
|
|
|
|
- #7257, #583: revert a 4.03 change of behavior on (Unix.sleep 0.),
|
|
it now calls (nano)sleep for 0 seconds as in (< 4.03) versions.
|
|
(Hannes Mehnert, review by Damien Doligez)
|
|
|
|
- #7259 and #603: flambda does not collapse pattern matching
|
|
in some cases
|
|
(Pierre Chambart, report by Reed Wilson, review by Mark Shinwell)
|
|
|
|
- #7260: GADT + subtyping compile time crash
|
|
(Jacques Garrigue, report by Nicolás Ojeda Bär)
|
|
|
|
- #7269: Segfault from conjunctive constraints in GADT
|
|
(Jacques Garrigue, report by Stephen Dolan)
|
|
|
|
- #7276: Support more than FD_SETSIZE sockets in Windows' emulation
|
|
of select
|
|
(David Scott, review by Alain Frisch)
|
|
|
|
* #7278: Prevent private inline records from being mutated
|
|
(Alain Frisch, report by Pierre Chambart)
|
|
|
|
- #7284: Bug in mcomp_fields leads to segfault
|
|
(Jacques Garrigue, report by Leo White)
|
|
|
|
- #7285: Relaxed value restriction broken with principal
|
|
(Jacques Garrigue, report by Leo White)
|
|
|
|
- #7297: -strict-sequence turns off Warning 21
|
|
(Jacques Garrigue, report by Valentin Gatien-Baron)
|
|
|
|
- #7299: remove access to OCaml heap inside blocking section in win32unix
|
|
(David Allsopp, report by Andreas Hauptmann)
|
|
|
|
- #7300: remove access to OCaml heap inside blocking in Unix.sleep on Windows
|
|
(David Allsopp)
|
|
|
|
- #7305: -principal causes loop in type checker when compiling
|
|
(Jacques Garrigue, report by Anil Madhavapeddy, analysis by Leo White)
|
|
|
|
- #7330: Missing exhaustivity check for extensible variant
|
|
(Jacques Garrigue, report by Elarnon *)
|
|
|
|
- #7374: Contractiveness check unsound with constraints
|
|
(Jacques Garrigue, report by Leo White)
|
|
|
|
- #7378: GADT constructors can be re-exposed with an incompatible type
|
|
(Jacques Garrigue, report by Alain Frisch)
|
|
|
|
- #7389: Unsoundness in GADT exhaustiveness with existential variables
|
|
(Jacques Garrigue, report by Stephen Dolan)
|
|
|
|
* #533: Thread library: fixed [Thread.wait_signal] so that it
|
|
converts back the signal number returned by [sigwait] to an
|
|
OS-independent number
|
|
(Jérémie Dimino)
|
|
|
|
- #600: (similar to #555) ensure that register typing constraints are
|
|
respected at N-way join points in the control flow graph
|
|
(Mark Shinwell)
|
|
|
|
- #672: Fix float_of_hex parser to correctly reject some invalid forms
|
|
(Bogdan Tătăroiu, review by Thomas Braibant and Alain Frisch)
|
|
|
|
- #700: Fix maximum weak bucket size
|
|
(Nicolás Ojeda Bär, review by François Bobot)
|
|
|
|
- #708 Allow more module aliases in strengthening (Leo White)
|
|
|
|
- #713, #7301: Fix wrong code generation involving lazy values in Flambda
|
|
mode
|
|
(Mark Shinwell, review by Pierre Chambart and Alain Frisch)
|
|
|
|
- #721: Fix infinite loop in flambda due to [@@specialise] annotations
|
|
|
|
- #779: Building native runtime on Windows could fail when bootstrapping
|
|
FlexDLL if there was also a system-installed flexlink
|
|
(David Allsopp, report Michael Soegtrop)
|
|
|
|
- #805, #815, #833: check for integer overflow in String.concat
|
|
(Jeremy Yallop,
|
|
review by Damien Doligez, Alain Frisch, Daniel Bünzli, Fabrice Le Fessant)
|
|
|
|
- #810: check for integer overflow in Array.concat
|
|
(Jeremy Yallop)
|
|
|
|
- #814: fix the Buffer.add_substring bounds check to handle overflow
|
|
(Jeremy Yallop)
|
|
|
|
- #880: Fix [@@inline] with default parameters in flambda (Leo White)
|
|
|
|
* #1353: add labels to BytesLabels.sub_string (Jacques Garrigue)
|
|
|
|
### Internal/compiler-libs changes:
|
|
|
|
- #7200, #539: Improve, fix, and add test for parsing/pprintast.ml
|
|
(Runhang Li, David Sheets, Alain Frisch)
|
|
|
|
- #351: make driver/pparse.ml functions type-safe
|
|
(Gabriel Scherer, Dmitrii Kosarev, review by Jérémie Dimino)
|
|
|
|
- #516: Improve Texp_record constructor representation, and
|
|
propagate updated record type information
|
|
(Pierre Chambart, review by Alain Frisch)
|
|
|
|
- #678: Graphics.close_graph crashes 64-bit Windows ports (re-implementation
|
|
of #3963)
|
|
(David Allsopp)
|
|
|
|
- #679: delay registration of docstring after the mapper is applied
|
|
(Hugo Heuzard, review by Leo White)
|
|
|
|
- #872: don't attach (**/**) comments to any particular node
|
|
(Thomas Refis, review by Leo White)
|
|
|
|
OCaml 4.03.0 (25 Apr 2016):
|
|
---------------------------
|
|
|
|
(Changes that can break existing programs are marked with a "*")
|
|
|
|
### Language features:
|
|
|
|
- #5528: inline records for constructor arguments
|
|
(Alain Frisch)
|
|
|
|
- #6220, #6403, #6437, #6801:
|
|
Improved redundancy and exhaustiveness checks for GADTs.
|
|
Namely, the redundancy checker now checks whether the uncovered pattern
|
|
of the pattern is actually inhabited, exploding at most one wild card.
|
|
This is also done for exhaustiveness when there is only one case.
|
|
Additionally, one can now write unreachable cases, of the form
|
|
"pat -> .", which are treated by the redundancy check.
|
|
(Jacques Garrigue)
|
|
|
|
- #6374: allow "_ t" as a short-hand for "(_, _, ..) t" for n-ary type
|
|
constructors
|
|
(Alain Frisch)
|
|
|
|
- #6714: allow [@@ocaml.warning] on most structure and signature items:
|
|
values, modules, module types
|
|
(whitequark)
|
|
|
|
- #6806: Syntax shortcut for putting a type annotation on a record field:
|
|
{ f1 : typ = e } is sugar for { f1 = (e : typ) }
|
|
{ f1 : typ } is sugar for { f1 = (f1 : typ) }
|
|
(Valentin Gatien-Baron, review by Jérémie Dimino)
|
|
|
|
- #6806: Allow type annotations before the "->" in "fun <args> -> <expr>"
|
|
fun x y : (int * int) -> (x, y)
|
|
(Valentin Gatien-Baron, review by Jérémie Dimino)
|
|
|
|
- #26: support for "(type a b)" as syntactic sugar for "(type a) (type b)"
|
|
(Gabriel Scherer)
|
|
|
|
- #42: short functor type syntax: "S -> T" for "functor (_ : S) -> T"
|
|
(Leo White)
|
|
|
|
- #88: allow field punning in object copying expressions:
|
|
{< x; y; >} is sugar for {< x = x; y = y; >}
|
|
(Jeremy Yallop)
|
|
|
|
- #112: octal escape sequences for char and string literals
|
|
"Make it \o033[1mBOLD\o033[0m"
|
|
(Rafaël Bocquet, request by John Whitington)
|
|
|
|
- #167: allow to annotate externals' arguments and result types so
|
|
they can be unboxed or untagged: [@unboxed], [@untagged]. Supports
|
|
untagging int and unboxing int32, int64, nativeint and float.
|
|
(Jérémie Dimino, Mark Shinwell)
|
|
|
|
- #173: [@inline] and [@inlined] attributes (for function declarations
|
|
and call sites respectively) to control inlining
|
|
(Pierre Chambart, Mark Shinwell)
|
|
|
|
- #188: accept [@@immediate] attribute on type declarations to mark types
|
|
that are represented at runtime by an integer
|
|
(Will Crichton, reviewed by Leo White)
|
|
|
|
* #234: allow "[]" as a user-defined constructor. Demand parenthesis
|
|
around "::" when using "::" as user-defined constructor:
|
|
code using "| :: of ..." must change to "| (::) of ...".
|
|
(Runhang Li, review by Damien Doligez)
|
|
|
|
- #240: replace special annotations on externals by attributes:
|
|
* "float" is generalized to [@@unboxed]
|
|
* "noalloc" becomes [@@noalloc]
|
|
Deprecate "float" and "noalloc".
|
|
(Jérémie Dimino)
|
|
|
|
- #254: @ocaml.warn_on_literal_pattern attribute on constructors to
|
|
warn when the argument is matches against a constant pattern. This
|
|
attribute is applied on predefined exception constructors which
|
|
carry purely informational (with no stability guarantee) messages.
|
|
(Alain Frisch)
|
|
|
|
- #268: hexadecimal notation for floating-point literals: -0x1.ffffp+987
|
|
In OCaml source code, FP literals can be written using the hexadecimal
|
|
notation 0x<mantissa in hex>p<exponent> from ISO C99.
|
|
(Xavier Leroy)
|
|
|
|
- #273: allow to get the extension slot of an extension constructor
|
|
by writing [%extension_constructor <path>]
|
|
(Jérémie Dimino)
|
|
|
|
- #282: change short-paths penalty heuristic to assign the same cost to
|
|
idents containing double underscores as to idents starting with an underscore
|
|
(Thomas Refis, Leo White)
|
|
|
|
- #6681 #326: signature items are now accepted as payloads for
|
|
extension and attributes, using the syntax [%foo: SIG ] or [@foo: SIG ].
|
|
Examples: "[%%client: val foo : int]" or "val%client foo : int".
|
|
(Alain Frisch and Gabriel Radanne)
|
|
|
|
* #342: Allow shortcuts for extension and attributes on all keywords:
|
|
module%foo, class[@foo], etc.
|
|
The attribute in "let[@foo] .. in .." is now attached to the value binding,
|
|
not to the expression.
|
|
(Gabriel Radanne)
|
|
|
|
### Compilers:
|
|
|
|
* #4231, #5461: warning 31 is now fatal by default
|
|
(Warning 31: A module is linked twice in the same executable.)
|
|
This is an interim solution; double-linking of modules has dangerous
|
|
semantics, eg. exception constructors end up with two distinct declarations.
|
|
(Alain Frisch)
|
|
|
|
- #4800: better compilation of tuple assignment
|
|
(Gabriel Scherer and Alain Frisch)
|
|
|
|
- #5995: keep -for-pack into account to name exceptions;
|
|
-for-pack should now be used during bytecode compilation as well
|
|
(Alain Frisch, report by Christophe Troestler)
|
|
|
|
- #6400: better error message for '_' used as an expression
|
|
(Alain Frisch, report by whitequark)
|
|
|
|
- #6501: harden the native-code generator against certain uses of "%identity"
|
|
(Xavier Leroy, report by Antoine Miné)
|
|
|
|
- #6636: add --version option
|
|
(whitequark)
|
|
|
|
- #6679: fix pprintast printing of constraints in type declarations
|
|
(Alain Frisch, report by Jun Furuse)
|
|
|
|
- #6737: fix Typedtree attributes on (fun x -> body) expressions
|
|
(Alain Frisch, report by Oleg Kiselyov)
|
|
|
|
* #6865: remove special case for parsing "let _ = expr" in structures
|
|
(Jérémie Dimino, Alain Frisch)
|
|
|
|
* #6438, #7059, #315: Pattern guard disables exhaustiveness check
|
|
(function Some x when x = 0 -> ()) will now raise warning 8 (non-exhaustive)
|
|
instead of warning 25 (all clauses are guarded). 25 isn't raised anymore.
|
|
Projects that set warning 8 as an error may fail to compile (presumably
|
|
this is the semantics they wanted).
|
|
(Alain Frisch, request by Martin Jambon and John Whitington)
|
|
|
|
- #6920: fix debug information around uses of %apply or %revapply
|
|
(Jérémie Dimino, report by Daniel Bünzli)
|
|
|
|
- #6939: Segfault with improper use of let-rec
|
|
(Alain Frisch)
|
|
|
|
- #6943: native-code generator for POWER/PowerPC 64 bits, both in
|
|
big-endian (ppc64) and little-endian (ppc64le) configuration.
|
|
(Xavier Leroy, with inspiration from RedHat's unofficial ppc64 and ppc64le
|
|
ports)
|
|
|
|
- #6979: better code generation in x86-32 backend for copying floats to
|
|
the stack
|
|
(Marc Lasson, review by Xavier Leroy)
|
|
|
|
- #7018: fix missing identifier renaming during inlining
|
|
(Alain Frisch, review by Xavier Leroy)
|
|
|
|
- #7022, #259: unbox float and boxed ints earlier, avoid second pass
|
|
(Alain Frisch)
|
|
|
|
- #7026, #288: remove write barrier for polymorphic variants without
|
|
arguments
|
|
(Simon Cruanes)
|
|
|
|
- #7031: new warning 57, ambiguous guarded or-patterns
|
|
(Luc Maranget, Gabriel Scherer, report by Martin Clochard and Claude Marché)
|
|
|
|
- #7064, #316: allowing to mark compilation units and sub-modules as
|
|
deprecated
|
|
(Alain Frisch)
|
|
|
|
- #7067: fix performance regression (wrt. 4.01) in the native compiler
|
|
for long nested structures
|
|
(Alain Frisch, report by Daniel Bünzli, review by Jacques Garrigue)
|
|
|
|
- #7097: fix strange syntax error message around illegal packaged module
|
|
signature constraints
|
|
(Alain Frisch, report by Jun Furuse)
|
|
|
|
- #7118, #7120, #408, #476: Bug fixed in stack unwinding
|
|
metadata generation. Was a cause of crashes in GUI programs on OS X.
|
|
(Bart Jacobs, review by Mark Shinwell)
|
|
|
|
- #7168: Exceeding stack limit in bytecode can lead to a crash.
|
|
(Jacques-Henri Jourdan)
|
|
|
|
- #7232: Strange Pprintast output with ppx_deriving
|
|
(Damien Doligez, report by Anton Bachin)
|
|
|
|
- #17: some cmm optimizations of integer operations with constants
|
|
(Stephen Dolan, review by Pierre Chambart)
|
|
|
|
- #89: improve type-specialization of unapplied primitives:
|
|
unapplied annotations (compare : int -> _),
|
|
type propagation (List.sort compare [1;2;3])
|
|
and propagation from module signatures now lead to specialization
|
|
(Frédéric Bour, review by Gabriel Scherer)
|
|
|
|
- #107: Prevent more unnecessary float boxing, especially in `if` and `match`
|
|
(Vladimir Brankov, review by Alain Frisch)
|
|
|
|
- #109: new (lazy) unboxing strategy for float and int references
|
|
(Vladimir Brankov, review by Alain Frisch)
|
|
|
|
- #115: More precise typing of values at the C-- and Mach level.
|
|
(Xavier Leroy, review by Pierre Chambart)
|
|
|
|
- #132: Flambda: new intermediate language and "middle-end" optimizers
|
|
(Pierre Chambart, Mark Shinwell, Leo White)
|
|
|
|
- #212, #7226, #542: emit column position in gas assembly `.loc`
|
|
(Frédéric Bour, Anton Bachin)
|
|
|
|
- #207: Colors in compiler messages (warnings, errors)
|
|
configure with -color {auto|always|never} or TERM=dumb
|
|
(Simon Cruanes, review by Gabriel Scherer)
|
|
|
|
- #258: more precise information on PowerPC instruction sizes
|
|
(Pierre Chambart, Xavier Leroy)
|
|
|
|
- #263: improve code generation for if-equivalents of (&&) and (||)
|
|
(Pierre Chambart)
|
|
|
|
- #270: Make [transl_exception_constructor] generate [Immutable] blocks
|
|
(Mark Shinwell)
|
|
|
|
- #271: Fix incorrect mutability flag when records are built using "with"
|
|
(Mark Shinwell)
|
|
|
|
- #275: native-code generator for IBM z System running Linux.
|
|
In memoriam Gene Amdahl, 1922-2015.
|
|
(Bill O'Farrell, Tristan Amini, Xavier Leroy)
|
|
|
|
- #282: relax short-paths safety check in presence of module aliases, take
|
|
penalty into account while building the printing map.
|
|
(Thomas Refis, Leo White)
|
|
|
|
- #306: Instrument the compiler to debug performance regressions
|
|
(Pierre Chambart)
|
|
|
|
- #319: add warning 58 for missing cmx files, and
|
|
extend -opaque option to mli files: a missing .cmx does not warn
|
|
if the corresponding .cmi is compiled -opaque.
|
|
(Leo White)
|
|
|
|
- #388: OCAML_FLEXLINK environment variable allows overriding flexlink
|
|
command (David Allsopp)
|
|
|
|
- #392: put all parsetree invariants in a new module Ast_invariants
|
|
(Jérémie Dimino)
|
|
|
|
- #407: don't display the name of compiled .c files when calling the
|
|
Microsoft C Compiler (same as the assembler).
|
|
(David Allsopp)
|
|
|
|
- #431: permit constant float arrays to be eligible for pattern match
|
|
branch merging
|
|
(Pierre Chambart)
|
|
|
|
- #455: provide more debugging information to Js_of_ocaml
|
|
(Jérôme Vouillon)
|
|
|
|
- #514, #554: Added several command-line flags to explicitly enable
|
|
settings that are currently the default:
|
|
`-alias-deps`, `-app-funct`, `-no-keep-docs`, `-no-keep-locs`,
|
|
`-no-principal`, `-no-rectypes`, `-no-strict-formats`
|
|
(Demi Obenour)
|
|
|
|
- #545: use reraise to preserve backtrace on
|
|
`match .. with exception e -> raise e`
|
|
(Nicolás Ojeda Bär, review by Gabriel Scherer)
|
|
|
|
### Runtime system:
|
|
|
|
* #596: make string/bytes distinguishable in the underlying
|
|
compiler implementation; caml_fill_string and caml_create_string are
|
|
deprecated and will be removed in the future, please use
|
|
caml_fill_bytes and caml_create_bytes for migration
|
|
(Hongbo Zhang, review by Damien Doligez, Alain Frisch, and Hugo Heuzard)
|
|
|
|
- #3612, #2429: allow allocating custom block with finalizers
|
|
in the minor heap.
|
|
(Pierre Chambart)
|
|
|
|
* #6517: use ISO C99 types {,u}int{32,64}_t in preference to our homegrown
|
|
types {,u}int{32,64}.
|
|
C stubs may have to be updated as {,u}int{32,64}_t are not defined anymore.
|
|
(Xavier Leroy)
|
|
|
|
- #6760: closures evaluated in the toplevel can now be marshalled
|
|
(whitequark, review by Jacques-Henri Jourdan)
|
|
|
|
- #6902, #210: emit a runtime warning on stderr
|
|
when finalizing an I/O channel which is still open:
|
|
"channel opened on file '...' dies without being closed"
|
|
this is controlled by OCAMLRUNPARAM=W=1 or with Sys.enable_runtime_warnings.
|
|
The behavior of affected program is not changed,
|
|
but they should still be fixed.
|
|
(Alain Frisch, review by Damien Doligez)
|
|
|
|
- Signal handling: for read-and-clear, use GCC/Clang atomic builtins
|
|
if available.
|
|
(Xavier Leroy)
|
|
|
|
- #6910, #224: marshaling (output_value, input_value, et al)
|
|
now support marshaled data bigger than 4 Gb.
|
|
(Xavier Leroy)
|
|
|
|
* #22: The undocumented layout of weak arrays has been changed. Finalisation
|
|
functions are now run before the erasure of the corresponding values.
|
|
|
|
* #226: select higher levels of optimization for GCC >= 3.4 and Clang
|
|
when compiling the run-time system and C stub code.
|
|
"-std=gnu99 -O2 -fno-strict-aliasing -fwrapv" is used by default.
|
|
This also affects default flags for user stubs compiled with "ocamlc -c foo.c"
|
|
and may uncover bugs in them.
|
|
(Xavier Leroy)
|
|
|
|
- #262: Multiple GC roots per compilation unit
|
|
(Pierre Chambart, Mark Shinwell, review by Damien Doligez)
|
|
|
|
* #297: Several changes to improve the worst-case GC pause time.
|
|
Changes Gc.control and Gc.major_slice and adds functions to the Gc module.
|
|
(Damien Doligez, with help from François Bobot, Thomas Braibant, Leo White)
|
|
|
|
- #325: Add v=0x400 flag to OCAMLRUNPARAM to display GC stats on exit
|
|
(Louis Gesbert, review by Alain Frisch)
|
|
|
|
### Standard library:
|
|
|
|
- #7848, #230: Array.map2, Array.iter2
|
|
(John Christopher McAlpine)
|
|
|
|
- #5197, #63: Arg: allow flags such as --flag=arg as well as --flag arg
|
|
(Richard Jones)
|
|
|
|
- #6017, #7034, #267: More efficient ifprintf implementation
|
|
(Jeremy Yallop, review by Gabriel Scherer)
|
|
|
|
- #6296: Some documentation on the floating-point representations
|
|
recognized by Pervasives.float_of_string
|
|
(Xavier Leroy)
|
|
|
|
- #6316: Scanf.scanf failure on %u formats when reading big integers
|
|
(Xavier Leroy, Benoît Vaugon)
|
|
|
|
- #6321: guarantee that "hypot infinity nan = infinity"
|
|
(for conformance with ISO C99)
|
|
(Xavier Leroy)
|
|
|
|
- #6390, #36: expose Sys.{int_size,max_wosize} for js_of_ocaml portability
|
|
(Hugo Heuzard)
|
|
|
|
- #6449: Add Map.union
|
|
(Alain Frisch)
|
|
|
|
* #6494: Add 'equal' functions in modules
|
|
Bytes, Char, Digest, Int32, Int64, Nativeint, and String
|
|
Users defining their own modules with signature 'module type of Int32'
|
|
have to extend their implementation.
|
|
(Romain Calascibetta)
|
|
|
|
* #6524, #79: Filename: Optional ?perms argument to open_temp_file
|
|
May break partial applications of the function (fix by passing ?perms:None)
|
|
(Daniel Bünzli, review by Kate Deplaix)
|
|
|
|
* #6525, #80: Add Uchar module to the standard library
|
|
May introduce module name conflicts with existing projects.
|
|
(Daniel Bünzli, review by Yoriyuki Yamagata and Damien Doligez)
|
|
|
|
- #6577: improve performance of %L, %l, %n, %S, %C format specifiers
|
|
(Alain Frisch)
|
|
|
|
- #6585: fix memory leak in win32unix/createprocess.c
|
|
(Alain Frisch, report by user 'aha')
|
|
|
|
- #6645, #174: Guarantee that Set.add, Set.remove, Set.filter
|
|
return the original set if no change is required
|
|
(Alain Frisch, Mohamed Iguernlala)
|
|
|
|
- #6649, #222: accept (int_of_string "+3")
|
|
(John Christopher McAlpine)
|
|
|
|
- #6694, #6695, #124: deprecate functions using ISO-8859-1 character set
|
|
in Char, Bytes, String and provide alternatives *_acii using US-ASCII.
|
|
Affected functions:
|
|
{Char,String,Bytes}.{uppercase,lowercase},
|
|
{String,Bytes}.{capitalize,uncaptialize}
|
|
(whitequark, review by Damien Doligez)
|
|
|
|
- #22: Add the Ephemeron module that implements ephemerons and weak
|
|
hash table
|
|
(François Bobot, review by Damien Doligez, Daniel Bünzli,
|
|
Alain Frisch, Pierre Chambart)
|
|
|
|
- #164: more efficient (branchless) implementation of Pervasives.compare
|
|
specialized at type 'float'.
|
|
(Vladimir Brankov)
|
|
|
|
- #175: Guarantee that Map.add, Map.remove, Map.filter
|
|
return the original map if no change is required.
|
|
(Mohamed Iguernlala)
|
|
|
|
- #201: generalize types of Printf.{ifprintf,ikfprintf}
|
|
(Maxence Guesdon)
|
|
|
|
- #216: add the missing POSIX.1-2001 signals in Sys
|
|
(Guillaume Bury)
|
|
|
|
- #239: remove type-unsafe code from Stream
|
|
(Pierre Chambart, review by Gabriel Scherer and Jeremy Yallop)
|
|
|
|
- #250: Check for negative start element in Array.sub
|
|
(Jeremy Yallop)
|
|
|
|
- #265: new implementation of Queue avoiding Obj.magic
|
|
(Jérémie Dimino)
|
|
|
|
- #268, #303: '%h' and '%H' modifiers for printf and scanf to
|
|
support floating-point numbers in hexadecimal notation
|
|
(Xavier Leroy, Benoît Vaugon)
|
|
|
|
- #272: Switch classify_float to [@@unboxed]
|
|
(Alain Frisch)
|
|
|
|
- Improve speed of classify_float by not going through fpclassify()
|
|
(Alain Frisch, Xavier Leroy)
|
|
|
|
- #277: Switch the following externals to [@@unboxed]:
|
|
* {Nativeint,Int32,Int64}.{of,to}_float
|
|
* Int{32,64}.float_of_bits
|
|
* Int{32,64}.bits_of_float
|
|
(Jérémie Dimino)
|
|
|
|
- #281: Switch the following externals to [@@unboxed]:
|
|
* Sys.time (and [@@noalloc])
|
|
* Pervasives.ldexp (and [@@noalloc])
|
|
* Pervasives.compare for float, nativeint, int32, int64.
|
|
(François Bobot)
|
|
|
|
- #3622, #195: add function Stack.fold
|
|
(Simon Cruanes)
|
|
|
|
- #329: Add exists, for_all, mem and memq functions in Array
|
|
(Bernhard Schommer)
|
|
|
|
- #337: Add [Hashtbl.filter_map_inplace]
|
|
(Alain Frisch)
|
|
|
|
- #356: Add [Format.kasprintf]
|
|
(Jérémie Dimino, Mark Shinwell)
|
|
|
|
### Type system:
|
|
|
|
- #5545: Type annotations on methods cannot control the choice of abbreviation
|
|
(Jacques Garrigue)
|
|
|
|
* #6465: allow incremental weakening of module aliases.
|
|
This is done by adding equations to submodules when expanding aliases.
|
|
In theory this may be incompatible is some corner cases defining a module
|
|
type through inference, but no breakage known on published code.
|
|
(Jacques Garrigue)
|
|
|
|
- #6593: Functor application in tests/basic-modules fails after commit 15405
|
|
(Jacques Garrigue)
|
|
|
|
### Toplevel and debugger:
|
|
|
|
- #6113: Add descriptions to directives, and display them via #help
|
|
(Nick Giannarakis, Berke Durak, Francis Southern and Gabriel Scherer)
|
|
|
|
- #6396: Warnings-as-errors not properly flushed in the toplevel
|
|
(Alain Frisch)
|
|
|
|
- #6401: use proper error reporting for toplevel environment initialization:
|
|
no more Env.Error(_) at start time
|
|
(Gabriel Scherer, Alain Frisch)
|
|
|
|
- #6468: toplevel now supports backtraces if invoked with OCAMLRUNPARAM=b
|
|
(whitequark and Jake Donham,
|
|
review by Gabriel Scherer and Jacques-Henri Jourdan)
|
|
|
|
- #6906: wrong error location for unmatched paren with #use in toplevel
|
|
(Damien Doligez, report by Kenichi Asai)
|
|
|
|
- #6935, #298: crash in debugger when load_printer is given a directory
|
|
(Junsong Li, review by Gabriel Scherer)
|
|
|
|
- #7081: report preprocessor warnings in the toplevel
|
|
(Valentin Gatien-Baron, review by Jérémie Dimino)
|
|
|
|
- #7098: Loss of ppx context in toplevel after an exception
|
|
(Alain Frisch, report by whitequark)
|
|
|
|
- #7101: The toplevel does not close in_channel for libraries specified on
|
|
its command line
|
|
(Alain Frisch)
|
|
|
|
- #7119: the toplevel does not respect [@@@warning]
|
|
(Alain Frisch, report by Gabriel Radanne)
|
|
|
|
### Other libraries:
|
|
|
|
* Unix library: channels created by Unix.in_channel_of_descr or
|
|
Unix.out_channel_of_descr no longer support text mode under Windows.
|
|
Calling [set_binary_mode_{in,out} chan false] on these channels
|
|
now causes an error.
|
|
(Xavier Leroy)
|
|
|
|
- #4023 and #68: add Unix.sleepf (sleep with sub-second resolution)
|
|
(Evgenii Lepikhin and Xavier Leroy)
|
|
|
|
* Protect Unix.sleep against interruptions by handled signals.
|
|
Before, a handled signal could cause Unix.sleep to return early.
|
|
Now, the sleep is restarted until the given time is elapsed.
|
|
(Xavier Leroy)
|
|
|
|
* #6120, #462: implement Unix.symlink and Unix.readlink on
|
|
Windows. Unix.symlink has a new optional argument to_dir (ignored on
|
|
non-native Windows platforms). stat functions reimplemented to avoid
|
|
buggy Microsoft CRT implementations (native Windows only)
|
|
(David Allsopp, review by Daniel Bünzli)
|
|
|
|
- #6263: add kind_size_in_bytes and size_in_bytes functions
|
|
to Bigarray module.
|
|
(Runhang Li, review by Mark Shinwell)
|
|
|
|
- #6289: Unix.utimes uses the current time only if both arguments
|
|
are exactly 0.0. Also, use sub-second resolution if available.
|
|
(Xavier Leroy, report by Christophe Troestler)
|
|
|
|
- #6896: serious reimplementation of Big_int.float_of_big_int and
|
|
Ratio.float_of_ratio, ensuring that the result is correctly rounded.
|
|
(Xavier Leroy)
|
|
|
|
- #6989: in Str library, make sure that all \(...\) groups are binding
|
|
and can be consulted with Str.matched_group. There used to be
|
|
a limitation to 32 binding groups.
|
|
(Xavier Leroy)
|
|
|
|
- #7013: spurious wake-up in the Event module
|
|
(Xavier Leroy)
|
|
|
|
- #7024: in documentation of Str regular expressions, clarify what
|
|
"end of line" means for "^" and "$" regexps.
|
|
(Xavier Leroy, question by Fredrik Lindgren)
|
|
|
|
- #7209: do not run at_exit handlers in [Unix.create_process] and
|
|
similar functions when the [exec] call fails in the child process
|
|
(Jérémie Dimino)
|
|
|
|
### OCamldep:
|
|
|
|
- #286: add support for module aliases
|
|
(Jacques Garrigue)
|
|
|
|
### Manual:
|
|
|
|
- #302: The OCaml reference manual is now included in the manual/
|
|
subdirectory of the main OCaml source repository. Contributions to
|
|
the manual are warmly welcome.
|
|
(François Bobot, review by Florian Angeletti)
|
|
|
|
- #6601: replace strcpy with caml_strdup in sample code
|
|
(Christopher Zimmermann)
|
|
|
|
- #6676: ongoing simplification of the "Language Extensions" section
|
|
(Alain Frisch, John Whitington)
|
|
|
|
- #6898: Update win32 support documentation of the Unix library
|
|
(Damien Doligez, report by Daniel Bünzli)
|
|
|
|
- #7092, #379: Add missing documentation for new 4.03 features
|
|
(Florian Angeletti)
|
|
|
|
- #7094, #468, #551: add new section 8.5 to document warnings
|
|
The general idea is to document warnings that may require explanations.
|
|
Currently documented warnings are:
|
|
- 52: Fragile constant pattern.
|
|
- 57: Ambiguous or-pattern variables under guard
|
|
(Florian Angeletti and Gabriel Scherer)
|
|
|
|
- #7109, #380: Fix bigarray documentation layout
|
|
(Florian Angeletti, Leo White)
|
|
|
|
### Bug fixes:
|
|
|
|
- #3612: memory leak in bigarray read from file
|
|
(Pierre Chambart, report by Gary Huber)
|
|
|
|
* #4166, #6956: force linking when calling external C primitives
|
|
(Jacques Garrigue, reports by Markus Mottl and Christophe Troestler)
|
|
|
|
* #4466, #5325: under Windows, concurrent read and write operations
|
|
on the same socket could block unexpectedly. Fixed by keeping sockets
|
|
in asynchronous mode rather than creating them in synchronous mode.
|
|
(Xavier Leroy)
|
|
|
|
* #4539: change exception string raised when comparing functional values
|
|
May break programs matching on the string argument of Invalid_argument.
|
|
Matching on the string argument of Invalid_argument or Failure is a
|
|
programming mistake: these strings may change in future versions.
|
|
(Nicolas Braud-Santoni, report by Eric Cooper)
|
|
|
|
- #4832: Filling bigarrays may block out runtime
|
|
(Markus Mottl)
|
|
|
|
- #5663: program rejected due to nongeneralizable type variable that
|
|
appears nowhere
|
|
(Jacques Garrigue, report by Stephen Weeks)
|
|
|
|
- #5780: report more informative type names in GADTs error messages
|
|
(Jacques Garrigue, report by Sebastien Furic)
|
|
|
|
- #5887: move the byterun/*.h headers to byterun/caml/*.h to avoid header
|
|
name clashes
|
|
(Jérôme Vouillon and Adrien Nader and whitequark)
|
|
|
|
* #6081: ocaml now adds script's directory to search path, not current
|
|
directory
|
|
(Thomas Leonard and Damien Doligez)
|
|
|
|
- #6108, #6802: fail cleanly if dynlink.cma or ocamltoplevel.cma
|
|
are loaded inside the toplevel loop.
|
|
(Xavier Leroy)
|
|
|
|
- #6171: Confusing error message when a type escapes its scope.
|
|
(Jacques Garrigue and Leo White, report by John Whitington)
|
|
|
|
- #6340: Incorrect handling of \r when processing "Windows" source files
|
|
(Damien Doligez, report by David Allsopp)
|
|
|
|
- #6342: Incorrect error message when type constraints differ
|
|
(Alain Frisch, report by Philippe Wang)
|
|
|
|
* #6521: {Bytes,Char,String}.escaped were locale-dependent
|
|
we now escape all non-ASCII-printable instead of a locale-dependent subset.
|
|
(Damien Doligez, report by Jun Furuse)
|
|
|
|
- #6526: ocamllex should not warn on unescaped newline inside comments
|
|
(Damien Doligez, report by user 'dhekir')
|
|
|
|
- #6341: ocamldoc -colorize-code adds spurious <br> tags to <pre> blocks
|
|
(Maxence Guesdon, report by Damien Doligez)
|
|
|
|
- #6560: Wrong failure message for {Int32,Int64,NativeInt}.of_string
|
|
It reported (Failure "int_of_string"), now "Int32.of_string" etc.
|
|
(Maxime Dénès and Gabriel Scherer)
|
|
|
|
- #6648: show_module should indicate its elision
|
|
(Jacques Garrigue, report by Leo White)
|
|
|
|
- #6650: Cty_constr not handled correctly by Subst
|
|
(Jacques Garrigue, report by Leo White)
|
|
|
|
- #6651: Failing component lookup
|
|
(Jacques Garrigue, report by Leo White)
|
|
|
|
* #6664: Crash when finalising lazy values of the wrong type.
|
|
(Damien Doligez)
|
|
|
|
- #6672: Unused variance specification allowed in with constraint
|
|
(Jacques Garrigue, report by Leo White)
|
|
|
|
- #6677: Allow to disable warning 39 (useless "rec") with [@ocaml.warning]
|
|
applied to the first value binding of the would-be "rec" declaration
|
|
(Alain Frisch, report by Jun Furuse)
|
|
|
|
- #6744: Univars can escape through polymorphic variants (partial fix)
|
|
(Jacques Garrigue, report by Leo White)
|
|
|
|
- #6752: Extensible variant types and scope escaping
|
|
A side-effect of the fix is that (ocamlc -i) sometimes reports
|
|
(type-sound) invalid signature, with a type used before its declaration.
|
|
(Jacques Garrigue, report by Maxence Guesdon)
|
|
|
|
- #6762: improve warning 45 in presence of re-exported type definitions
|
|
(Warning 45: open statement shadows the constructor)
|
|
(Alain Frisch, report by Olivier Andrieu)
|
|
|
|
- #6776: Failure to kill the "tick" thread, segfault when exiting the runtime
|
|
(Damien Doligez, report by Thomas Braibant)
|
|
|
|
- #6780: Poor error message for wrong -farch and -ffpu options (ocamlopt, ARM)
|
|
(Xavier Leroy, report by whitequark)
|
|
|
|
- #6805: Duplicated expression in case of hole in a non-failing switch.
|
|
(Luc Maranget)
|
|
|
|
* #6808: the parsing of OCAMLRUNPARAM is too lax
|
|
(Damien Doligez)
|
|
|
|
- #6874: Inefficient code generated for module function arguments
|
|
(Jacques Garrigue, report by Markus Mottl)
|
|
|
|
- #6888: The list command of ocamldebug uses the wrong file
|
|
(Damien Doligez, report by Pierre-Marie Pédrot)
|
|
|
|
- #6897: Bad error message for some pattern matching on extensible variants
|
|
(Alain Frisch, report by Gabriel Radanne)
|
|
|
|
- #6899: Optional parameters and non generalizable type variables
|
|
(Thomas Refis and Leo White)
|
|
|
|
- #6907: Stack overflow printing error in class declaration
|
|
(Jacques Garrigue, report by Ivan Gotovchits)
|
|
|
|
- #6931: Incorrect error message on type error inside record construction
|
|
(Damien Doligez, report by Leo White)
|
|
|
|
- #6938: fix regression on "%047.27{l,L,n}{d,i,x,X,o,u}"
|
|
(Benoît Vaugon, report by Arduino Cascella)
|
|
|
|
- #6944: let module X = Path in … is not typed as a module alias
|
|
(Jacques Garrigue, report by Frédéric Bour)
|
|
|
|
- #6945 and #227: protect Sys and Unix functions against string
|
|
arguments containing the null character '\000'
|
|
(Simon Cruanes and Xavier Leroy, report by Daniel Bünzli)
|
|
|
|
- #6946: Uncaught exception with wrong type for "%ignore"
|
|
(Jacques Garrigue, report by Leo White)
|
|
|
|
- #6954: Infinite loop in type checker with module aliases
|
|
(Jacques Garrigue, report by Markus Mottl)
|
|
|
|
- #6972, #276: 4.02.3 regression on documentation comments in .cmt files
|
|
(Leo White, report by Olivier Andrieu)
|
|
|
|
- #6977: String literals in comments interpret escape sequences
|
|
(Damien Doligez, report by Daniel Bünzli and David Sheets)
|
|
|
|
- #6980: Assert failure from polymorphic variants and existentials
|
|
(Jacques Garrigue, report by Leo White)
|
|
|
|
- #6981: Ctype.Unify(_) with associated functor arg referring to previous one
|
|
(Jacques Garrigue, report by Nicholas Labich)
|
|
|
|
- #6982: unexpected type error when packing a module alias
|
|
(Jacques Garrigue, report by Valentin Gatien-Baron)
|
|
|
|
- #6985: `module type of struct include Bar end exposes
|
|
%s#row when Bar contains private row types
|
|
(Jacques Garrigue, report by Nicholas Labich)
|
|
|
|
- #6992: Segfault from bug in GADT/module typing
|
|
(Jacques Garrigue, report by Stephen Dolan)
|
|
|
|
- #6993: Segfault from recursive modules violating exhaustiveness assumptions
|
|
(Jacques Garrigue, report by Stephen Dolan)
|
|
|
|
- #6998: Typer fails reading unnecessary cmis with -no-alias-deps and -w -49
|
|
(Leo White, report by Valentin Gatien-Baron)
|
|
|
|
- #7003: String.sub may cause segmentation fault on sizes above 2^31
|
|
(Damien Doligez, report by Radek Micek)
|
|
|
|
- #7008: Fatal error in ocamlc with empty compilation unit name
|
|
(Damien Doligez, report by Cesar Kunz)
|
|
|
|
- #7012: Variable name forgotten when it starts with a capital letter
|
|
(Jacques Garrigue, Gabriel Scherer,
|
|
report by Thomas Leonard and Florian Angeletti)
|
|
|
|
- #7016: fix Stack overflow in GADT typing
|
|
Note: Equi-recursive types are considered when checking GADT pattern
|
|
exhaustiveness, even when -rectypes is not used.
|
|
(Jacques Garrigue, report by Mikhail Mandrykin)
|
|
|
|
- #7030: libasmrun_shared.so fails to build on SPARC Solaris
|
|
(report and fix by Patrick Star)
|
|
|
|
- #7036: Module alias is not taken into account when checking module
|
|
type compatibility (in a class type)
|
|
(Jacques Garrigue)
|
|
|
|
- #7037: more reproducible builds, don't put temp file names into objects
|
|
(Xavier Leroy)
|
|
|
|
- #7038: out of memory condition in caml_io_mutex_lock
|
|
(Xavier Leroy, report by Marc Lasson)
|
|
|
|
- #7039: Unix.getsockname returns garbage for unnamed PF_UNIX sockets
|
|
(Xavier Leroy)
|
|
|
|
- #7042 and #295: CSE optimization confuses the FP literals +0.0 and -0.0
|
|
(Xavier Leroy)
|
|
|
|
- #7075: Fix repetitions in ocamldoc generated documentation
|
|
(Florian Angeletti)
|
|
|
|
- #7082: Object type in recursive module's `with` annotation
|
|
(Jacques Garrigue and Alain Frisch, report by Nicholas Labich)
|
|
|
|
- #7096: ocamldoc uses an incorrect subscript/superscript style
|
|
(Gabriel Scherer, report by user 'pierpa')
|
|
|
|
- #7108: ocamldoc, have -html preserve custom/extended html generators
|
|
(Armaël Guéneau)
|
|
|
|
- #7111: reject empty let bindings instead of printing incorrect syntax
|
|
(Jérémie Dimino)
|
|
|
|
* #7113: -safe-string can break GADT compatibility check
|
|
bytes and string are now considered compatible even with -safe-string,
|
|
which may break exhaustivity for code assuming they were disjoint
|
|
(Jacques Garrigue, report by Jeremy Yallop)
|
|
|
|
- #7115: shadowing in a branch of a GADT match breaks unused variable warning
|
|
(Alain Frisch, report by Valentin Gatien-Baron)
|
|
|
|
- #7133, #450: generate local jump labels on OS X
|
|
(Bart Jacobs)
|
|
|
|
- #7135: only warn about ground coercions in -principal mode
|
|
(Jacques Garrigue, report by Jeremy Yallop)
|
|
|
|
* #7152: Typing equality involving non-generalizable type variable
|
|
A side-effect of the fix is that, for deeply nested non generalizable
|
|
type variables, having an interface file may no longer be sufficient,
|
|
and you may have to add a local type annotation (cf #7313)
|
|
(Jacques Garrigue, report by François Bobot)
|
|
|
|
- #7160: Type synonym definitions can weaken gadt constructor types
|
|
(Jacques Garrigue, report by Mikhail Mandrykin)
|
|
|
|
- #7181: Misleading error message with GADTs and polymorphic variants
|
|
(Jacques Garrigue, report by Pierre Chambart)
|
|
|
|
- #7182: Assertion failure with recursive modules and externals
|
|
(Jacques Garrigue, report by Jeremy Yallop)
|
|
|
|
- #7196: "let open" is not correctly pretty-printed to the left of a ';'
|
|
(Gabriel Scherer, report by Christophe Raffalli)
|
|
|
|
- #7214: Assertion failure in Env.add_gadt_instances
|
|
(Jacques Garrigue, report by Stephen Dolan)
|
|
|
|
- #7220: fix a memory leak when using both threads and exception backtraces
|
|
(Gabriel Scherer, review by François Bobot, report by Rob Hoes)
|
|
|
|
- #7222: Escaped existential type
|
|
(Jacques Garrigue, report by Florian Angeletti)
|
|
|
|
- #7230: Scrutinee discarded in match with only refutation cases
|
|
(Jacques Garrigue, report by Jeremy Yallop)
|
|
|
|
- #7234: Compatibility check wrong for abstract type constructors
|
|
(Jacques Garrigue, report by Stephen Dolan)
|
|
|
|
- #7324: OCaml 4.03.0 type checker dies with an assert failure when
|
|
given some cyclic recursive module expression
|
|
(Jacques Garrigue, report by jmcarthur)
|
|
|
|
- #7368: Manual major GC fails to compact the heap
|
|
(Krzysztof Pszeniczny)
|
|
|
|
- #205: Clear caml_backtrace_last_exn before registering as root
|
|
(report and fix by Frédéric Bour)
|
|
|
|
- #220: minor -dsource error on recursive modules
|
|
(Hongbo Zhang)
|
|
|
|
- #228: fix a dangling internal pointer in (bytecode )debug_info
|
|
(Gabriel Scherer and Mark Shinwell and Xavier Leroy)
|
|
|
|
- #233: Make CamlinternalMod.init_mod robust to optimization
|
|
(Pierre Chambart, Mark Shinwell)
|
|
|
|
- #249: fix a few hardcoded ar commands
|
|
(Daniel Bünzli)
|
|
|
|
- #251: fix cross-compilation with ocamldoc enabled
|
|
(whitequark)
|
|
|
|
- #280: Fix stdlib dependencies for .p.cmx
|
|
(Pierre Chambart, Mark Shinwell)
|
|
|
|
- #283: Fix memory leaks in intern.c when OOM is raised
|
|
(Marc Lasson, review by Alain Frisch)
|
|
|
|
- #22: Fix the cleaning of weak pointers. In very rare cases
|
|
accessing a value during the cleaning of the weak pointers could
|
|
result in the value being removed from one weak arrays and kept in
|
|
another one. That breaks the property that a value is removed from a
|
|
weak pointer only when it is dead and garbage collected.
|
|
(François Bobot, review by Damien Doligez)
|
|
|
|
- #313: Prevent quadratic cases in CSE
|
|
(Pierre Chambart, review by Xavier Leroy)
|
|
|
|
- #6795, #6996: Make ocamldep report errors passed in
|
|
[%ocaml.error] extension points
|
|
(Jérémie Dimino)
|
|
|
|
- #355: make ocamlnat build again
|
|
(Jérémie Dimino, Thomas Refis)
|
|
|
|
- #405: fix compilation under Visual Studio 2015
|
|
(David Allsopp)
|
|
|
|
- #441: better type error location in presence of type constraints
|
|
(Thomas Refis, report by Arseniy Alekseyev)
|
|
|
|
- #477: reallow docstrings inside object types, and inside polymorphic
|
|
variant and arrow types
|
|
(Thomas Refis)
|
|
|
|
### Features wishes:
|
|
|
|
- #4518, #29: change location format for reporting errors in ocamldoc
|
|
(Sergei Lebedev)
|
|
|
|
- #4714: List.cons
|
|
|
|
- #5418 (comments) : generate dependencies with $(CC) instead of gcc
|
|
(Damien Doligez, report by Michael Grünewald)
|
|
|
|
- #6167: OCAMLPARAM support for disabling PIC generation ("pic=0")
|
|
(Gabor Pali)
|
|
|
|
- #6367, #25: introduce Asttypes.arg_label to encode labelled arguments
|
|
(Frédéric Bour and Jacques Garrigue)
|
|
|
|
- #6452, #140: add internal support for custom printing formats
|
|
(Jérémie Dimino)
|
|
|
|
- #6611: remove the option wrapper on optional arguments in the syntax tree
|
|
(Alain Frisch, review by Damien Doligez, request by whitequark)
|
|
|
|
- #6635: support M.[], M.(), M.{< >} and M.[| |]
|
|
(Jeremy Yallop, review by Gabriel Radanne)
|
|
|
|
- #6691: install .cmt[i] files for stdlib and compiler-libs
|
|
(David Sheets, request by Gabriel Radanne)
|
|
|
|
- #6722: compatibility with x32 architecture (x86-64 in ILP32 mode).
|
|
ocamlopt is not supported, but bytecode compiles cleanly.
|
|
(Adam Borowski and Xavier Leroy)
|
|
|
|
- #6742: remove duplicate virtual_flag information from Tstr_class
|
|
(Gabriel Radanne and Jacques Garrigue)
|
|
|
|
- #6719: improve Buffer.add_channel when not enough input is available
|
|
(Simon Cruanes)
|
|
|
|
* #6816: reject integer and float literals directly followed by an identifier.
|
|
This was previously read as two separate tokens.
|
|
[let abc = 1 in (+) 123abc] was accepted and is now rejected.
|
|
(Hugo Heuzard)
|
|
|
|
- #6876: improve warning 6 by listing the omitted labels.
|
|
(Warning 6: Label omitted in function application)
|
|
(Eyyüb Sari)
|
|
|
|
- #6924: tiny optim to avoid some spilling of floats in x87
|
|
(Alain Frisch)
|
|
|
|
- #111: `(f [@taillcall]) x y` warns if `f x y` is not a tail-call
|
|
(Simon Cruanes)
|
|
|
|
- #118: ocamldep -allow-approx: fallback to a lexer-based approximation
|
|
(Frédéric Bour)
|
|
|
|
- #137: add untypeast.ml (in open recursion style) to compiler-libs
|
|
(Gabriel Radanne)
|
|
|
|
- #142: add a CAMLdrop macro for undoing CAMLparam*/CAMLlocal*
|
|
(Thomas Braibant and Damien Doligez)
|
|
|
|
- #145: speeedup bigarray access by optimizing Cmmgen.bigarray_indexing
|
|
(Vladimir Brankov, review by Gabriel Scherer)
|
|
|
|
- #147: [type 'a result = Ok of 'a | Error of 'b] in Pervasives
|
|
(Yaron Minsky)
|
|
|
|
- #156, #279: optimize caml_frame_descriptors realloc (dynlink speedup)
|
|
(Pierre Chambart, Alain Frisch,
|
|
review by François Bobot, Xavier Leroy and Damien Doligez)
|
|
|
|
- #165, #221: fix windows compilation warnings
|
|
(Bernhard Schommer, Gabriel Scherer, report by Alain Frisch)
|
|
|
|
* #170: Parse arbitrary precision integers.
|
|
Accept a single [A-Za-z] as modifier for integers (generalizing 'l','L','n')
|
|
and floats.
|
|
May cause breakage (ie. ppx preprocessor) because of changes in the parsetree.
|
|
This changes #6816 a little bit by reading the literal [123a] as a single
|
|
token that can later be rewritten by a ppx preprocessor.
|
|
(Hugo Heuzard)
|
|
|
|
- #189: Added .dylib and .so as extensions for ocamlmklib
|
|
(Edgar Aroutiounian, whitequark)
|
|
|
|
- #191: Making gc.h and some part of memory.h public
|
|
(Thomas Refis)
|
|
|
|
- #196: Make [Thread.id] and [Thread.self] [noalloc]
|
|
(Clark Gaebel)
|
|
|
|
- #237: a CONTRIBUTING document
|
|
(François Bobot, Gabriel Scherer, review by Xavier Leroy)
|
|
|
|
- #245: remove a few remaining French comments
|
|
(Florian Angeletti)
|
|
|
|
- #252: improve build instructions in MSVC Windows README
|
|
(Philip Daian)
|
|
|
|
- #308: add experimental support for NetBSD/arm (verified on RaspberryPi)
|
|
(Rich Neswold)
|
|
|
|
- #335: Type error messages specifies if a type is abstract
|
|
because no corresponding cmi could be found.
|
|
(Hugo Heuzard)
|
|
|
|
- #365: prevent printing just a single type variable on one side
|
|
of a type error clash.
|
|
(Hugo Heuzard)
|
|
|
|
- #383: configure: define _ALL_SOURCE for build on AIX7.1
|
|
(tkob)
|
|
|
|
- #401: automatically retry failed test directories in the testsuite
|
|
(David Allsopp)
|
|
|
|
- #451: an optional 'parallel' target in testsuite/Makefile using the
|
|
GNU parallel tool to run tests in parallel.
|
|
(Gabriel Scherer)
|
|
|
|
- #555: ensure that register typing constraints are respected at
|
|
join points in the control flow graph
|
|
(Mark Shinwell, debugging & test case by Arseniy Alekseyev and Leo White,
|
|
code review by Xavier Leroy)
|
|
|
|
### Build system:
|
|
|
|
- #388: FlexDLL added as a Git submodule and bootstrappable with the compiler
|
|
(David Allsopp)
|
|
|
|
OCaml 4.02.3 (27 Jul 2015):
|
|
---------------------------
|
|
|
|
Bug fixes:
|
|
- #6908: Top-level custom printing for GADTs: interface change in 4.02.2
|
|
(Grégoire Henry, report by Jeremy Yallop)
|
|
- #6919: corrupted final_table
|
|
(ygrek)
|
|
- #6926: Regression: ocamldoc lost unattached comment
|
|
(Damien Doligez, report by François Bobot)
|
|
- #6930: Aliased result type of GADT constructor results in assertion failure
|
|
(Jacques Garrigue)
|
|
|
|
Feature wishes:
|
|
- #6691: install .cmt[i] files for stdlib and compiler-libs
|
|
(David Sheets, request by Gabriel Radanne)
|
|
- #37: New primitive: caml_alloc_dummy_function
|
|
(Hugo Heuzard)
|
|
|
|
OCaml 4.02.2 (17 Jun 2015):
|
|
---------------------------
|
|
|
|
(Changes that can break existing programs are marked with a "*")
|
|
|
|
Language features:
|
|
- #6583: add a new class of binary operators with the same syntactic
|
|
precedence as method calls; these operators start with # followed
|
|
by a non-empty sequence of operator symbols (for instance #+, #!?).
|
|
It is also possible to use '#' as part of these extra symbols
|
|
(for instance ##, or #+#); this is rejected by the type-checker,
|
|
but can be used e.g. by ppx rewriters.
|
|
(Alain Frisch, request by Gabriel Radanne)
|
|
* #6016: add a "nonrec" keyword for type declarations
|
|
(Jérémie Dimino)
|
|
* #6612, #152: change the precedence of attributes in type declarations
|
|
(Jérémie Dimino)
|
|
|
|
Compilers:
|
|
- #6600: make -short-paths faster by building the printing map
|
|
incrementally
|
|
(Jacques Garrigue)
|
|
- #6642: replace $CAMLORIGIN in -ccopt with the path to cma or cmxa
|
|
(whitequark, Gabriel Scherer, review by Damien Doligez)
|
|
- #6797: new option -output-complete-obj
|
|
to output an object file with included runtime and autolink libraries
|
|
(whitequark)
|
|
- #6845: -no-check-prims to tell ocamlc not to check primitives in runtime
|
|
(Alain Frisch)
|
|
- #149: Attach documentation comments to parse tree
|
|
(Leo White)
|
|
- #159: Better locations for structure/signature items
|
|
(Leo White)
|
|
|
|
Toplevel and debugger:
|
|
- #5958: generalized polymorphic #install_printer
|
|
(Pierre Chambart and Grégoire Henry)
|
|
|
|
OCamlbuild:
|
|
- #6237: explicit "infer" tag to control or disable menhir --infer
|
|
(Hugo Heuzard)
|
|
- #6625: pass -linkpkg to files built with -output-obj.
|
|
(whitequark)
|
|
- #6702: explicit "linkpkg" and "dontlink(foo)" flags
|
|
(whitequark, Gabriel Scherer)
|
|
- #6712: Ignore common VCS directories
|
|
(whitequark)
|
|
- #6720: pass -g to C compilers when tag 'debug' is set
|
|
(whitequark, Gabriel Scherer)
|
|
- #6733: add .byte.so and .native.so targets to pass
|
|
-output-obj -cclib -shared.
|
|
(whitequark)
|
|
- #6733: "runtime_variant(X)" to pass -runtime-variant X option.
|
|
(whitequark)
|
|
- #6774: new menhir-specific flags "only_tokens" and "external_tokens(Foo)"
|
|
(François Pottier)
|
|
|
|
Libraries:
|
|
- #6285: Add support for nanosecond precision in Unix.stat()
|
|
(Jérémie Dimino, report by user 'gfxmonk')
|
|
- #6781: Add higher baud rates to Unix termios
|
|
(Damien Doligez, report by Berke Durak)
|
|
- #6834: Add Obj.{first,last}_non_constant_constructor_tag
|
|
(Mark Shinwell, request by Gabriel Scherer)
|
|
|
|
Runtime:
|
|
- #6078: Release the runtime system when calling caml_dlopen
|
|
(Jérémie Dimino)
|
|
- #6675: GC hooks
|
|
(Damien Doligez and Roshan James)
|
|
|
|
Build system:
|
|
- #5418 (comments) : generate dependencies with $(CC) instead of gcc
|
|
(Damien Doligez and Michael Grünewald)
|
|
- #6266: Cross compilation for iOs, Android etc
|
|
(whitequark, review by Damien Doligez and Mark Shinwell)
|
|
|
|
Installation procedure:
|
|
- Update instructions for x86-64 PIC mode and POWER architecture builds
|
|
(Mark Shinwell)
|
|
|
|
Bug fixes:
|
|
- #5271: Location.prerr_warning is hard-coded to use Format.err_formatter
|
|
(Damien Doligez, report by Rolf Rolles)
|
|
- #5395: OCamlbuild mishandles relative symlinks and include paths
|
|
(Damien Doligez, report by Didier Le Botlan)
|
|
- #5822: wrong value of Options.ext_dll on windows
|
|
(Damien Doligez and Daniel Weil)
|
|
- #5836, #6684: printing lazy values in ocamldebug may segfault
|
|
(Gabriel Scherer, request by the Coq team)
|
|
- #5887: move the byterun/*.h headers to byterun/caml/*.h to avoid
|
|
header name clashes
|
|
(Jérôme Vouillon and Adrien Nader and whitequark)
|
|
- #6281: Graphics window does not acknowledge second click (double click)
|
|
(Kyle Headley)
|
|
- #6490: incorrect backtraces in gdb on AArch64. Also fixes incorrect
|
|
backtraces on 32-bit ARM.
|
|
(Mark Shinwell)
|
|
- #6573: extern "C" for systhreads/threads.h
|
|
(Mickaël Delahaye)
|
|
- #6575: Array.init evaluates callback although it should not do so
|
|
(Alain Frisch, report by Gerd Stolpmann)
|
|
- #6607: The manual doesn't mention 0x200 flag for OCAMLRUNPARAM=v
|
|
(Alain Frisch)
|
|
- #6616: allow meaningful use of -use-runtime without -custom.
|
|
(whitequark)
|
|
- #6617: allow android build with pthreads support (since SDK r10c)
|
|
(whitequark)
|
|
- #6626: ocamlbuild on cygwin cannot find ocamlfind
|
|
(Gergely Szilvasy)
|
|
- #6628: Configure script rejects legitimate arguments
|
|
(Michael Grünewald, Damien Doligez)
|
|
- #6630: Failure of tests/prim-bigstring/{big,}string.ml on big-endian
|
|
architectures
|
|
(Pierre Chambart, testing by Mark Shinwell)
|
|
- #6640: ocamlbuild: wrong "unused tag" warning on "precious"
|
|
(report by user 'william')
|
|
- #6652: ocamlbuild -clean does not print a newline after output
|
|
(Damien Doligez, report by Andi McClure)
|
|
- #6658: cross-compiler: version check not working on OS X
|
|
(Gerd Stolpmann)
|
|
- #6665: Failure of tests/asmcomp on sparc
|
|
(Stéphane Glondu)
|
|
- #6667: wrong implementation of %bswap16 on ARM64
|
|
(Xavier Leroy)
|
|
- #6669: fix 4.02 regression in toplevel printing of lazy values
|
|
(Leo White, review by Gabriel Scherer)
|
|
- #6671: Windows: environment variable 'TZ' affects Unix.gettimeofday
|
|
(Mickaël Delahaye and Damien Doligez)
|
|
- #6680: Missing parentheses in warning about polymorphic variant value
|
|
(Jacques Garrigue and Gabriel Scherer, report by Philippe Veber)
|
|
- #6686: Bug in [subst_boxed_number]
|
|
(Jérémie Dimino, Mark Shinwell)
|
|
- #6690: Uncaught exception (Not_found) with (wrong) wildcard or unification
|
|
type variable in place of a local abstract type
|
|
(Jacques Garrigue, report by Mikhail Mandrykin)
|
|
- #6693 (part two): Incorrect relocation types in x86-64 runtime system
|
|
(whitequark, review by Jacques-Henri Jourdan, Xavier Leroy and Mark Shinwell)
|
|
- #6717: Pprintast does not print let-pattern attributes
|
|
(Gabriel Scherer, report by whitequark)
|
|
- #6727: Printf.sprintf "%F" misbehavior
|
|
(Benoît Vaugon, report by Vassili Karpov)
|
|
- #6747: ocamlobjinfo: missing symbol caml_plugin_header due to underscore
|
|
(Damien Doligez, Maverick Woo)
|
|
- #6749: ocamlopt returns n for (n mod 1) instead of 0
|
|
(Mark Shinwell and Jérémie Dimino)
|
|
- #6753: Num.quo_num and Num.mod_num incorrect for some negative arguments
|
|
(Xavier Leroy)
|
|
- #6758: Ocamldoc "analyse_module: parsetree and typedtree don't match"
|
|
(Damien Doligez, report by user 'maro')
|
|
- #6759: big_int_of_string incorrectly parses some hexa literals
|
|
(Damien Doligez, report by Pierre-yves Strub)
|
|
- #6763: #show with -short-paths doesn't select shortest type paths
|
|
(Jacques Garrigue, report by David Sheets)
|
|
- #6768: Typechecker overflow the stack on cyclic type
|
|
(Jacques Garrigue, report by user 'darktenaibre')
|
|
- #6770: (duplicate of #6686)
|
|
- #6772: asmrun/signals_asm.c doesn't compile on NetBSD/i386
|
|
(Kenji Tokudome)
|
|
- #6775: Digest.file leaks file descriptor on error
|
|
(Valentin Gatien-Baron)
|
|
- #6779: Cross-compilers cannot link bytecode using custom primitives
|
|
(Damien Doligez, request by whitequark)
|
|
- #6787: Soundness bug with polymorphic variants
|
|
(Jacques Garrigue, with help from Leo White and Grégoire Henry,
|
|
report by Michael O'Connor)
|
|
- #6790: otherlibs should be built with -g
|
|
(Damien Doligez, report by whitequark)
|
|
- #6791: "%s@[", "%s@{" regression in Scanf
|
|
(Benoît Vaugon)
|
|
- #6793: ocamlbuild passes nonsensical "-ocamlc ..." commands to menhir
|
|
(Gabriel Scherer, report by Damien Doligez)
|
|
- #6799: include guards missing for unixsupport.h and other files
|
|
(Andreas Hauptmann)
|
|
- #6810: Improve documentation of Bigarray.Genarray.map_file
|
|
(Mark Shinwell and Daniel Bünzli)
|
|
- #6812: -short-paths and -no-alias-deps can create inconsistent assumptions
|
|
(Jacques Garrigue, report by Valentin Gatien-Baron)
|
|
- #6817: GADT exhaustiveness breakage with modules
|
|
(Leo White, report by Pierre Chambart)
|
|
- #6824: fix buffer sharing on partial application of Format.asprintf
|
|
(Gabriel Scherer, report by Alain Frisch)
|
|
- #6831: Build breaks for -aspp gcc on solaris-like OSs
|
|
(John Tibble)
|
|
- #6836: Assertion failure using -short-paths
|
|
(Jacques Garrigue, report by David Sheets)
|
|
- #6837: Build profiling libraries on FreeBSD and NetBSD x86-64
|
|
(Mark Shinwell, report by Michael Grünewald)
|
|
- #6841: Changing compilation unit name with -o breaks ocamldebug
|
|
(Jacques Garrigue, report by Jordan Walke)
|
|
- #6842: export Typemod.modtype_of_package
|
|
- #6843: record weak dependencies even when the .cmi is missing
|
|
(Leo White, Gabriel Scherer)
|
|
- #6849: Inverted pattern unification error
|
|
(Jacques Garrigue, report by Leo White)
|
|
- #6857: __MODULE__ doesn't give the current module with -o
|
|
(Jacques Garrigue, report by Valentin Gatien-Baron)
|
|
- #6862: Exhaustiveness check wrong for class constructor arguments
|
|
(Jacques Garrigue)
|
|
- #6869: Improve comment on [Hashtbl.hash_param]
|
|
(Mark Shinwell, report by Jun Furuse)
|
|
- #6870: Unsoundness when -rectypes fails to detect non-contractive type
|
|
(Jacques Garrigue, report by Stephen Dolan)
|
|
- #6872: Type-directed propagation fails to disambiguate variants
|
|
that are also exception constructors
|
|
(Jacques Garrigue, report by Romain Beauxis)
|
|
- #6878: AArch64 backend generates invalid asm: conditional branch
|
|
out of range (Mark Shinwell, report by Richard Jones, testing by Richard
|
|
Jones and Xavier Leroy, code review by Xavier Leroy and Thomas Refis)
|
|
- #6879: Wrong optimization of 1 mod n
|
|
(Mark Shinwell, report by Jean-Christophe Filliâtre)
|
|
- #6884: The __CYGWIN32__ #define should be replaced with __CYGWIN__
|
|
(Adrien Nader)
|
|
- #6886: -no-alias-deps allows to build self-referential compilation units
|
|
(Jacques Garrigue, report by Valentin Gatien-Baron)
|
|
- #6889: ast_mapper fails to rewrite class attributes
|
|
(Sébastien Briais)
|
|
- #6893: ocamlbuild: "tag not used" warning when using (p)dep
|
|
(Gabriel Scherer, report by Christiano Haesbaert)
|
|
- #143: fix getsockopt behaviour for boolean socket options
|
|
(Anil Madhavapeddy and Andrew Ray)
|
|
- #190: typo in pervasives
|
|
(Guillaume Bury)
|
|
- Misplaced assertion in major_gc.c for no-naked-pointers mode
|
|
(Stephen Dolan, Mark Shinwell)
|
|
|
|
Feature wishes:
|
|
- #6452, #140: add internal support for custom printing formats
|
|
(Jérémie Dimino)
|
|
- #6641: add -g, -ocamlcflags, -ocamloptflags options to ocamlmklib
|
|
(whitequark)
|
|
- #6693: also build libasmrun_shared.so and lib{asm,caml}run_pic.a
|
|
(whitequark, review by Mark Shinwell)
|
|
- #6842: export Typemod.modtype_of_package
|
|
(Jacques Garrigue, request by Jun Furuse)
|
|
- #139: more versatile specification of locations of .annot
|
|
(Christophe Troestler, review by Damien Doligez)
|
|
- #171: allow custom warning printers / catchers
|
|
(Benjamin Canou, review by Damien Doligez)
|
|
- #191: Making gc.h and some part of memory.h public
|
|
(Thomas Refis)
|
|
|
|
OCaml 4.02.1 (14 Oct 2014):
|
|
---------------------------
|
|
|
|
(Changes that can break existing programs are marked with a "*")
|
|
|
|
Standard library:
|
|
* Add optional argument ?limit to Arg.align.
|
|
|
|
Bug Fixes:
|
|
- #4099: Bug in Makefile.nt: won't stop on error
|
|
(George Necula)
|
|
- #6181: Improve MSVC build
|
|
(Chen Gang)
|
|
- #6207: Configure doesn't detect features correctly on Haiku
|
|
(Jessica Hamilton)
|
|
- #6466: Non-exhaustive matching warning message for open types is confusing
|
|
(whitequark)
|
|
- #6529: fix quadratic-time algorithm in Consistbl.extract.
|
|
(Xavier Leroy, Alain Frisch, relase-worthy report by Kate Deplaix)
|
|
- #6530: Add stack overflow handling for native code (OpenBSD i386 and amd64)
|
|
(Cristopher Zimmermann)
|
|
- #6533: broken semantics of %(%) when substituted by a box
|
|
(Benoît Vaugon, report by Boris Yakobowski)
|
|
- #6534: legacy support for %.10s
|
|
(Benoît Vaugon, Gabriel Scherer, report by Nick Chapman)
|
|
- #6536: better documentation of flag # in format strings
|
|
(Damien Doligez, report by Nick Chapman)
|
|
- #6544: Bytes and CamlinternalFormat missing from threads stdlib.cma
|
|
(Christopher Zimmermann)
|
|
- #6546: -dsource omits parens for `List ((`String "A")::[]) in patterns
|
|
(Gabriel Scherer, report by whitequark)
|
|
- #6547: __MODULE__ aborts the compiler if the module name cannot be inferred
|
|
(Jacques Garrigue, report by Kaustuv Chaudhuri)
|
|
- #6549: Debug section is sometimes not readable when using -pack
|
|
(Hugo Heuzard, review by Gabriel Scherer)
|
|
- #6553: Missing command line options for ocamldoc
|
|
(Maxence Guesdon)
|
|
- #6554: fix race condition when retrieving backtraces
|
|
(Jérémie Dimino, Mark Shinwell).
|
|
- #6557: String.sub throws Invalid_argument("Bytes.sub")
|
|
(Damien Doligez, report by Oliver Bandel)
|
|
- #6562: Fix ocamldebug module source lookup
|
|
(Leo White)
|
|
- #6563: Inclusion of packs failing to run module initializers
|
|
(Jacques Garrigue, report by Mark Shinwell)
|
|
- #6564: infinite loop in Mtype.remove_aliases
|
|
(Jacques Garrigue, report by Mark Shinwell)
|
|
- #6565: compilation fails with Env.Error(_)
|
|
(Jacques Garrigue and Mark Shinwell)
|
|
- #6566: -short-paths and signature inclusion errors
|
|
(Jacques Garrigue, report by Mark Shinwell)
|
|
- #6572: Fatal error with recursive modules
|
|
(Jacques Garrigue, report by Quentin Stievenart)
|
|
- #6575: Array.init evaluates callback although it should not do so
|
|
(Alain Frisch, report by Gerd Stolpmann)
|
|
- #6578: Recursive module containing alias causes Segmentation fault
|
|
(Jacques Garrigue)
|
|
- #6581: Some bugs in generative functors
|
|
(Jacques Garrigue, report by Mark Shinwell)
|
|
- #6584: ocamldep support for "-open M"
|
|
(Gabriel Scherer, review by Damien Doligez, report by Hezekiah M. Carty)
|
|
- #6588: Code generation errors for ARM
|
|
(Mark Shinwell, Xavier Leroy)
|
|
- #6590: Improve Windows (MSVC and mingw) build
|
|
(Chen Gang)
|
|
- #6599: ocamlbuild: add -bin-annot when using -pack
|
|
(Christopher Zimmermann)
|
|
- #6602: Fatal error when tracing a function with abstract type
|
|
(Jacques Garrigue, report by Hugo Herbelin)
|
|
- ocamlbuild: add an -ocamlmklib option to change the ocamlmklib command
|
|
(Jérôme Vouillon)
|
|
|
|
OCaml 4.02.0 (29 Aug 2014):
|
|
---------------------------
|
|
|
|
(Changes that can break existing programs are marked with a "*")
|
|
|
|
Language features:
|
|
- Attributes and extension nodes
|
|
(Alain Frisch)
|
|
- Generative functors (#5905)
|
|
(Jacques Garrigue)
|
|
* Module aliases
|
|
(Jacques Garrigue)
|
|
* Alternative syntax for string literals {id|...|id} (can break comments)
|
|
(Alain Frisch)
|
|
- Separation between read-only strings (type string) and read-write byte
|
|
sequences (type bytes). Activated by command-line option -safe-string.
|
|
(Damien Doligez)
|
|
- #6318: Exception cases in pattern matching
|
|
(Jeremy Yallop, backend by Alain Frisch)
|
|
- #5584: Extensible open datatypes
|
|
(Leo White)
|
|
|
|
Build system for the OCaml distribution:
|
|
- Use -bin-annot when building.
|
|
- Use GNU make instead of portable makefiles.
|
|
- Updated build instructions for 32-bit Mac OS X on Intel hardware.
|
|
|
|
Shedding weight:
|
|
* Removed Camlp4 from the distribution, now available as third-party software.
|
|
* Removed Labltk from the distribution, now available as a third-party library.
|
|
|
|
Type system:
|
|
* #6235: Keep typing of pattern cases independent in principal mode
|
|
(i.e. information from previous cases is no longer used when typing
|
|
patterns; cf. '#6235' in testsuite/test/typing-warnings/records.ml)
|
|
(Jacques Garrigue)
|
|
- Allow opening a first-class module or applying a generative functor
|
|
in the body of a generative functor. Allow it also in the body of
|
|
an applicative functor if no types are created
|
|
(Jacques Garrigue, suggestion by Leo White)
|
|
* Module aliases are now typed in a specific way, which remembers their
|
|
identity. Compiled interfaces become smaller, but may depend on the
|
|
original modules. This also changes the signature inferred by
|
|
"module type of".
|
|
(Jacques Garrigue, feedback from Leo White, Mark Shinwell and Nick Chapman)
|
|
- #6331: Slight change in the criterion to distinguish private
|
|
abbreviations and private row types: create a private abbreviation for
|
|
closed objects and fixed polymorphic variants.
|
|
(Jacques Garrigue)
|
|
* #6333: Compare first class module types structurally rather than
|
|
nominally. Value subtyping allows module subtyping as long as the internal
|
|
representation is unchanged.
|
|
(Jacques Garrigue)
|
|
|
|
Compilers:
|
|
- More aggressive constant propagation, including float and
|
|
int32/int64/nativeint arithmetic. Constant propagation for floats
|
|
can be turned off with option -no-float-const-prop, for codes that
|
|
change FP rounding modes at run-time.
|
|
(Xavier Leroy)
|
|
- New back-end optimization pass: common subexpression elimination (CSE).
|
|
(Reuses results of previous computations instead of recomputing them.)
|
|
(Xavier Leroy)
|
|
- New back-end optimization pass: dead code elimination.
|
|
(Removes arithmetic and load instructions whose results are unused.)
|
|
(Xavier Leroy)
|
|
- #6269: Optimization of sequences of string patterns
|
|
(Benoît Vaugon and Luc Maranget)
|
|
- Experimental native code generator for AArch64 (ARM 64 bits)
|
|
(Xavier Leroy)
|
|
- #6042: Optimization of integer division and modulus by constant divisors
|
|
(Xavier Leroy and Phil Denys)
|
|
- Add "-open" command line flag for opening a single module before typing
|
|
(Leo White, Mark Shinwell and Nick Chapman)
|
|
* "-o" now sets module name to the output file name up to the first "."
|
|
(it also applies when "-o" is not given, i.e. the module name is then
|
|
the input file name up to the first ".")
|
|
(Leo White, Mark Shinwell and Nick Chapman)
|
|
* #5779: better sharing of structured constants
|
|
(Alain Frisch)
|
|
- #5817: new flag to keep locations in cmi files
|
|
(Alain Frisch)
|
|
- #5854: issue warning 3 when referring to a value marked with
|
|
the [@@ocaml.deprecated] attribute
|
|
(Alain Frisch, suggestion by Pierre-Marie Pédrot)
|
|
- #6017: a new format implementation based on GADTs
|
|
(Benoît Vaugon and Gabriel Scherer)
|
|
* #6203: Constant exception constructors no longer allocate
|
|
(Alain Frisch)
|
|
- #6260: avoid unnecessary boxing in let
|
|
(Vladimir Brankov)
|
|
- #6345: Better compilation of optional arguments with default values
|
|
(Alain Frisch, review by Jacques Garrigue)
|
|
- #6389: ocamlopt -opaque option for incremental native compilation
|
|
(Pierre Chambart, Gabriel Scherer)
|
|
|
|
Toplevel interactive system:
|
|
- #5377: New "#show_*" directives
|
|
(ygrek, Jacques Garrigue and Alain Frisch)
|
|
|
|
Runtime system:
|
|
- New configure option "-no-naked-pointers" to improve performance by
|
|
avoiding page table tests during block darkening and the marking phase
|
|
of the major GC. In this mode, all out-of-heap pointers must point at
|
|
things that look like OCaml values: in particular they must have a valid
|
|
header. The colour of said headers should be black.
|
|
(Mark Shinwell, reviews by Damien Doligez and Xavier Leroy)
|
|
- Fixed bug in native code version of [caml_raise_with_string] that could
|
|
potentially lead to heap corruption.
|
|
(Mark Shinwell)
|
|
* Blocks initialized by [CAMLlocal*] and [caml_alloc] are now filled with
|
|
[Val_unit] rather than zero.
|
|
(Mark Shinwell)
|
|
- Fixed a major performance problem on large heaps (~1GB) by making heap
|
|
increments proportional to heap size by default
|
|
(Damien Doligez)
|
|
- #4765: Structural equality treats exception specifically
|
|
(Alain Frisch)
|
|
- #5009: efficient comparison/indexing of exceptions
|
|
(Alain Frisch, request by Markus Mottl)
|
|
- #6075: avoid using unsafe C library functions (strcpy, strcat, sprintf)
|
|
(Xavier Leroy, reports from user 'jfc' and Anil Madhavapeddy)
|
|
- An ISO C99-compliant C compiler and standard library is now assumed.
|
|
(Plus special exceptions for MSVC.) In particular, emulation code for
|
|
64-bit integer arithmetic was removed, the C compiler must support a
|
|
64-bit integer type.
|
|
(Xavier Leroy)
|
|
|
|
Standard library:
|
|
* Add new modules Bytes and BytesLabels for mutable byte sequences.
|
|
(Damien Doligez)
|
|
- #4986: add List.sort_uniq and Set.of_list
|
|
(Alain Frisch)
|
|
- #5935: a faster version of "raise" which does not maintain the backtrace
|
|
(Alain Frisch)
|
|
- #6146: support "Unix.kill pid Sys.sigkill" under Windows
|
|
(Romain Bardou and Alain Frisch)
|
|
- #6148: speed improvement for Buffer
|
|
(John Whitington)
|
|
- #6180: efficient creation of uninitialized float arrays
|
|
(Alain Frisch, request by Markus Mottl)
|
|
- #6355: Improve documentation regarding finalisers and multithreading
|
|
(Daniel Bünzli, Mark Shinwell)
|
|
- Trigger warning 3 for all values marked as deprecated in the documentation.
|
|
(Damien Doligez)
|
|
|
|
OCamldoc:
|
|
- #6257: handle full doc comments for variant constructors and
|
|
record fields
|
|
(Maxence Guesdon, request by ygrek)
|
|
- #6274: allow doc comments on object types
|
|
(Thomas Refis)
|
|
- #6310: fix ocamldoc's subscript/superscript CSS font size
|
|
(Anil Madhavapeddy)
|
|
- #6425: fix generation of man pages
|
|
(Maxence Guesdon, report by Anil Madhavapeddy)
|
|
|
|
Bug fixes:
|
|
- #2719: wrong scheduling of bound checks within a
|
|
try...with Invalid_argument -> _ ... (Xavier Leroy)
|
|
- #4719: Sys.executable_name wrong if executable name contains dots (Windows)
|
|
(Alain Frisch, report by Bart Jacobs)
|
|
- #5406 ocamlbuild: "tag 'package' does not expect a parameter"
|
|
(Gabriel Scherer)
|
|
- #5598, #6165: Alterations to handling of \013 in source files
|
|
breaking other tools
|
|
(David Allsopp and Damien Doligez)
|
|
- #5820: Fix camlp4 lexer roll back problem
|
|
(Hongbo Zhang)
|
|
- #5946: CAMLprim taking (void) as argument
|
|
(Benoît Vaugon)
|
|
- #6038: on x86-32, enforce 16-byte stack alignment for compatibility
|
|
with recent GCC and Clang. Win32/MSVC keeps 4-byte stack alignment.
|
|
(Xavier Leroy)
|
|
- #6062: Fix a 4.01 camlp4 DELETE_RULE regression caused by commit 13047
|
|
(Hongbo Zhang, report by Christophe Troestler)
|
|
- #6173: Typing error message is worse than before
|
|
(Jacques Garrigue and John Whitington)
|
|
- #6174: OCaml compiler loops on an example using GADTs (-rectypes case)
|
|
(Jacques Garrigue and Grégoire Henry, report by Chantal Keller)
|
|
- #6175: open! was not supported by camlp4
|
|
(Hongbo Zhang)
|
|
- #6184: ocamlbuild: `ocamlfind ocamldep` does not support -predicate
|
|
(Kate Deplaix)
|
|
- #6194: Incorrect unused warning with first-class modules in patterns
|
|
(Jacques Garrigue, report by Markus Mottl and Leo White)
|
|
- #6211: in toplevel interactive use, bad interaction between uncaught
|
|
exceptions and multiple bindings of the form "let x = a let y = b;;".
|
|
(Xavier Leroy)
|
|
- #6216: inlining of GADT matches generates invalid assembly
|
|
(Xavier Leroy and Alain Frisch, report by Mark Shinwell)
|
|
- #6232: Don't use [mktemp] on platforms where [mkstemp] is available
|
|
(Stéphane Glondu, Mark Shinwell)
|
|
- #6233: out-of-bounds exceptions lose their locations on ARM, PowerPC
|
|
(Jacques-Henri Jourdan and Xavier Leroy,
|
|
report and testing by Stéphane Glondu)
|
|
- #6235: Issue with type information flowing through a variant pattern
|
|
(Jacques Garrigue, report by Hongbo Zhang)
|
|
- #6239: sometimes wrong stack alignment when raising exceptions
|
|
in -g mode with backtraces active
|
|
(Xavier Leroy, report by Yaron Minsky)
|
|
- #6240: Fail to expand module type abbreviation during substyping
|
|
(Jacques Garrigue, report by Leo White)
|
|
- #6241: Assumed inequality between paths involving functor arguments
|
|
(Jacques Garrigue, report by Jeremy Yallop)
|
|
- #6243: Make "ocamlopt -g" more resistant to ill-formed locations
|
|
(Xavier Leroy, report by Pierre-Marie Pédrot)
|
|
- #6262: equality of first-class modules take module aliases into account
|
|
(Alain Frisch and Leo White)
|
|
- #6268: -DMODEL_$(MODEL) not passed when building asmrun/arm.p.o
|
|
(Peter Michael Green)
|
|
- #6273: fix Sys.file_exists on large files (Win32)
|
|
(Christoph Bauer)
|
|
- #6275: Soundness bug related to type constraints
|
|
(Jacques Garrigue, report by Leo White)
|
|
- #6293: Assert_failure with invalid package type
|
|
(Jacques Garrigue, report by Elnatan Reisner)
|
|
- #6300: ocamlbuild -use-ocamlfind conflicts with -ocamlc
|
|
(Gabriel Scherer)
|
|
- #6302: bytecode debug information re-read from filesystem every time
|
|
(Jacques-Henri Jourdan)
|
|
- #6307: Behavior of 'module type of' w.r.t. module aliases
|
|
(Jacques Garrigue, report by Alain Frisch)
|
|
- #6332: Unix.open_process fails to pass empty arguments under Windows
|
|
(Damien Doligez, report Virgile Prevosto)
|
|
- #6346: Build failure with latest version of xcode on OSX
|
|
(Jérémie Dimino)
|
|
- #6348: Unification failure for GADT when original definition is hidden
|
|
(Leo White and Jacques Garrigue, report by Jeremy Yallop)
|
|
- #6352: Automatic removal of optional arguments and sequencing
|
|
(Jacques Garrigue and Alain Frisch)
|
|
- #6361: Hashtbl.hash not terminating on some lazy values w/ recursive types
|
|
(Xavier Leroy, report by Leo White)
|
|
- #6383: Exception Not_found when using object type in absent module
|
|
(Jacques Garrigue, report by Sébastien Briais)
|
|
- #6384: Uncaught Not_found exception with a hidden .cmi file
|
|
(Leo White)
|
|
- #6385: wrong allocation of large closures by the bytecode interpreter
|
|
(Xavier Leroy, report by Stephen Dolan)
|
|
- #6394: Assertion failed in Typecore.expand_path
|
|
(Alain Frisch and Jacques Garrigue)
|
|
- #6405: unsound interaction of -rectypes and GADTs
|
|
(Jacques Garrigue, report by Gabriel Scherer and Benoît Vaugon)
|
|
- #6408: Optional arguments given as ~?arg instead of ?arg in message
|
|
(Michael O'Connor)
|
|
- #6411: missing libgcc_s_sjlj-1.dll in mingw (add -static-libgcc)
|
|
(Jun Furuse and Alain Frisch, Jonathan Protzenko and Adrien Nader)
|
|
- #6436: Typos in @deprecated text in stdlib/arrayLabels.mli
|
|
(John Whitington)
|
|
- #6439: Don't use the deprecated [getpagesize] function
|
|
(John Whitington, Mark Shinwell)
|
|
- #6441: undetected tail-call in some mutually-recursive functions
|
|
(many arguments, and mutual block mixes functions and non-functions)
|
|
(Stefan Holdermans, review by Xavier Leroy)
|
|
- #6443: ocaml segfault when List.fold_left is traced then executed
|
|
(Jacques Garrigue, report by user 'Reventlov')
|
|
- #6451: some bugs in untypeast.ml
|
|
(Jun Furuse, review by Alain Frisch)
|
|
- #6460: runtime assertion failure with large [| e1;...eN |]
|
|
float array expressions
|
|
(Leo White)
|
|
- #6463: -dtypedtree fails on class fields
|
|
(Leo White)
|
|
- #6469: invalid -dsource printing of "external _pipe = ...", "Pervasives.(!)"
|
|
(Gabriel Scherer and Damien Doligez, user 'ngunn')
|
|
- #6482: ocamlbuild fails when _tags file in unhygienic directory
|
|
(Gabriel Scherer)
|
|
- #6502: ocamlbuild spurious warning on "use_menhir" tag
|
|
(Xavier Leroy)
|
|
- #6505: Missed Type-error leads to a segfault upon record access
|
|
(Jacques Garrigue, Jeremy Yallop, report by Christoph Höger)
|
|
- #6507: crash on AArch64 resulting from incorrect setting of
|
|
[caml_bottom_of_stack]. (Richard Jones, Mark Shinwell)
|
|
- #6509: add -linkall flag to ocamlcommon.cma
|
|
(Frédéric Bour)
|
|
- #6513: Fatal error Ctype.Unify(_) in functor type
|
|
- #6523: failure upon character bigarray access, and unnecessary change
|
|
in comparison ordering (Jeremy Yallop, Mark Shinwell)
|
|
- bound-checking bug in caml_string_{get,set}{16,32,64}
|
|
(Pierre Chambart and Gabriel Scherer, report by Nicolas Trangez)
|
|
- sometimes wrong stack alignment at out-of-bounds array access
|
|
(Gabriel Scherer and Xavier Leroy, report by Pierre Chambart)
|
|
|
|
Features wishes:
|
|
- #4243: make the Makefiles parallelizable
|
|
(Grégoire Henry and Damien Doligez)
|
|
- #4323: have "of_string" in Num and Big_int work with binary and
|
|
hex representations
|
|
(Zoe Paraskevopoulou, review by Gabriel Scherer)
|
|
- #4771: Clarify documentation of Dynlink.allow_only
|
|
(Damien Doligez, report by David Allsopp)
|
|
- #4855: 'camlp4 -I +dir' accepted, dir is relative to 'camlp4 -where'
|
|
(Jun Furuse and Hongbo Zhang, report by Dmitry Grebeniuk)
|
|
- #5201: ocamlbuild: add --norc to the bash invocation to help performances
|
|
(Daniel Weil)
|
|
- #5650: Camlp4FoldGenerator doesn't handle well "abstract" types
|
|
(Hongbo Zhang)
|
|
- #5808: allow simple patterns, not just identifiers, in "let p : t = ..."
|
|
(Alain Frisch)
|
|
- #5851: warn when -r is disabled because no _tags file is present
|
|
(Gabriel Scherer)
|
|
- #5899: a programmer-friendly access to backtrace information
|
|
(Jacques-Henri Jourdan and Gabriel Scherer)
|
|
- #6000 comment 9644: add a warning for non-principal coercions to format
|
|
(Jacques Garrigue, report by Damien Doligez)
|
|
- #6054: add support for M.[ foo ], M.[| foo |] etc.
|
|
(Kaustuv Chaudhuri)
|
|
- #6064: GADT representation for Bigarray.kind + CAML_BA_CHAR runtime kind
|
|
(Jeremy Yallop, review by Gabriel Scherer)
|
|
- #6071: Add a -noinit option to the toplevel
|
|
(David Sheets)
|
|
- #6087: ocamlbuild, improve _tags parsing of escaped newlines
|
|
(Gabriel Scherer, request by Daniel Bünzli)
|
|
- #6109: Typos in ocamlbuild error messages
|
|
(Gabriel Kerneis)
|
|
- #6116: more efficient implementation of Digest.to_hex
|
|
(ygrek)
|
|
- #6142: add cmt file support to ocamlobjinfo
|
|
(Anil Madhavapeddy)
|
|
- #6166: document -ocamldoc option of ocamlbuild
|
|
(Xavier Clerc)
|
|
- #6182: better message for virtual objects and class types
|
|
(Leo White, Stephen Dolan)
|
|
- #6183: enhanced documentation for 'Unix.shutdown_connection'
|
|
(Anil Madhavapeddy, report by Jun Furuse)
|
|
- #6187: ocamlbuild: warn when using -plugin-tag(s) without myocamlbuild.ml
|
|
(Kate Deplaix)
|
|
- #6246: allow wildcard _ as for-loop index
|
|
(Alain Frisch, request by ygrek)
|
|
- #6267: more information printed by "bt" command of ocamldebug
|
|
(Josh Watzman)
|
|
- #6270: remove need for -I directives to ocamldebug in common case
|
|
(Josh Watzman, review by Xavier Clerc and Alain Frisch)
|
|
- #6311: Improve signature mismatch error messages
|
|
(Alain Frisch, suggestion by Daniel Bünzli)
|
|
- #6358: obey DESTDIR in install targets
|
|
(Gabriel Scherer, request by François Berenger)
|
|
- #6388, #6424: more parsetree correctness checks for -ppx users
|
|
(Alain Frisch, request by whitequark and Jun Furuse)
|
|
- #6406: Expose OCaml version in C headers
|
|
(whitequark and Romain Calascibetta)
|
|
- #6446: improve "unused declaration" warnings wrt. name shadowing
|
|
(Alain Frisch)
|
|
- #6495: ocamlbuild tags 'safe_string', 'unsafe_string'
|
|
(Anil Madhavapeddy)
|
|
- #6497: pass context information to -ppx preprocessors
|
|
(whitequark, Alain Frisch)
|
|
- ocamllex: user-definable refill action
|
|
(Frédéric Bour, review by Gabriel Scherer and Luc Maranget)
|
|
- shorten syntax for functor signatures: "functor (M1:S1) (M2:S2) .. -> .."
|
|
(Thomas Gazagnaire and Jeremy Yallop, review by Gabriel Scherer)
|
|
- make ocamldebug -I auto-detection work with ocamlbuild
|
|
(Josh Watzman)
|
|
|
|
OCaml 4.01.0 (12 Sep 2013):
|
|
---------------------------
|
|
|
|
(Changes that can break existing programs are marked with a "*")
|
|
|
|
Other libraries:
|
|
- Labltk: updated to Tcl/Tk 8.6.
|
|
|
|
Type system:
|
|
- #5759: use well-disciplined type information propagation to
|
|
disambiguate label and constructor names
|
|
(Jacques Garrigue, Alain Frisch and Leo White)
|
|
* Propagate type information towards pattern-matching, even in the presence of
|
|
polymorphic variants (discarding only information about possibly-present
|
|
constructors). As a result, matching against absent constructors is no longer
|
|
allowed for exact and fixed polymorphic variant types.
|
|
(Jacques Garrigue)
|
|
* #6035: Reject multiple declarations of the same method or instance variable
|
|
in an object
|
|
(Alain Frisch)
|
|
|
|
Compilers:
|
|
- #5861: raise an error when multiple private keywords are used in type
|
|
declarations
|
|
(Hongbo Zhang)
|
|
- #5634: parsetree rewriter (-ppx flag)
|
|
(Alain Frisch)
|
|
- ocamldep now supports -absname
|
|
(Alain Frisch)
|
|
- #5768: On "unbound identifier" errors, use spell-checking to suggest names
|
|
present in the environment
|
|
(Gabriel Scherer)
|
|
- ocamlc has a new option -dsource to visualize the parsetree
|
|
(Alain Frisch, Hongbo Zhang)
|
|
- tools/eqparsetree compares two parsetree ignoring location
|
|
(Hongbo Zhang)
|
|
- ocamlopt now uses clang as assembler on OS X if available, which enables
|
|
CFI support for OS X.
|
|
(Benedikt Meurer)
|
|
- Added a new -short-paths option, which attempts to use the shortest
|
|
representation for type constructors inside types, taking open modules
|
|
into account. This can make types much more readable if your code
|
|
uses lots of functors.
|
|
(Jacques Garrigue)
|
|
- #5986: added flag -compat-32 to ocamlc, ensuring that the generated
|
|
bytecode executable can be loaded on 32-bit hosts.
|
|
(Xavier Leroy)
|
|
- #5980: warning on open statements which shadow an existing
|
|
identifier (if it is actually used in the scope of the open); new
|
|
open! syntax to silence it locally
|
|
(Alain Frisch, thanks to a report of Daniel Bünzli)
|
|
* warning 3 is extended to warn about other deprecated features:
|
|
- ISO-latin1 characters in identifiers
|
|
- uses of the (&) and (or) operators instead of (&&) and (||)
|
|
(Damien Doligez)
|
|
- Experimental OCAMLPARAM for ocamlc and ocamlopt
|
|
(Fabrice Le Fessant)
|
|
- #5571: incorrect ordinal number in error message
|
|
(Alain Frisch, report by John Carr)
|
|
- #6073: add signature to Tstr_include
|
|
(patch by Leo White)
|
|
|
|
Standard library:
|
|
- #5899: expose a way to inspect the current call stack,
|
|
Printexc.get_callstack
|
|
(Gabriel Scherer, Jacques-Henri Jourdan, Alain Frisch)
|
|
- #5986: new flag Marshal.Compat_32 for the serialization functions
|
|
(Marshal.to_*), forcing the output to be readable on 32-bit hosts.
|
|
(Xavier Leroy)
|
|
- infix application operators |> and @@ in Pervasives
|
|
(Fabrice Le Fessant)
|
|
- #6176: new Format.asprintf function with a %a formatter
|
|
compatible with Format.fprintf (unlike Format.sprintf)
|
|
(Pierre Weis)
|
|
|
|
Other libraries:
|
|
- #5568: add O_CLOEXEC flag to Unix.openfile, so that the returned
|
|
file descriptor is created in close-on-exec mode
|
|
(Xavier Leroy)
|
|
|
|
Runtime system:
|
|
* #6019: more efficient implementation of caml_modify() and caml_initialize().
|
|
The new implementations are less lenient than the old ones: now,
|
|
the destination pointer of caml_modify() must point within the minor or
|
|
major heaps, and the destination pointer of caml_initialize() must
|
|
point within the major heap.
|
|
(Xavier Leroy, from an experiment by Brian Nigito, with feedback
|
|
from Yaron Minsky and Gerd Stolpmann)
|
|
|
|
Internals:
|
|
- Moved debugger/envaux.ml to typing/envaux.ml to publish env_of_only_summary
|
|
as part of compilerlibs, to be used on bin-annot files.
|
|
(Fabrice Le Fessant)
|
|
- The test suite can now be run without installing OCaml first.
|
|
(Damien Doligez)
|
|
|
|
Bug fixes:
|
|
- #3236: Document the fact that queues are not thread-safe
|
|
(Damien Doligez)
|
|
- #3468: (part 1) Sys_error documentation
|
|
(Damien Doligez)
|
|
- #3679: Warning display problems
|
|
(Fabrice Le Fessant)
|
|
- #3963: Graphics.wait_next_event in Win32 hangs if window closed
|
|
(Damien Doligez)
|
|
- #4079: Queue.copy is now tail-recursive
|
|
(patch by Christophe Papazian)
|
|
- #4138: Documentation for Unix.mkdir
|
|
(Damien Doligez)
|
|
- #4469: emacs mode: caml-set-compile-command is annoying with ocamlbuild
|
|
(Daniel Bünzli)
|
|
- #4485: Graphics: Keyboard events incorrectly delivered in native code
|
|
(Damien Doligez, report by Sharvil Nanavati)
|
|
- #4502: ocamlbuild now reliably excludes the build-dir from hygiene check
|
|
(Gabriel Scherer, report by Romain Bardou)
|
|
- #4762: ?? is not used at all, but registered as a lexer token
|
|
(Alain Frisch)
|
|
- #4788: wrong error message when executable file is not found for backtrace
|
|
(Damien Doligez, report by Claudio Sacerdoti Coen)
|
|
- #4812: otherlibs/unix: add extern int code_of_unix_error (value error);
|
|
(Goswin von Berdelow)
|
|
- #4887: input_char after close_in crashes ocaml (msvc runtime)
|
|
(Alain Frisch and Christoph Bauer, report by ygrek)
|
|
- #4994: ocaml-mode doesn't work with xemacs21
|
|
(Damien Doligez, report by Stéphane Glondu)
|
|
- #5098: creating module values may lead to memory leaks
|
|
(Alain Frisch, report by Milan Stanojević)
|
|
- #5102: ocamlbuild fails when using an unbound variable in rule dependency
|
|
(Xavier Clerc, report by Daniel Bünzli)
|
|
* #5119: camlp4 now raises a specific exception when 'DELETE_RULE' fails,
|
|
rather than raising 'Not_found'
|
|
(ygrek)
|
|
- #5121: %( %) in Format module seems to be broken
|
|
(Pierre Weis, first patch by Valentin Gatien-Baron, report by Khoo Yit Phang)
|
|
- #5178: document in INSTALL how to build a 32-bit version under Linux x86-64
|
|
(Benjamin Monate)
|
|
- #5212: Improve ocamlbuild error messages of _tags parser
|
|
(ygrek)
|
|
- #5240: register exception printers for Unix.Unix_error and Dynlink.Error
|
|
(Jérémie Dimino)
|
|
- #5300: ocamlbuild: verbose parameter should implicitly set classic display
|
|
(Xavier Clerc, report by Robert Jakob)
|
|
- #5327: (Windows) Unix.select blocks if same socket listed in first and
|
|
third arguments
|
|
(David Allsopp, displaying impressive MSDN skills)
|
|
- #5343: ocaml -rectypes is unsound wrt module subtyping (was still unsound)
|
|
(Jacques Garrigue)
|
|
- #5350: missing return code checks in the runtime system
|
|
(Xavier Leroy)
|
|
- #5468: ocamlbuild should preserve order of parametric tags
|
|
(Wojciech Meyer, report by Dario Texeira)
|
|
- #5551: Avoid repeated lookups for missing cmi files
|
|
(Alain Frisch)
|
|
- #5552: unrecognized gcc option -no-cpp-precomp
|
|
(Damien Doligez, report by Markus Mottl)
|
|
* #5580: missed opportunities for constant propagation
|
|
(Xavier Leroy and John Carr)
|
|
- #5611: avoid clashes between .cmo files and output files during linking
|
|
(Wojciech Meyer)
|
|
- #5662: typo in md5.c
|
|
(Olivier Andrieu)
|
|
- #5673: type equality in a polymorphic field
|
|
(Jacques Garrigue, report by Jean-Louis Giavitto)
|
|
- #5674: Methods call are 2 times slower with 4.00 than with 3.12
|
|
(Jacques Garrigue, Gabriel Scherer, report by Jean-Louis Giavitto)
|
|
- #5694: Exception raised by type checker
|
|
(Jacques Garrigue, report by Markus Mottl)
|
|
- #5695: remove warnings on sparc code emitter
|
|
(Fabrice Le Fessant)
|
|
- #5697: better location for warnings on statement expressions
|
|
(Dan Bensen)
|
|
- #5698: remove hardcoded limit of 200000 labels in emitaux.ml
|
|
(Fabrice Le Fessant, report by Marcin Sawicki)
|
|
- #5702: bytecomp/bytelibrarian lib_sharedobjs was defined but never used
|
|
(Hongbo Zhang, Fabrice Le Fessant)
|
|
- #5708: catch Failure"int_of_string" in ocamldebug
|
|
(Fabrice Le Fessant, report by user 'schommer')
|
|
- #5712: (9) new option -bin-annot is not documented
|
|
(Damien Doligez, report by Hendrik Tews)
|
|
- #5731: instruction scheduling forgot to account for destroyed registers
|
|
(Xavier Leroy, Benedikt Meurer, reported by Jeffrey Scofield)
|
|
- #5734: improved Win32 implementation of Unix.gettimeofday
|
|
(David Allsopp)
|
|
- #5735: %apply and %revapply not first class citizens
|
|
(Fabrice Le Fessant, reported by Jun Furuse)
|
|
- #5738: first class module patterns not handled by ocamldep
|
|
(Fabrice Le Fessant, Jacques Garrigue, reported by Hongbo Zhang)
|
|
- #5739: Printf.printf "%F" (-.nan) returns -nan
|
|
(Xavier Leroy, David Allsopp, reported by Samuel Mimram)
|
|
- #5741: make pprintast.ml in compiler_libs
|
|
(Alain Frisch, Hongbo Zhang)
|
|
- #5747: 'unused open' warning not given when compiling with -annot
|
|
(Alain Frisch, reported by Valentin Gatien-Baron)
|
|
- #5752: missing dependencies at byte-code link with mlpack
|
|
(Wojciech Meyer, Nicholas Lucaroni)
|
|
- #5763: ocamlbuild does not give correct flags when running menhir
|
|
(Gabriel Scherer, reported by Philippe Veber)
|
|
- #5765: ocamllex doesn't preserve line directives
|
|
(Damien Doligez, reported by Martin Jambon)
|
|
- #5770: Syntax error messages involving unclosed parens are sometimes
|
|
incorrect
|
|
(Michel Mauny)
|
|
- #5772: problem with marshaling of mutually-recursive functions
|
|
(Jacques-Henri Jourdan, reported by Cédric Pasteur)
|
|
- #5775: several bug fixes for tools/pprintast.ml
|
|
(Hongbo Zhang)
|
|
- #5784: -dclambda option is ignored
|
|
(Pierre Chambart)
|
|
- #5785: misbehaviour with abstracted structural type used as GADT index
|
|
(Jacques Garrigue, report by Jeremy Yallop)
|
|
- #5787: Bad behavior of 'Unused ...' warnings in the toplevel
|
|
(Alain Frisch)
|
|
- #5793: integer marshalling is inconsistent between architectures
|
|
(Xavier Clerc, report by Pierre-Marie Pédrot)
|
|
- #5798: add ARM VFPv2 support for Raspbian (ocamlopt)
|
|
(Jeffrey Scofield and Anil Madhavapeddy, patch review by Benedikt Meurer)
|
|
- #5802: Avoiding "let" as a value name
|
|
(Jacques Garrigue, report by Tiphaine Turpin)
|
|
- #5805: Assert failure with warning 34 on pre-processed file
|
|
(Alain Frisch, report by Tiphaine Turpin)
|
|
- #5806: ensure that backtrace tests are always run (testsuite)
|
|
(Xavier Clerc, report by user 'michi')
|
|
- #5809: Generating .cmt files takes a long time, in case of type error
|
|
(Alain Frisch)
|
|
- #5810: error in switch printing when using -dclambda
|
|
(Pierre Chambart)
|
|
- #5811: Untypeast produces singleton tuples for constructor patterns
|
|
with only one argument
|
|
(Tiphaine Turpin)
|
|
- #5813: GC not called when unmarshaling repeatedly in a tight loop (ocamlopt)
|
|
(Xavier Leroy, report by David Waern)
|
|
- #5814: read_cmt -annot does not report internal references
|
|
(Alain Frisch)
|
|
- #5815: Multiple exceptions in signatures gives an error
|
|
(Leo White)
|
|
- #5816: read_cmt -annot does not work for partial .cmt files
|
|
(Alain Frisch)
|
|
- #5819: segfault when using [with] on large recursive record (ocamlopt)
|
|
(Xavier Leroy, Damien Doligez)
|
|
- #5821: Wrong record field is reported as duplicate
|
|
(Alain Frisch, report by Martin Jambon)
|
|
- #5824: Generate more efficient code for immediate right shifts.
|
|
(Pierre Chambart, review by Xavier Leroy)
|
|
- #5825: Add a toplevel primitive to use source file wrapped with the
|
|
corresponding module
|
|
(Grégoire Henry, Wojciech Meyer, caml-list discussion)
|
|
- #5833: README.win32 can leave the wrong flexlink in the path
|
|
(Damien Doligez, report by William Smith)
|
|
- #5835: nonoptional labeled arguments can be passed with '?'
|
|
(Jacques Garrigue, report by Elnatan Reisner)
|
|
- #5840: improved documentation for 'Unix.lseek'
|
|
(Xavier Clerc, report by Matej Košík)
|
|
- #5848: Assertion failure in type checker
|
|
(Jacques Garrigue, Alain Frisch, report by David Waern)
|
|
- #5858: Assert failure during typing of class
|
|
(Jacques Garrigue, report by Julien Signoles)
|
|
- #5865: assert failure when reporting undefined field label
|
|
(Jacques Garrigue, report by Anil Madhavapeddy)
|
|
- #5872: Performance: Buffer.add_char is not inlined
|
|
(Gerd Stolpmann, Damien Doligez)
|
|
- #5876: Uncaught exception with a typing error
|
|
(Alain Frisch, Gabriel Scherer, report by Julien Moutinho)
|
|
- #5877: multiple "open" can become expensive in memory
|
|
(Fabrice Le Fessant and Alain Frisch)
|
|
- #5880: 'Genlex.make_lexer' documentation mentions the wrong exception
|
|
(Xavier Clerc, report by Virgile Prevosto)
|
|
- #5885: Incorrect rule for compiling C stubs when shared libraries are not
|
|
supported.
|
|
(Jérôme Vouillon)
|
|
- #5891: ocamlbuild: support rectypes tag for mlpack
|
|
(Khoo Yit Phang)
|
|
- #5892: GADT exhaustiveness check is broken
|
|
(Jacques Garrigue and Leo White)
|
|
- #5906: GADT exhaustiveness check is still broken
|
|
(Jacques Garrigue, report by Sébastien Briais)
|
|
- #5907: Undetected cycle during typecheck causes exceptions
|
|
(Jacques Garrigue, report by Pascal Zimmer)
|
|
- #5910: Fix code generation bug for "mod 1" on ARM.
|
|
(Benedikt Meurer, report by user 'jteg68')
|
|
- #5911: Signature substitutions fail in submodules
|
|
(Jacques Garrigue, report by Markus Mottl)
|
|
- #5912: add configure option -no-cfi (for OSX 10.6.x with XCode 4.0.2)
|
|
(Damien Doligez against XCode versions, report by Thomas Gazagnaire)
|
|
- #5914: Functor breaks with an equivalent argument signature
|
|
(Jacques Garrigue, report by Markus Mottl and Grégoire Henry)
|
|
- #5920, #5957: linking failure for big bytecodes on 32bit architectures
|
|
(Benoît Vaugon and Chet Murthy, report by Jun Furuse and Sebastien Mondet)
|
|
- #5928: Missing space between words in manual page for ocamlmktop
|
|
(Damien Doligez, report by Matej Košík)
|
|
- #5930: ocamldep leaks temporary preprocessing files
|
|
(Gabriel Scherer, report by Valentin Gatien-Baron)
|
|
- #5933: Linking is slow when there are functions with large arities
|
|
(Valentin Gatien-Baron, review by Gabriel Scherer)
|
|
- #5934: integer shift by negative amount (in otherlibs/num)
|
|
(Xavier Leroy, report by John Regehr)
|
|
- #5944: Bad typing performances of big variant type declaration
|
|
(Benoît Vaugon)
|
|
- #5945: Mix-up of Minor_heap_min and Minor_heap_max units
|
|
(Benoît Vaugon)
|
|
- #5948: GADT with polymorphic variants bug
|
|
(Jacques Garrigue, report by Leo White)
|
|
- #5953: Unix.system does not handle EINTR
|
|
(Jérémie Dimino)
|
|
- #5965: disallow auto-reference to a recursive module in its definition
|
|
(Alain Frisch, report by Arthur Windler via Gabriel Scherer)
|
|
- #5973: Format module incorrectly parses format string
|
|
(Pierre Weis, report by Frédéric Bour)
|
|
- #5974: better documentation for Str.regexp
|
|
(Damien Doligez, report by william)
|
|
- #5976: crash after recovering from two stack overflows (ocamlopt on MacOS X)
|
|
(Xavier Leroy, report by Pierre Boutillier)
|
|
- #5977: Build failure on raspberry pi: "input_value: integer too large"
|
|
(Alain Frisch, report by Sylvain Le Gall)
|
|
- #5981: Incompatibility check assumes abstracted types are injective
|
|
(Jacques Garrigue, report by Jeremy Yallop)
|
|
- #5982: caml_leave_blocking section and errno corruption
|
|
(Jérémie Dimino)
|
|
- #5985: Unexpected interaction between variance and GADTs
|
|
(Jacques Garrigue, Jeremy Yallop and Leo White and Gabriel Scherer)
|
|
- #5988: missing from the documentation: -impl is a valid flag for ocamlopt
|
|
(Damien Doligez, report by Vincent Bernardoff)
|
|
- #5989: Assumed inequalities involving private rows
|
|
(Jacques Garrigue, report by Jeremy Yallop)
|
|
- #5992: Crash when pattern-matching lazy values modifies the scrutinee
|
|
(Luc Maranget, Leo White)
|
|
- #5993: Variance of private type abbreviations not checked for modules
|
|
(Jacques Garrigue)
|
|
- #5997: Non-compatibility assumed for concrete types with same constructor
|
|
(Jacques Garrigue, report by Gabriel Scherer)
|
|
- #6004: Type information does not flow to "inherit" parameters
|
|
(Jacques Garrigue, report by Alain Frisch)
|
|
- #6005: Type unsoundness with recursive modules
|
|
(Jacques Garrigue, report by Jérémie Dimino and Josh Berdine)
|
|
- #6010: Big_int.extract_big_int gives wrong results on negative arguments
|
|
(Xavier Leroy, report by Drake Wilson via Stéphane Glondu)
|
|
- #6024: Format syntax for printing @ is incompatible with 3.12.1
|
|
(Damien Doligez, report by Boris Yakobowski)
|
|
- #6001: Reduce the memory used by compiling Camlp4
|
|
(Hongbo Zhang and Gabriel Scherer, report by Henri Gouraud)
|
|
- #6031: Camomile problem with -with-frame-pointers
|
|
(Fabrice Le Fessant, report by Anil Madhavapeddy)
|
|
- #6032: better Random.self_init under Windows
|
|
(Alain Frisch, Xavier Leroy)
|
|
- #6033: Matching.inline_lazy_force needs eta-expansion (command-line flags)
|
|
(Pierre Chambart, Xavier Leroy and Luc Maranget,
|
|
regression report by Gabriel Scherer)
|
|
- #6046: testsuite picks up the wrong ocamlrun dlls
|
|
(Anil Madhavapeddy)
|
|
- #6056: Using 'match' prevents generalization of values
|
|
(Jacques Garrigue, report by Elnatan Reisner)
|
|
- #6058: 'ocamlbuild -use-ocamlfind -tag thread -package threads t.cma' fails
|
|
(Gabriel Scherer, report by Hezekiah M. Carty)
|
|
- #6069: ocamldoc: lexing: empty token
|
|
(Maxence Guesdon, Grégoire Henry, report by ygrek)
|
|
- #6072: configure does not handle FreeBSD current (i.e. 10) correctly
|
|
(Damien Doligez, report by Prashanth Mundkur)
|
|
- #6074: Wrong error message for failing Condition.broadcast
|
|
(Markus Mottl)
|
|
- #6084: Define caml_modify and caml_initialize as weak symbols to help
|
|
with Netmulticore
|
|
(Xavier Leroy, Gerd Stolpmann)
|
|
- #6090: Module constraint + private type seems broken in ocaml 4.01.0
|
|
(Jacques Garrigue, report by Kate Deplaix)
|
|
- #6109: Typos in ocamlbuild error messages
|
|
(Gabriel Kerneis)
|
|
- #6123: Assert failure when self escapes its class
|
|
(Jacques Garrigue, report by whitequark)
|
|
- #6158: Fatal error using GADTs
|
|
(Jacques Garrigue, report by Jeremy Yallop)
|
|
- #6163: Assert_failure using polymorphic variants in GADTs
|
|
(Jacques Garrigue, report by Leo White)
|
|
- #6164: segmentation fault on Num.power_num of 0/1
|
|
(Fabrice Le Fessant, report by Johannes Kanig)
|
|
- #6210: Camlp4 location error
|
|
(Hongbo Zhang, report by Jun Furuse)
|
|
|
|
Feature wishes:
|
|
- #5181: Merge common floating point constants in ocamlopt
|
|
(Benedikt Meurer)
|
|
- #5243: improve the ocamlbuild API documentation in signatures.mli
|
|
(Christophe Troestler)
|
|
- #5546: moving a function into an internal module slows down its use
|
|
(Alain Frisch, report by Fabrice Le Fessant)
|
|
- #5597: add instruction trace option 't' to OCAMLRUNPARAM
|
|
(Anil Madhavapeddy, Wojciech Meyer)
|
|
- #5676: IPv6 support under Windows
|
|
(Jérôme Vouillon, review by Jonathan Protzenko)
|
|
- #5721: configure -with-frame-pointers for Linux perf profiling
|
|
(Fabrice Le Fessant, test by Jérémie Dimino)
|
|
- #5722: toplevel: print full module path only for first record field
|
|
(Jacques Garrigue, report by ygrek)
|
|
- #5762: Add primitives for fast access to bigarray dimensions
|
|
(Pierre Chambart)
|
|
- #5769: Allow propagation of Sys.big_endian in native code
|
|
(Pierre Chambart, stealth commit by Fabrice Le Fessant)
|
|
- #5771: Add primitives for reading 2, 4, 8 bytes in strings and bigarrays
|
|
(Pierre Chambart)
|
|
- #5774: Add bswap primitives for amd64 and arm
|
|
(Pierre Chambart, test by Alain Frisch)
|
|
- #5795: Generate sqrtsd opcode instead of external call to sqrt on amd64
|
|
(Pierre Chambart)
|
|
- #5827: provide a dynamic command line parsing mechanism
|
|
(Hongbo Zhang)
|
|
- #5832: patch to improve "wrong file naming" error messages
|
|
(William Smith)
|
|
- #5864: Add a find operation to Set
|
|
(François Berenger)
|
|
- #5886: Small changes to compile for Android
|
|
(Jérôme Vouillon, review by Benedikt Meurer)
|
|
- #5902: -ppx based pre-processor executables accept arguments
|
|
(Alain Frisch, report by Wojciech Meyer)
|
|
- #5986: Protect against marshaling 64-bit integers in bytecode
|
|
(Xavier Leroy, report by Alain Frisch)
|
|
- #6049: support for OpenBSD/macppc platform
|
|
(Anil Madhavapeddy, review by Benedikt Meurer)
|
|
- #6059: add -output-obj rules for ocamlbuild
|
|
(Anil Madhavapeddy)
|
|
- #6060: ocamlbuild tags 'principal', 'strict_sequence' and 'short_paths'
|
|
(Anil Madhavapeddy)
|
|
- ocamlbuild tag 'no_alias_deps'
|
|
(Daniel Bünzli)
|
|
|
|
Tools:
|
|
- OCamlbuild now features a bin_annot tag to generate .cmt files.
|
|
(Jonathan Protzenko)
|
|
- OCamlbuild now features a strict_sequence tag to trigger the
|
|
strict-sequence option.
|
|
(Jonathan Protzenko)
|
|
- OCamlbuild now picks the non-core tools like ocamlfind and menhir from PATH
|
|
(Wojciech Meyer)
|
|
- #5884: Misc minor fixes and cleanup for emacs mode
|
|
(Stefan Monnier)
|
|
- #6030: Improve performance of -annot
|
|
(Guillaume Melquiond, Alain Frisch)
|
|
|
|
|
|
OCaml 4.00.1 (5 Oct 2012):
|
|
--------------------------
|
|
|
|
Bug fixes:
|
|
- #4019: better documentation of Str.matched_string
|
|
- #5111: ocamldoc, heading tags inside spans tags is illegal in html
|
|
- #5278: better error message when typing "make"
|
|
- #5468: ocamlbuild should preserve order of parametric tags
|
|
- #5563: harden Unix.select against file descriptors above FD_SETSIZE
|
|
- #5690: "ocamldoc ... -text README" raises exception
|
|
- #5700: crash with native-code stack backtraces under MacOS 10.8 x86-64
|
|
- #5707: AMD64 code generator: do not use r10 and r11 for parameter passing,
|
|
as these registers can be destroyed by the dynamic loader
|
|
- #5712: some documentation problems
|
|
- #5715: configuring with -no-shared-libs breaks under cygwin
|
|
- #5718: false positive on 'unused constructor' warning
|
|
- #5719: ocamlyacc generates code that is not warning 33-compliant
|
|
- #5725: ocamldoc output of preformatted code
|
|
- #5727: emacs caml-mode indents shebang line in toplevel scripts
|
|
- #5729: tools/untypeast.ml creates unary Pexp_tuple
|
|
- #5731: instruction scheduling forgot to account for destroyed registers
|
|
- #5735: %apply and %revapply not first class citizens
|
|
- #5738: first class module patterns not handled by ocamldep
|
|
- #5742: missing bound checks in Array.sub
|
|
- #5744: ocamldoc error on "val virtual"
|
|
- #5757: GC compaction bug (crash)
|
|
- #5758: Compiler bug when matching on floats
|
|
- #5761: Incorrect bigarray custom block size
|
|
|
|
|
|
OCaml 4.00.0 (26 Jul 2012):
|
|
---------------------------
|
|
|
|
(Changes that can break existing programs are marked with a "*")
|
|
|
|
- The official name of the language is now OCaml.
|
|
|
|
Language features:
|
|
- Added Generalized Algebraic Data Types (GADTs) to the language.
|
|
See chapter "Language extensions" of the reference manual for documentation.
|
|
- It is now possible to omit type annotations when packing and unpacking
|
|
first-class modules. The type-checker attempts to infer it from the context.
|
|
Using the -principal option guarantees forward compatibility.
|
|
- New (module M) and (module M : S) syntax in patterns, for immediate
|
|
unpacking of a first-class module.
|
|
|
|
Compilers:
|
|
- Revised simplification of let-alias (#5205, #5288)
|
|
- Better reporting of compiler version mismatch in .cmi files
|
|
* Warning 28 is now enabled by default.
|
|
- New option -absname to use absolute paths in error messages
|
|
- Optimize away compile-time beta-redexes, e.g. (fun x y -> e) a b.
|
|
- Added option -bin-annot to dump the AST with type annotations.
|
|
- Added lots of new warnings about unused variables, opens, fields,
|
|
constructors, etc.
|
|
* New meaning for warning 7: it is now triggered when a method is overridden
|
|
with the "method" keyword. Use "method!" to avoid the warning.
|
|
|
|
Native-code compiler:
|
|
- Optimized handling of partially-applied functions (#5287)
|
|
- Small improvements in code generated for array bounds checks (#5345,
|
|
#5360).
|
|
* New ARM backend (#5433):
|
|
. Supports both Linux/EABI (armel) and Linux/EABI+VFPv3 (armhf).
|
|
. Added support for the Thumb-2 instruction set with average code size
|
|
savings of 28%.
|
|
. Added support for position-independent code, natdynlink, profiling and
|
|
exception backtraces.
|
|
- Generation of CFI information, and filename/line number debugging (with -g)
|
|
annotations, enabling in particular precise stack backtraces with
|
|
the gdb debugger. Currently supported for x86 32-bits and 64-bits only.
|
|
(#5487)
|
|
- New tool: ocamloptp, the equivalent of ocamlcp for the native-code compiler.
|
|
|
|
OCamldoc:
|
|
- #5645: ocamldoc doesn't handle module/type substitution in signatures
|
|
- #5544: improve HTML output (less formatting in html code)
|
|
- #5522: allow referring to record fields and variant constructors
|
|
- fix #5419 (error message in french)
|
|
- fix #5535 (no cross ref to class after dump+load)
|
|
* Use first class modules for custom generators, to be able to
|
|
load various plugins incrementally adding features to the current
|
|
generator
|
|
* #5507: Use Location.t structures for locations.
|
|
- fix: do not keep code when not told to keep code.
|
|
|
|
Standard library:
|
|
- Added float functions "hypot" and "copysign" (#3806, #4752, #5246)
|
|
* Arg: options with empty doc strings are no longer included in the usage string
|
|
(#5437)
|
|
- Array: faster implementations of "blit", "copy", "sub", "append" and "concat"
|
|
(#2395, #2787, #4591)
|
|
* Hashtbl:
|
|
. Statistically-better generic hash function based on Murmur 3 (#5225)
|
|
. Fixed behavior of generic hash function w.r.t. -0.0 and NaN (#5222)
|
|
. Added optional "random" parameter to Hashtbl.create to randomize
|
|
collision patterns and improve security (#5572, CVE-2012-0839)
|
|
. Added "randomize" function and "R" parameter to OCAMLRUNPARAM
|
|
to turn randomization on by default (#5572, CVE-2012-0839)
|
|
. Added new functorial interface "MakeSeeded" to support randomization
|
|
with user-provided seeded hash functions.
|
|
. Install new header <caml/hash.h> for C code.
|
|
- Filename: on-demand (lazy) initialization of the PRNG used by "temp_file".
|
|
- Marshal: marshalling of function values (flag Marshal.Closures) now
|
|
also works for functions that come from dynamically-loaded modules (#5215)
|
|
- Random:
|
|
. More random initialization (Random.self_init()), using /dev/urandom
|
|
when available (e.g. Linux, FreeBSD, MacOS X, Solaris)
|
|
* Faster implementation of Random.float (changes the generated sequences)
|
|
- Format strings for formatted input/output revised to correct #5380
|
|
. Consistently treat %@ as a plain @ character
|
|
. Consistently treat %% as a plain % character
|
|
- Scanf: width and precision for floating point numbers are now handled
|
|
- Scanf: new function "unescaped" (#3888)
|
|
- Set and Map: more efficient implementation of "filter" and "partition"
|
|
- String: new function "map" (#3888)
|
|
|
|
Installation procedure:
|
|
- Compiler internals are now installed in `ocamlc -where`/compiler-libs.
|
|
The files available there include the .cmi interfaces for all compiler
|
|
modules, plus the following libraries:
|
|
ocamlcommon.cma/.cmxa modules common to ocamlc, ocamlopt, ocaml
|
|
ocamlbytecomp.cma/.cmxa modules for ocamlc and ocaml
|
|
ocamloptcomp.cma/.cmxa modules specific to ocamlopt
|
|
ocamltoplevel.cma modules specific to ocaml
|
|
(#8255, #4653, frequently-asked feature).
|
|
* Some .cmi for toplevel internals that used to be installed in
|
|
`ocamlc -where` are now to be found in `ocamlc -where`/compiler-libs.
|
|
Add "-I +compiler-libs" where needed.
|
|
* toplevellib.cma is no longer installed because subsumed by
|
|
ocamlcommon.cma ocamlbytecomp.cma ocamltoplevel.cma
|
|
- Added a configuration option (-with-debug-runtime) to compile and install
|
|
a debug version of the runtime system, and a compiler option
|
|
(-runtime-variant) to select the debug runtime.
|
|
|
|
Bug Fixes:
|
|
|
|
- #8109: functions of the Lazy module whose named started with 'lazy_' have
|
|
been deprecated, and new ones without the prefix added
|
|
- #3571: in Bigarrays, call msync() before unmapping to commit changes
|
|
- #4292: various documentation problems
|
|
- #4511, #4838: local modules remove polymorphism
|
|
* #4549: Filename.dirname is not handling multiple / on Unix
|
|
- #4688: (Windows) special floating-point values aren't converted to strings
|
|
correctly
|
|
- #4697: Unix.putenv leaks memory on failure
|
|
- #4705: camlp4 does not allow to define types with `True or `False
|
|
- #4746: wrong detection of stack overflows in native code under Linux
|
|
- #4869: rare collisions between assembly labels for code and data
|
|
- #4880: "assert" constructs now show up in the exception stack backtrace
|
|
- #4892: Array.set could raise "out of bounds" before evaluating 3rd arg
|
|
- #4937: camlp4 incorrectly handles optional arguments if 'option' is
|
|
redefined
|
|
- #5024: camlp4r now handles underscores in irrefutable pattern matching of
|
|
records
|
|
- #5064, #5485: try to ensure that 4K words of stack are available
|
|
before calling into C functions, raising a Stack_overflow exception
|
|
otherwise. This reduces (but does not eliminate) the risk of
|
|
segmentation faults due to stack overflow in C code
|
|
- #5073: wrong location for 'Unbound record field label' error
|
|
- #5084: sub-sub-module building fails for native code compilation
|
|
- #5120: fix the output function of Camlp4.Debug.formatter
|
|
- #5131: compilation of custom runtime with g++ generates lots of warnings
|
|
- #5137: caml-types-explore does not work
|
|
- #5159: better documentation of type Lexing.position
|
|
- #5171: Map.join does more comparisons than needed
|
|
- #5176: emacs mode: stack overflow in regexp matcher
|
|
- #5179: port OCaml to mingw-w64
|
|
- #5211: updated Genlex documentation to state that camlp4 is mandatory for
|
|
'parser' keyword and associated notation
|
|
- #5214: ocamlfind plugin invokes 'cut' utility
|
|
- #5218: use $(MAKE) instead of "make" in Makefiles
|
|
- #5224: confusing error message in non-regular type definition
|
|
- #5231: camlp4: fix parsing of <:str_item< type t = $x$ >>
|
|
- #5233: finaliser on weak array gives dangling pointers (crash)
|
|
- #5238, #5277: Sys_error when getting error location
|
|
- #5261, #5497: Ocaml source-code examples are not "copy-paste-able"
|
|
* #5279: executable name is not initialized properly in caml_startup_code
|
|
- #5290: added hash functions for channels, nats, mutexes, conditions
|
|
- #5291: undetected loop in class initialization
|
|
- #5295: OS threads: problem with caml_c_thread_unregister()
|
|
- #5301: camlp4r and exception equal to another one with parameters
|
|
- #5305: prevent ocamlbuild from complaining about links to _build/
|
|
- #5306: comparing to Thread.self() raises exception at runtime
|
|
- #5309: Queue.add is not thread/signal safe
|
|
- #5310: Ratio.create_ratio/create_normalized_ratio have misleading names
|
|
- #5311: better message for warning 23
|
|
* #5312: command-line arguments @reponsefile auto-expansion feature
|
|
removed from the Windows OCaml runtime, to avoid conflicts with "-w @..."
|
|
- #5313: ocamlopt -g misses optimizations
|
|
- #5214: ocamlfind plugin invokes 'cut' utility
|
|
- #5316: objinfo now shows ccopts/ccobjs/force_link when applicable
|
|
- #5318: segfault on stack overflow when reading marshaled data
|
|
- #5319: %r11 clobbered by Lswitch in Windows AMD64 native-code compilation
|
|
- #5322: type abbreviations expanding to a universal type variable
|
|
- #5328: under Windows, Unix.select leaves sockets in non-blocking mode
|
|
- #5330: thread tag with '.top' and '.inferred.mli' targets
|
|
- #5331: ocamlmktop is not always a shell script
|
|
- #5335: Unix.environment segfaults after a call to clearenv
|
|
- #5338: sanitize.sh has windows style end-of-lines (mingw)
|
|
- #5344: some predefined exceptions need special printing
|
|
- #5349: Hashtbl.replace uses new key instead of reusing old key
|
|
- #5356: ocamlbuild handling of 'predicates' for ocamlfind
|
|
- #5364: wrong compilation of "((val m : SIG1) : SIG2)"
|
|
- #5370: ocamldep omits filename in syntax error message
|
|
- #5374: camlp4 creates wrong location for type definitions
|
|
- #5380: strange sscanf input segfault
|
|
- #5382: EOPNOTSUPP and ENOTSUPP different on exotic platforms
|
|
- #5383: build failure in Win32/MSVC
|
|
- #5387: camlp4: str_item and other syntactic elements with Nils are
|
|
not very usable
|
|
- #5389: compaction sometimes leaves a very large heap
|
|
- #5393: fails to build from source on GNU/kFreeBSD because of -R link option
|
|
- #5394: documentation for -dtypes is missing in manpage
|
|
- #5397: Filename.temp_dir_name should be mutable
|
|
- #5410: fix printing of class application with Camlp4
|
|
- #5416: (Windows) Unix.(set|clear)_close_on_exec now preserves blocking mode
|
|
- #5435: ocamlbuild does not find .opt executables on Windows
|
|
- #5436: update object ids on unmarshaling
|
|
- #5442: camlp4: quotation issue with strings
|
|
- #5453: configure doesn't find X11 under Ubuntu/MultiarchSpec
|
|
- #5461: Double linking of bytecode modules
|
|
- #5463: Bigarray.*.map_file fail if empty array is requested
|
|
- #5465: increase stack size of ocamlopt.opt for windows
|
|
- #5469: private record type generated by functor loses abbreviation
|
|
- #5475: Wrapper script for interpreted LablTk wrongly handles command line
|
|
parameters
|
|
- #5476: bug in native code compilation of let rec on float arrays
|
|
- #5477: use pkg-config to configure graphics on linux
|
|
- #5481: update camlp4 magic numbers
|
|
- #5482: remove bashism in test suite scripts
|
|
- #5495: camlp4o dies on infix definition (or)
|
|
- #5498: Unification with an empty object only checks the absence of
|
|
the first method
|
|
- #5503: error when ocamlbuild is passed an absolute path as build directory
|
|
- #5509: misclassification of statically-allocated empty array that
|
|
falls exactly at beginning of an otherwise unused data page.
|
|
- #5510: ocamldep has duplicate -ml{,i}-synonym options
|
|
- #5511: in Bigarray.reshape, unwarranted limitation on new array dimensions.
|
|
- #5513: Int64.div causes floating point exception (ocamlopt, x86)
|
|
- #5516: in Bigarray C stubs, use C99 flexible array types if possible
|
|
- #5518: segfault with lazy empty array
|
|
- #5531: Allow ocamlbuild to add ocamldoc flags through -docflag
|
|
and -docflags switches
|
|
- #5538: combining -i and -annot in ocamlc
|
|
- #5543: in Bigarray.map_file, try to avoid using lseek() when growing file
|
|
- #5648: (probably fixed) test failures in tests/lib-threads
|
|
- #5551: repeated calls to find_in_path degrade performance
|
|
- #5552: Mac OS X: unrecognized gcc option "-no-cpp-precomp"
|
|
- #5555: add Hashtbl.reset to resize the bucket table to its initial size
|
|
- #5560: incompatible type for tuple pattern with -principal
|
|
- #5575: Random states are not marshallable across architectures
|
|
- #5579: camlp4: when a plugin is loaded in the toplevel,
|
|
Token.Filter.define_filter has no effect before the first syntax error
|
|
- #5585: typo: "explicitely"
|
|
- #5587: documentation: "allows to" is not correct English
|
|
- #5593: remove C file when -output-obj fails
|
|
- #5597: register names for instrtrace primitives in embedded bytecode
|
|
- #5598: add backslash-space support in strings in ocamllex
|
|
- #5603: wrong .file debug info generated by ocamlopt -g
|
|
- #5604: fix permissions of files created by ocamlbuild itself
|
|
- #5610: new unmarshaler (from #5318) fails to freshen object identifiers
|
|
- #5614: add missing -linkall flag when compiling ocamldoc.opt
|
|
- #5616: move ocamlbuild documentation to the reference manual
|
|
- #5619: Uncaught CType.Unify exception in the compiler
|
|
- #5620: invalid printing of type manifest (camlp4 revised syntax)
|
|
- #5637: invalid printing of anonymous type parameters (camlp4 revised syntax)
|
|
- #5643: issues with .cfi and .loc directives generated by ocamlopt -g
|
|
- #5644: Stream.count broken when used with Sapp or Slazy nodes
|
|
- #5647: Cannot use install_printer in debugger
|
|
- #5651: printer for abstract data type (camlp4 revised syntax)
|
|
- #5654: self pattern variable location tweak
|
|
- #5655: ocamlbuild doesn't pass cflags when building C stubs
|
|
- #5657: wrong error location for abbreviated record fields
|
|
- #5659: ocamlmklib -L option breaks with MSVC
|
|
- #5661: fixes for the test suite
|
|
- #5668: Camlp4 produces invalid syntax for "let _ = ..."
|
|
- #5671: initialization of compare_ext field in caml_final_custom_operations()
|
|
- #5677: do not use "value" as identifier (genprintval.ml)
|
|
- #5687: dynlink broken when used from "output-obj" main program (bytecode)
|
|
- problem with printing of string literals in camlp4 (reported on caml-list)
|
|
- emacs mode: colorization of comments and strings now works correctly
|
|
- problem with forall and method (reported on caml-list on 2011-07-26)
|
|
- crash when using OCAMLRUNPARAM=a=X with invalid X (reported in private)
|
|
|
|
Feature wishes:
|
|
- #2757: new option "-stdin" to make ocaml read stdin as a script
|
|
- #3358: better error message when mixing -a and .cmxa
|
|
- #3492: documentation: remove restriction on mixed streams
|
|
- #7971: allow configuring LIBDIR, BINDIR, and MANDIR relative to $(PREFIX)
|
|
- #8285: add Digest.from_hex
|
|
- #8341: toplevel: add option to suppress continuation prompts
|
|
- #4278: configure: option to disable "graph" library
|
|
- #4444: new String.trim function, removing leading and trailing whistespace
|
|
- #4549: make Filename.dirname/basename POSIX compliant
|
|
- #4830: add option -v to expunge.ml
|
|
- #4898: new Sys.big_endian boolean for machine endianness
|
|
- #4963, #5467: no extern "C" into ocaml C-stub headers
|
|
- #5199: tests are run only for bytecode if either native support is missing,
|
|
or a non-empty value is set to "BYTECODE_ONLY" Makefile variable
|
|
- #5215: marshalling of dynlinked closure
|
|
- #5236: new '%revapply' primitive with the semantics 'revapply x f = f x',
|
|
and '%apply' with semantics 'apply f x = f x'.
|
|
- #5255: natdynlink detection on powerpc, hurd, sparc
|
|
- #5295: OS threads: problem with caml_c_thread_unregister()
|
|
- #5297: compiler now checks existence of builtin primitives
|
|
- #5329: (Windows) more efficient Unix.select if all fd's are sockets
|
|
- #5357: warning for useless open statements
|
|
- #5358: first class modules don't allow "with type" declarations for types
|
|
in sub-modules
|
|
- #5385: configure: emit a warning when MACOSX_DEPLOYMENT_TARGET is set
|
|
- #5396: ocamldep: add options -sort, -all, and -one-line
|
|
- #5397: Filename.temp_dir_name should be mutable
|
|
- #5403: give better error message when emacs is not found in PATH
|
|
- #5411: new directive for the toplevel: #load_rec
|
|
- #5420: Unix.openfile share mode (Windows)
|
|
- #5421: Unix: do not leak fds in various open_proc* functions
|
|
- #5434: implement Unix.times in win32unix (partially)
|
|
- #5438: new warnings for unused declarations
|
|
- #5439: upgrade config.guess and config.sub
|
|
- #5445 and others: better printing of types with user-provided names
|
|
- #5454: Digest.compare is missing and md5 doc update
|
|
- #5455: .emacs instructions, add lines to recognize ocaml scripts
|
|
- #5456: pa_macro: replace __LOCATION__ after macro expansion; add LOCATION_OF
|
|
- #5461: bytecode: emit warning when linking two modules with the same name
|
|
- #5478: ocamlopt assumes ar command exists
|
|
- #5479: Num.num_of_string may raise an exception, not reflected in the
|
|
documentation.
|
|
- #5501: increase IO_BUFFER_SIZE to 64KiB
|
|
- #5532: improve error message when bytecode file is wrong
|
|
- #5555: add function Hashtbl.reset to resize the bucket table to
|
|
its initial size.
|
|
- #5586: increase UNIX_BUFFER_SIZE to 64KiB
|
|
- #5597: register names for instrtrace primitives in embedded bytecode
|
|
- #5599: Add warn() tag in ocamlbuild to control -w compiler switch
|
|
- #5628: add #remove_directory and Topdirs.remove_directory to remove
|
|
a directory from the load path
|
|
- #5636: in system threads library, issue with linking of pthread_atfork
|
|
- #5666: C includes don't provide a revision number
|
|
- ocamldebug: ability to inspect values that contain code pointers
|
|
- ocamldebug: new 'environment' directive to set environment variables
|
|
for debuggee
|
|
- configure: add -no-camlp4 option
|
|
|
|
Shedding weight:
|
|
* Removed the obsolete native-code generators for Alpha, HPPA, IA64 and MIPS.
|
|
* The "DBM" library (interface with Unix DBM key-value stores) is no
|
|
longer part of this distribution. It now lives its own life at
|
|
https://forge.ocamlcore.org/projects/camldbm/
|
|
* The "OCamlWin" toplevel user interface for MS Windows is no longer
|
|
part of this distribution. It now lives its own life at
|
|
https://forge.ocamlcore.org/projects/ocamltopwin/
|
|
|
|
Other changes:
|
|
- Copy VERSION file to library directory when installing.
|
|
|
|
|
|
OCaml 3.12.1 (4 Jul 2011):
|
|
--------------------------
|
|
|
|
Bug fixes:
|
|
- #4345, #4767: problems with camlp4 printing of float values
|
|
- #4380: ocamlbuild should not use tput on windows
|
|
- #4487, #5164: multiple 'module type of' are incompatible
|
|
- #4552: ocamlbuild does not create symlinks when using '.itarget' file
|
|
- #4673, #5144: camlp4 fails on object copy syntax
|
|
- #4702: system threads: cleanup tick thread at exit
|
|
- #4732: camlp4 rejects polymorphic variants using keywords from macros
|
|
- #4778: Win32/MSVC port: rare syntax error in generated MASM assembly file
|
|
- #4794, #4959: call annotations not generated by ocamlopt
|
|
- #4820: revised syntax pretty printer crashes with 'Stack_overflow'
|
|
- #4928: wrong printing of classes and class types by camlp4
|
|
- #4939: camlp4 rejects patterns of the '?x:_' form
|
|
- #4967: ocamlbuild passes wrong switches to ocamldep through menhir
|
|
- #4972: mkcamlp4 does not include 'dynlink.cma'
|
|
- #5039: ocamlbuild should use '-linkpkg' only when linking programs
|
|
- #5066: ocamldoc: add -charset option used in html generator
|
|
- #5069: fcntl() in caml_sys_open may block, do it within blocking section
|
|
- #5071, #5129, #5134: inconsistencies between camlp4 and camlp4* binaries
|
|
- #5080, #5104: regression in type constructor handling by camlp4
|
|
- #5090: bad interaction between toplevel and camlp4
|
|
- #5095: ocamlbuild ignores some tags when building bytecode objects
|
|
- #5100: ocamlbuild always rebuilds a 'cmxs' file
|
|
- #5103: build and install objinfo when building with ocamlbuild
|
|
- #5109: crash when a parser calls a lexer that calls another parser
|
|
- #5110: invalid module name when using optional argument
|
|
- #5115: bytecode executables produced by msvc64 port crash on 32-bit versions
|
|
- #5117: bigarray: wrong function name without HAS_MMAP; missing include
|
|
- #5118: Camlp4o and integer literals
|
|
- #5122: camlp4 rejects lowercase identifiers for module types
|
|
- #5123: shift_right_big_int returns a wrong zero
|
|
- #5124: substitution inside a signature leads to odd printing
|
|
- #5128: typo in 'Camlp4ListComprehension' syntax extension
|
|
- #5136: obsolete function used in emacs mode
|
|
- #5145: ocamldoc: missing html escapes
|
|
- #5146: problem with spaces in multi-line string constants
|
|
- #5149: (partial) various documentation problems
|
|
- #5156: rare compiler crash with objects
|
|
- #5165: ocamlbuild does not pass '-thread' option to ocamlfind
|
|
- #5167: camlp4r loops when printing package type
|
|
- #5172: camlp4 support for 'module type of' construct
|
|
- #5175: in bigarray accesses, make sure bigarray expr is evaluated only once
|
|
- #5177: Gc.compact implies Gc.full_major
|
|
- #5182: use bytecode version of ocamldoc to generate man pages
|
|
- #5184: under Windows, alignment issue with bigarrays mapped from files
|
|
- #5188: double-free corruption in bytecode system threads
|
|
- #5192: mismatch between words and bytes in interpreting max_young_wosize
|
|
- #5202: error in documentation of atan2
|
|
- #5209: natdynlink incorrectly detected on BSD systems
|
|
- #5213: ocamlbuild should pass '-rectypes' to ocamldoc when needed
|
|
- #5217: ocamlfind plugin should add '-linkpkg' for toplevel
|
|
- #5228: document the exceptions raised by functions in 'Filename'
|
|
- #5229: typo in build script ('TAG_LINE' vs 'TAGLINE')
|
|
- #5230: error in documentation of Scanf.Scanning.open_in
|
|
- #5234: option -shared reverses order of -cclib options
|
|
- #5237: incorrect .size directives generated for x86-32 and x86-64
|
|
- #5244: String.compare uses polymorphic compare_val (regression of #4194)
|
|
- #5248: regression introduced while fixing #5118
|
|
- #5252: typo in docs
|
|
- #5258: win32unix: unix fd leak under windows
|
|
- #5269: (tentative fix) Wrong ext_ref entries in .annot files
|
|
- #5272: caml.el doesn't recognize downto as a keyword
|
|
- #5276: issue with ocamlc -pack and recursively-packed modules
|
|
- #5280: alignment constraints incorrectly autodetected on MIPS 32
|
|
- #5281: typo in error message
|
|
- #5308: unused variables not detected in "include (struct .. end)"
|
|
- camlp4 revised syntax printing bug in the toplevel (reported on caml-list)
|
|
- configure: do not define _WIN32 under cygwin
|
|
- Hardened generic comparison in the case where two custom blocks
|
|
are compared and have different sets of custom operations.
|
|
- Hardened comparison between bigarrays in the case where the two
|
|
bigarrays have different kinds.
|
|
- Fixed wrong autodetection of expm1() and log1p().
|
|
- don't add .exe suffix when installing the ocamlmktop shell script
|
|
- ocamldoc: minor fixes related to the display of ocamldoc options
|
|
- fixed bug with huge values in OCAMLRUNPARAM
|
|
- mismatch between declaration and definition of caml_major_collection_slice
|
|
|
|
Feature wishes:
|
|
- #4992: added '-ml-synonym' and '-mli-synonym' options to ocamldep
|
|
- #5065: added '-ocamldoc' option to ocamlbuild
|
|
- #5139: added possibility to add options to ocamlbuild
|
|
- #5158: added access to current camlp4 parsers and printers
|
|
- #5180: improved instruction selection for float operations on amd64
|
|
- stdlib: added a 'usage_string' function to Arg
|
|
- allow with constraints to add a type equation to a datatype definition
|
|
- ocamldoc: allow to merge '@before' tags like other ones
|
|
- ocamlbuild: allow dependency on file "_oasis"
|
|
|
|
Other changes:
|
|
- Changed default minor heap size from 32k to 256k words.
|
|
- Added new operation 'compare_ext' to custom blocks, called when
|
|
comparing a custom block value with an unboxed integer.
|
|
|
|
|
|
Objective Caml 3.12.0 (2 Aug 2010):
|
|
-----------------------------------
|
|
|
|
(Changes that can break existing programs are marked with a "*" )
|
|
|
|
Language features:
|
|
- Shorthand notation for records: in expressions and patterns,
|
|
{ lbl } stands for { lbl = lbl } and { M.lbl } for { M.lbl = lbl }
|
|
- Record patterns of the form { lbl = pat; _ } to mark that not all
|
|
labels are listed, purposefully. (See new warning below.)
|
|
- Explicit naming of a generic type; in an expression
|
|
"fun ... (type t) ... -> e", the type t is considered abstract in its
|
|
scope (the arguments that follow it and the body of the function),
|
|
and then replaced by a fresh type variable. In particular, the type
|
|
t can be used in contexts where a type variable is not allowed
|
|
(e.g. for defining an exception in a local module).
|
|
- Explicit polymorphic types and polymorphic recursion. In let
|
|
definitions, one can write an explicit polymorphic type just
|
|
immediately the function name; the polymorphism will be enforced,
|
|
and recursive calls may use the polymorphism.
|
|
The syntax is the same as for polymorphic methods:
|
|
"let [rec] <ident> : 'a1 ... 'an. <typexp> = ..."
|
|
- First-class packages modules.
|
|
New kind of type expression, for packaged modules: (module PT).
|
|
New kind of expression, to pack a module as a first-class value:
|
|
(module MODEXPR : PT).
|
|
New kind of module expression, to unpack a first-class value as a module:
|
|
(val EXPR : PT).
|
|
PT is a package type of the form "S" or
|
|
"S with type t1 = ... and ... and type tn = ..." (S refers to a module type).
|
|
- Local opening of modules in a subexpression.
|
|
Syntax: "let open M in e", or "M.(e)"
|
|
- In class definitions, method and instance variable override can now
|
|
be made explicit, by writing "method!", "val!" or "inherit!" in place of
|
|
"method", "val" and "inherit". It is an error to override an
|
|
undefined member (or to use overriding inheritance when nothing get
|
|
overridden). Additionally, these constructs disactivate respectively
|
|
warnings 7 (method override, code 'M') and 13 (instance variable
|
|
override, code 'V'). Note that, by default, warning 7 is inactive
|
|
and warning 13 is active.
|
|
- "Destructive" substitution in signatures.
|
|
By writing "<signature> with type t := <typeconstr>" and
|
|
"<signature> with module M := <module-path>" one replaces "t" and "M"
|
|
inside the signature, removing their respective fields. Among other
|
|
uses, this allows to merge two signatures containing identically
|
|
named fields.
|
|
* While fixing #4824, also corrected a gaping hole in the type checker,
|
|
which allowed instantiating separately object parameters and instance
|
|
variables in an interface. This hole was here since the beginning of
|
|
ocaml, and as a result many programs using object inheritance in a non
|
|
trivial way will need to be corrected. You can look at lablgtk2 for an
|
|
example.
|
|
|
|
Compilers and toplevel:
|
|
- Warnings are now numbered and can be switched on and off individually.
|
|
The old system with letters referring to sets of warnings is still
|
|
supported.
|
|
- New warnings:
|
|
+ 9 (code 'R') to signal record patterns without "; _" where
|
|
some labels of the record type are not listed in the pattern.
|
|
+ 28 when giving a wildcard argument to a constant constructor in
|
|
a pattern-matching.
|
|
+ 29 when an end-of-line appears unescaped in a string constant.
|
|
+ 30 when the same constructor or record field is defined twice in
|
|
mutually-recursive type definitions.
|
|
* The semantics of warning 7 (code 'M', method override) have changed
|
|
(it now detects all overrides, not just repeated definitions inside
|
|
the same class body), and it is now inactive by default.
|
|
- Better error report in case of unbound qualified identifier: if the module
|
|
is unbound this error is reported in the first place.
|
|
- Added option '-strict-sequence' to force left hand part of sequence to have
|
|
type unit.
|
|
- Added option '-no-app-funct' to turn applicative functors off.
|
|
This option can help working around mysterious type incompatibilities
|
|
caused by the incomplete comparison of applicative paths F(X).t.
|
|
|
|
Native-code compiler:
|
|
- AMD64: shorter and slightly more efficient code generated for
|
|
float comparisons.
|
|
|
|
Standard library:
|
|
- Format: new function ikfprintf analogous to ifprintf with a continuation
|
|
argument.
|
|
* #4210, #4245: stricter range checking in string->integer conversion
|
|
functions (int_of_string, Int32.of_string, Int64.of_string,
|
|
Nativeint.of_string). The decimal string corresponding to
|
|
max_int + 1 is no longer accepted.
|
|
- Scanf: to prevent confusion when mixing Scanf scanning functions and direct
|
|
low level input, value Scanf.stdin has been added.
|
|
* Random: changed the algorithm to produce better randomness. Now passes the
|
|
DieHard tests.
|
|
- Map: implement functions from Set that make sense for Map.
|
|
|
|
Other libraries:
|
|
* Str: letters that constitute a word now include digits 0-9 and
|
|
underscore _. This changes the interpretation of '\b' (word boundary)
|
|
in regexps, but is more consistent with other regexp libraries. (#4874).
|
|
|
|
Ocamlbuild:
|
|
- Add support for native dynlink.
|
|
|
|
New tool:
|
|
- ocamlobjinfo: displays various information, esp. dependencies, for
|
|
compiled OCaml files (.cmi, .cmo, .cma, .cmx, .cmxa, .cmxs, and bytecode
|
|
executables). Extends and makes more official the old objinfo tool
|
|
that was installed by some OCaml packages.
|
|
|
|
All tools:
|
|
- #4857: add a -vnum option to display the version number and nothing else
|
|
|
|
Bug Fixes:
|
|
- #4012: Map.map and Map.mapi do not conform to specification
|
|
- #4478: better error messages for type definition mismatches
|
|
- #4683: labltk script uses fixed path on windows
|
|
- #4742: finalisation function raising an exception blocks other finalisations
|
|
- #4775: compiler crash on crazy types (temporary fix)
|
|
- #4824: narrowing the type of class parameters with a module specification
|
|
- #4862: relaxed value restriction and records
|
|
- #4884: optional arguments do not work when Some is redefined
|
|
- #4964: parenthesized names for infix functions in annot files
|
|
- #4970: better error message for instance variables
|
|
- #4975: spelling mistakes
|
|
- #4988: contravariance lost with ocamlc -i
|
|
- #5004: problem in Buffer.add_channel with very large lengths.
|
|
- #5008: on AMD64/MSVC port, rare float corruption during GC.
|
|
- #5018: wrong exception raised by Dynlink.loadfile.
|
|
- #5057: fatal typing error with local module + functor + polymorphic variant
|
|
- Wrong type for Obj.add_offset.
|
|
- Small problem with representation of Int32, Int64, and Nativeint constants.
|
|
- Use RTLD_LOCAL for native dynlink in private mode.
|
|
|
|
Objective Caml 3.11.2 (20 Jan 2010):
|
|
------------------------------------
|
|
|
|
Bug fixes:
|
|
- #4151: better documentation for min and max w.r.t. NaN
|
|
- #4421: ocamlbuild uses wrong compiler for C files
|
|
- #4710, #4720: ocamlbuild does not use properly configuration information
|
|
- #4750: under some Windows installations, high start-up times for Unix lib
|
|
- #4777: problem with scanf and CRLF
|
|
- #4783: ocamlmklib problem under Windows
|
|
- #4810: BSD problem with socket addresses, e.g. in Unix.getnameinfo
|
|
- #4813: issue with parsing of float literals by the GNU assembler
|
|
- #4816: problem with modules and private types
|
|
- #4818: missed opportunity for type-based optimization of bigarray accesses
|
|
- #4821: check for duplicate method names in classes
|
|
- #4823: build problem on Mac OS X
|
|
- #4836: spurious errors raised by Unix.single_write under Windows
|
|
- #4841, #4860, #4930: problem with ocamlopt -output-obj under Mac OS X
|
|
- #4847: C compiler error with ocamlc -output-obj under Win64
|
|
- #4856: ocamlbuild uses ocamlrun to execute a native plugin
|
|
- #4867, #4760: ocamlopt -shared fails on Mac OS X 64bit
|
|
- #4873: ocamlbuild ignores "thread" tag when building a custom toplevel
|
|
- #4890: ocamlbuild tries to use native plugin on bytecode-only arch
|
|
- #4896: ocamlbuild should always pass -I to tools for external libraries
|
|
- #4900: small bug triggering automatic compaction even if max_overhead = 1M
|
|
- #4902: bug in %.0F printf format
|
|
- #4910: problem with format concatenation
|
|
- #4922: ocamlbuild recompiles too many files
|
|
- #4923: missing \xff for scanf %S
|
|
- #4933: functors not handling private types correctly
|
|
- #4940: problem with end-of-line in DOS text mode, tentative fix
|
|
- #4953: problem compiling bytecode interpreter on ARM in Thumb mode.
|
|
- #4955: compiler crash when typing recursive type expression with constraint
|
|
- Module Printf: the simple conversion %F (without width indication) was not
|
|
treated properly.
|
|
- Makefile: problem with cygwin, flexdll, and symbolic links
|
|
- Various build problems with ocamlbuild under Windows with msvc
|
|
|
|
Feature wishes:
|
|
- #2337: (tentative implementation) make ocamldebug use #linenum annotations
|
|
- #2464, #4477: custom exception printers
|
|
- #3456: Obj.double_field and Obj.set_double_field functions
|
|
- #4003: destination directory can be given to Filename.[open_]temp_file
|
|
- #4647: Buffer.blit function
|
|
- #4685: access to Filename.dir_sep
|
|
- #4703: support for debugging embedded applications
|
|
- #4723: "clear_rules" function to empty the set of ocamlbuild rules
|
|
- #4921: configure option to help cross-compilers
|
|
|
|
Objective Caml 3.11.1 (12 Jun 2009):
|
|
------------------------------------
|
|
|
|
Bug fixes:
|
|
- #4095: ocamldebug: strange behaviour of control-C
|
|
- #4403: ocamldebug: improved handling of packed modules
|
|
- #4650: Str.regexp_case_fold mis-handling complemented character sets [^a]
|
|
- #4660: Scanf.format_from_string: handling of double quote
|
|
- #4666: Unix.exec* failure in multithread programs under MacOS X and FreeBSD
|
|
- #4667: debugger out of sync with dynlink changes
|
|
- #4678: random "out of memory" error with systhreads
|
|
- #4690: issue with dynamic loading under MacOS 10.5
|
|
- #4692: wrong error message with options -i and -pack passed to ocamlc
|
|
- #4699: in otherlibs/dbm, fixed construction of dlldbm.so.
|
|
- #4704: error in caml_modify_generational_global_root()
|
|
- #4708: (ocamldoc) improved printing of infix identifiers such as "lor".
|
|
- #4722: typo in configure script
|
|
- #4729: documented the fact that PF_INET6 is not available on all platforms
|
|
- #4730: incorrect typing involving abbreviation "type 'a t = 'a"
|
|
- #4731: incorrect quoting of arguments passed to the assembler on x86-64
|
|
- #4735: Unix.LargeFile.fstat cannot report size over 32bits on Win32
|
|
- #4740: guard against possible processor error in
|
|
{Int32,Int64,Nativeint}.{div,rem}
|
|
- #4745: type inference wrongly produced non-generalizable type variables.
|
|
- #4749: better pipe size for win32unix
|
|
- #4756: printf: no error reported for wrong format '%_s'
|
|
- #4758: scanf: handling of \<newline> by format '%S'
|
|
- #4766: incorrect simplification of some type abbreviations.
|
|
- #4768: printf: %F does not respect width and precision specifications
|
|
- #4769: Format.bprintf fails to flush
|
|
- #4775: fatal error Ctype.Unify during module type-checking (temporary fix)
|
|
- #4776: bad interaction between exceptions and classes
|
|
- #4780: labltk build problem under Windows.
|
|
- #4790: under Windows, map ERROR_NO_DATA Win32 error to EPIPE Unix error.
|
|
- #4792: bug in Big_int.big_int_of_int64 on 32-bit platforms.
|
|
- #4796: ocamlyacc: missing NUL termination of string
|
|
- #4804: bug in Big_int.int64_of_big_int on 32-bit platforms.
|
|
- #4805: improving compatibility with the clang C compiler
|
|
- #4809: issue with Unix.create_process under Win32
|
|
- #4814: ocamlbrowser: crash when editing comments
|
|
- #4816: module abbreviations remove 'private' type restrictions
|
|
- #4817: Object type gives error "Unbound type parameter .."
|
|
- Module Parsing: improved computation of locations when an ocamlyacc rule
|
|
starts with an empty nonterminal
|
|
- Type-checker: fixed wrong variance computation for private types
|
|
- x86-32 code generator, MSVC port: wrong "fld" instruction generated.
|
|
- ocamlbuild: incorrectly using the compile-time value of $OCAMLLIB
|
|
- Makefile problem when configured with -no-shared-libs
|
|
- ocamldoc: use dynamic loading in native code
|
|
|
|
Other changes:
|
|
- Improved wording of various error messages
|
|
(contributed by Jonathan Davies, Citrix).
|
|
- Support for 64-bit mode in Solaris/x86 (#4670).
|
|
|
|
|
|
Objective Caml 3.11.0 (03 Dec 2008):
|
|
------------------------------------
|
|
|
|
(Changes that can break existing programs are marked with a "*" )
|
|
|
|
Language features:
|
|
- Addition of lazy patterns: "lazy <pat>" matches suspensions whose values,
|
|
after forcing, match the pattern <pat>.
|
|
- Introduction of private abbreviation types "type t = private <type-expr>",
|
|
for abstracting the actual manifest type in type abbreviations.
|
|
- Subtyping is now allowed between a private abbreviation and its definition,
|
|
and between a polymorphic method and its monomorphic instance.
|
|
|
|
Compilers:
|
|
- The file name for a compilation unit should correspond to a valid
|
|
identifier (Otherwise dynamic linking and other things can fail, and
|
|
a warning is emitted.)
|
|
* Revised -output-obj: the output name must now be provided; its
|
|
extension must be one of .o/.obj, .so/.dll, or .c for the
|
|
bytecode compiler. The compilers can now produce a shared library
|
|
(with all the needed -ccopts/-ccobjs options) directly.
|
|
- -dtypes renamed to -annot, records (in .annot files) which function calls
|
|
are tail calls.
|
|
- All compiler error messages now include a file name and location, for
|
|
better interaction with Emacs' compilation mode.
|
|
- Optimized compilation of "lazy e" when the argument "e" is
|
|
already evaluated.
|
|
- Optimized compilation of equality tests with a variant constant constructor.
|
|
- The -dllib options recorded in libraries are no longer ignored when
|
|
-use_runtime or -use_prims is used (unless -no_auto_link is
|
|
explicitly used).
|
|
- Check that at most one of -pack, -a, -shared, -c, -output-obj is
|
|
given on the command line.
|
|
- Optimized compilation of private types as regular manifest types
|
|
(e.g. abbreviation to float, float array or record types with only
|
|
float fields).
|
|
|
|
Native-code compiler:
|
|
- New port: Mac OS X / Intel in 64-bit mode (configure with -cc "gcc -m64").
|
|
- A new option "-shared" to produce a plugin that can be dynamically
|
|
loaded with the native version of Dynlink.
|
|
- A new option "-nodynlink" to enable optimizations valid only for code
|
|
that is never dynlinked (no-op except for AMD64).
|
|
- More aggressive unboxing of floats and boxed integers.
|
|
- Can select which assembler and asm options to use at configuration time.
|
|
|
|
Run-time system:
|
|
- New implementation of the page table describing the heap (two-level
|
|
array in 32 bits, sparse hashtable in 64 bits), fixes issues with address
|
|
space randomization on 64-bit OS (#4448).
|
|
- New "generational" API for registering global memory roots with the GC,
|
|
enables faster scanning of global roots.
|
|
(The functions are caml_*_generational_global_root in <caml/memory.h>.)
|
|
- New function "caml_raise_with_args" to raise an exception with several
|
|
arguments from C.
|
|
- Changes in implementation of dynamic linking of C code:
|
|
under Win32, use Alain Frisch's flexdll implementation of the dlopen
|
|
API; under MacOSX, use dlopen API instead of MacOSX bundle API.
|
|
- Programs may now choose a first-fit allocation policy instead of
|
|
the default next-fit. First-fit reduces fragmentation but is
|
|
slightly slower in some cases.
|
|
|
|
Standard library:
|
|
- Parsing library: new function "set_trace" to programmatically turn
|
|
on or off the printing of a trace during parsing.
|
|
- Printexc library: new functions "print_backtrace" and "get_backtrace"
|
|
to obtain a stack backtrace of the most recently raised exception.
|
|
New function "record_backtrace" to turn the exception backtrace mechanism
|
|
on or off from within a program.
|
|
- Scanf library: fine-tuning of meta format implementation;
|
|
fscanf behaviour revisited: only one input buffer is allocated for any
|
|
given input channel;
|
|
the %n conversion does not count a lookahead character as read.
|
|
|
|
Other libraries:
|
|
- Dynlink: on some platforms, the Dynlink library is now available in
|
|
native code. The boolean Dynlink.is_native allows the program to
|
|
know whether it has been compiled in bytecode or in native code.
|
|
- Bigarrays: added "unsafe_get" and "unsafe_set"
|
|
(non-bound-checking versions of "get" and "set").
|
|
- Bigarrays: removed limitation "array dimension < 2^31".
|
|
- Labltk: added support for TK 8.5.
|
|
- Num: added conversions between big_int and int32, nativeint, int64.
|
|
More efficient implementation of Num.quo_num and Num.mod_num.
|
|
- Threads: improved efficiency of mutex and condition variable operations;
|
|
improved interaction with Unix.fork (#4577).
|
|
- Unix: added getsockopt_error returning type Unix.error.
|
|
Added support for TCP_NODELAY and IPV6_ONLY socket options.
|
|
- Win32 Unix: "select" now supports all kinds of file descriptors.
|
|
Improved emulation of "lockf" (#4609).
|
|
|
|
Tools:
|
|
- ocamldebug now supported under Windows (MSVC and Mingw ports),
|
|
but without the replay feature. (Contributed by Dmitry Bely
|
|
and Sylvain Le Gall at OCamlCore with support from Lexifi.)
|
|
- ocamldoc: new option -no-module-constraint-filter to include functions
|
|
hidden by signature constraint in documentation.
|
|
- ocamlmklib and ocamldep.opt now available under Windows ports.
|
|
- ocamlmklib no longer supports the -implib option.
|
|
- ocamlnat: an experimental native toplevel (not built by default).
|
|
|
|
Camlp4:
|
|
* programs linked with camlp4lib.cma now also need dynlink.cma.
|
|
|
|
Bug fixes:
|
|
- Major GC and heap compaction: fixed bug involving lazy values and
|
|
out-of-heap pointers.
|
|
- #3915: updated most man pages.
|
|
- #4261: type-checking of recursive modules
|
|
- #4308: better stack backtraces for "spontaneous" exceptions such as
|
|
Stack_overflow, Out_of_memory, etc.
|
|
- #4338: Str.global_substitute, Str.global_replace and the Str.*split*
|
|
functions are now tail-recursive.
|
|
- #4503: fixed bug in classify_float on ARM.
|
|
- #4512: type-checking of recursive modules
|
|
- #4517: crash in ocamllex-generated lexers.
|
|
- #4542: problem with return value of Unix.nice.
|
|
- #4557: type-checking of recursive modules.
|
|
- #4562: strange %n semantics in scanf.
|
|
- #4564: add note "stack is not executable" to object files generated by
|
|
ocamlopt (Linux/x86, Linux/AMD64).
|
|
- #4566: bug in Ratio.approx_ratio_fix and Num.approx_num_fix.
|
|
- #4582: clarified the documentation of functions in the String module.
|
|
- #4583: stack overflow in "ocamlopt -g" during closure conversion pass.
|
|
- #4585: ocamldoc and "val virtual" declarations.
|
|
- #4587: ocamldoc and escaped @ characters.
|
|
- #4605: Buffer.add_substitute was sometime wrong when target string had
|
|
backslashes.
|
|
- #4614: Inconsistent declaration of CamlCBCmd in LablTk library.
|
|
|
|
|
|
Objective Caml 3.10.2 (29 Feb 2008):
|
|
------------------------------------
|
|
|
|
Bug fixes:
|
|
- #3410 (partial) Typo in ocamldep man page
|
|
- #3952 (partial) ocamlopt: allocation problems on ARM
|
|
- #4339 (continued) ocamlopt: problems on HPPA
|
|
- #4455 str.mli not installed under Windows
|
|
- #4473 crash when accessing float array with polymorphic method
|
|
- #4480 runtime would not compile without gcc extensions
|
|
- #4481 wrong typing of exceptions with object arguments
|
|
- #4490 typo in error message
|
|
- Random crash on 32-bit when major_heap_increment >= 2^22
|
|
- Big performance bug in Weak hashtables
|
|
- Small bugs in the make-package-macosx script
|
|
- Bug in typing of polymorphic variants (reported on caml-list)
|
|
|
|
|
|
Objective Caml 3.10.1 (11 Jan 2008):
|
|
------------------------------------
|
|
|
|
Bug fixes:
|
|
- #3830 small bugs in docs
|
|
- #4053 compilers: improved compilation time for large variant types
|
|
- #4174 ocamlopt: fixed ocamlopt -nopervasives
|
|
- #4199 otherlibs: documented a small problem in Unix.utimes
|
|
- #4280 camlp4: parsing of identifier (^)
|
|
- #4281 camlp4: parsing of type constraint
|
|
- #4285 runtime: cannot compile under AIX
|
|
- #4286 ocamlbuild: cannot compile under AIX and SunOS
|
|
- #4288 compilers: including a functor application with side effects
|
|
- #4295 camlp4 toplevel: synchronization after an error
|
|
- #4300 ocamlopt: crash with backtrace and illegal array access
|
|
- #4302 camlp4: list comprehension parsing problem
|
|
- #4304 ocamlbuild: handle -I correctly
|
|
- #4305 stdlib: alignment of Arg.Symbol
|
|
- #4307 camlp4: assertion failure
|
|
- #4312 camlp4: accept "let _ : int = 1"
|
|
- #4313 ocamlbuild: -log and missing directories
|
|
- #4315 camlp4: constraints in classes
|
|
- #4316 compilers: crash with recursive modules and Lazy
|
|
- #4318 ocamldoc: installation problem with Cygwin (tentative fix)
|
|
- #4322 ocamlopt: stack overflow under Windows
|
|
- #4325 compilers: wrong error message for unused var
|
|
- #4326 otherlibs: marshal Big_int on win64
|
|
- #4327 ocamlbuild: make emacs look for .annot in _build directory
|
|
- #4328 camlp4: stack overflow with nil nodes
|
|
- #4331 camlp4: guards on fun expressions
|
|
- #4332 camlp4: parsing of negative 32/64 bit numbers
|
|
- #4336 compilers: unsafe recursive modules
|
|
- #4337 (note) camlp4: invalid character escapes
|
|
- #4339 ocamlopt: problems on HP-UX (tentative fix)
|
|
- #4340 camlp4: wrong pretty-printing of optional arguments
|
|
- #4348 ocamlopt: crash on Mac Intel
|
|
- #4349 camlp4: bug in private type definitions
|
|
- #4350 compilers: type errors with records and polymorphic variants
|
|
- #4352 compilers: terminal recursion under Windows (tentative fix)
|
|
- #4354 ocamlcp: mismatch with ocaml on polymorphic let
|
|
- #4358 ocamlopt: float constants wrong on ARM
|
|
- #4360 ocamldoc: string inside comment
|
|
- #4365 toplevel: wrong pretty-printing of polymorphic variants
|
|
- #4373 otherlibs: leaks in win32unix
|
|
- #4374 otherlibs: threads module not initialized
|
|
- #4375 configure: fails to build on bytecode-only architectures
|
|
- #4377 runtime: finalisation of infix pointers
|
|
- #4378 ocamlbuild: typo in plugin.ml
|
|
- #4379 ocamlbuild: problem with plugins under Windows
|
|
- #4382 compilers: typing of polymorphic record fields
|
|
- #4383 compilers: including module with private type
|
|
- #4385 stdlib: Int32/Int64.format are unsafe
|
|
- #4386 otherlibs: wrong signal numbers with Unix.sigprocmask etc.
|
|
- #4387 ocamlbuild: build directory not used properly
|
|
- #4392 ocamldep: optional argument of class
|
|
- #4394 otherlibs: infinite loops in Str
|
|
- #4397 otherlibs: wrong size for flag arrays in win32unix
|
|
- #4402 ocamldebug: doesn't work with -rectypes
|
|
- #4410 ocamlbuild: problem with plugin and -build
|
|
- #4411 otherlibs: crash with Unix.access under Windows
|
|
- #4412 stdlib: marshalling broken on 64 bit architectures
|
|
- #4413 ocamlopt: crash on AMD64 with out-of-bound access and reraise
|
|
- #4417 camlp4: pretty-printing of unary minus
|
|
- #4419 camlp4: problem with constraint in type class
|
|
- #4426 compilers: problem with optional labels
|
|
- #4427 camlp4: wrong pretty-printing of lists of functions
|
|
- #4433 ocamlopt: fails to build on MacOSX 10.5
|
|
- #4435 compilers: crash with objects
|
|
- #4439 fails to build on MacOSX 10.5
|
|
- #4441 crash when build on sparc64 linux
|
|
- #4442 stdlib: crash with weak pointers
|
|
- #4446 configure: fails to detect X11 on MacOSX 10.5
|
|
- #4448 runtime: huge page table on 64-bit architectures
|
|
- #4450 compilers: stack overflow with recursive modules
|
|
- #4470 compilers: type-checking of recursive modules too restrictive
|
|
- #4472 configure: autodetection of libX11.so on Fedora x86_64
|
|
- printf: removed (partially implemented) positional specifications
|
|
- polymorphic < and <= comparisons: some C compiler optimizations
|
|
were causing incorrect results when arguments are incomparable
|
|
|
|
New features:
|
|
- made configure script work on PlayStation 3
|
|
- ARM port: brought up-to-date for Debian 4.0 (Etch)
|
|
- many other small changes and bugfixes in camlp4, ocamlbuild, labltk,
|
|
emacs files
|
|
|
|
|
|
Objective Caml 3.10.0 (18 May 2007):
|
|
------------------------------------
|
|
|
|
(Changes that can break existing programs are marked with a "*" )
|
|
|
|
Language features:
|
|
- Added virtual instance variables in classes "val virtual v : t"
|
|
* Changed the behaviour of instance variable overriding; the new
|
|
definition replaces the old one, rather than creating a new
|
|
variable.
|
|
|
|
New tools:
|
|
- ocamlbuild: compilation manager for OCaml applications and libraries.
|
|
See draft documentation at http://gallium.inria.fr/~pouillar/
|
|
* Camlp4: heavily revised implementation, new API.
|
|
|
|
New ports:
|
|
- MacOS X PowerPC 64 bits.
|
|
- MS Windows 64 bits (x64) using the Microsoft PSDK toolchain.
|
|
- MS Windows 32 bits using the Visual Studio 2005 toolchain.
|
|
|
|
Compilers:
|
|
- Faster type-checking of functor applications.
|
|
- Referencing an interface compiled with -rectypes from a module
|
|
not compiled with -rectypes is now an error.
|
|
- Revised the "fragile matching" warning.
|
|
|
|
Native-code compiler:
|
|
- Print a stack backtrace on an uncaught exception.
|
|
(Compile and link with ocamlopt -g; execute with OCAMLRUNPARAM=b.)
|
|
Supported on Intel/AMD in 32 and 64 bits, PPC in 32 and 64 bits.
|
|
- Stack overflow detection on MS Windows 32 bits (courtesy O. Andrieu).
|
|
- Stack overflow detection on MacOS X PPC and Intel.
|
|
- Intel/AMD 64 bits: generate position-independent code by default.
|
|
- Fixed bug involving -for-pack and missing .cmx files (#4124).
|
|
- Fixed bug causing duplication of literals (#4152).
|
|
|
|
Run-time system:
|
|
- C/Caml interface functions take "char const *" arguments
|
|
instead of "char *" when appropriate.
|
|
- Faster string comparisons (fast case if strings are ==).
|
|
|
|
Standard library:
|
|
- Refined typing of format strings (type format6).
|
|
- Printf, Format: new function ifprintf that consumes its arguments
|
|
and prints nothing (useful to print conditionally).
|
|
- Scanf:
|
|
new function format_from_string to convert a string to a format string;
|
|
new %r conversion to accommodate user defined scanners.
|
|
- Filename: improved Win32 implementation of Filename.quote.
|
|
- List: List.nth now tail-recursive.
|
|
- Sys: added Sys.is_directory. Some functions (e.g. Sys.command) that
|
|
could incorrectly raise Sys_io_blocked now raise Sys_error as intended.
|
|
- String and Char: the function ``escaped'' now escapes all the characters
|
|
especially handled by the compiler's lexer (#4220).
|
|
|
|
Other libraries:
|
|
- Bigarray: mmap_file takes an optional argument specifying
|
|
the start position of the data in the mapped file.
|
|
- Dynlink: now defines only two modules, Dynlink and Dynlinkaux (internal),
|
|
reducing risks of name conflicts with user modules.
|
|
- Labltk under Win32: now uses Tcl/Tk 8.4 instead of 8.3 by default.
|
|
- VM threads: improved performance of I/O operations (less polling).
|
|
- Unix: new function Unix.isatty.
|
|
- Unix emulation under Win32:
|
|
fixed incorrect error reporting in several functions (#4097);
|
|
better handling of channels opened on sockets (#4098);
|
|
fixed GC bug in Unix.system (#4112).
|
|
|
|
Documentation generator (OCamldoc):
|
|
- correctly handle '?' in value names (#4215)
|
|
- new option -hide-warnings not to print ocamldoc warnings
|
|
|
|
Lexer generator (ocamllex): improved error reporting.
|
|
|
|
License: fixed a typo in the "special exception" to the LGPL.
|
|
|
|
|
|
Objective Caml 3.09.3 (15 Sep 2006):
|
|
------------------------------------
|
|
|
|
Bug fixes:
|
|
- ocamldoc: -using modtype constraint to filter module elements displayed
|
|
in doc #4016
|
|
- ocamldoc: error in merging of top dependencies of modules #4007
|
|
- ocamldoc: -dot-colors has no effect #3981
|
|
- ocamdloc: missing crossref in text from intro files #4066
|
|
- compilers: segfault with recursive modules #4008
|
|
- compilers: infinite loop when compiling objects #4018
|
|
- compilers: bad error message when signature mismatch #4001
|
|
- compilers: infinite loop with -rectypes #3999
|
|
- compilers: contravariance bug in private rows
|
|
- compilers: unsafe cast with polymorphic exception #4002
|
|
- native compiler: bad assembly code generated for AMD64 #4067
|
|
- native compiler: stack alignment problems on MacOSX/i386 #4036
|
|
- stdlib: crash in marshalling #4030
|
|
- stdlib: crash when closing a channel twice #4039
|
|
- stdlib: memory leak in Sys.readdir #4093
|
|
- C interface: better definition of CAMLreturn #4068
|
|
- otherlibs/unix: crash in gethostbyname #3043
|
|
- tools: subtle problem with unset in makefile #4048
|
|
- camlp4: install pa_o_fast.o #3812
|
|
- camlp4: install more modules #3689
|
|
|
|
New features:
|
|
- ocamldoc: name resolution in cross-referencing {!name}: if name is not
|
|
found, then it is searched in the parent module/class, and in the parent
|
|
of the parent, and so on until it is found.
|
|
- ocamldoc: new option -short-functors to use a short form to display
|
|
functors in html generator #4017
|
|
- ocamlprof: added "-version" option
|
|
|
|
|
|
|
|
Objective Caml 3.09.2 (14 Apr 2006):
|
|
------------------------------------
|
|
|
|
Bug fixes:
|
|
- Makefile: problem with "make world.opt" #3954
|
|
- compilers: problem compiling several modules with one command line #3979
|
|
- compilers,ocamldoc: error message that Emacs cannot parse
|
|
- compilers: crash when printing type error #3968
|
|
- compilers: -dtypes wrong for monomorphic type variables #3894
|
|
- compilers: wrong warning on optional arguments #3980
|
|
- compilers: crash when wrong use of type constructor in let rec #3976
|
|
- compilers: better wording of "statement never returns" warning #3889
|
|
- runtime: inefficiency of signal handling #3990
|
|
- runtime: crashes with I/O in multithread programs #3906
|
|
- camlp4: empty file name in error messages #3886
|
|
- camlp4: stack overflow #3948
|
|
- otherlibs/labltk: ocamlbrowser ignores its command line options #3961
|
|
- otherlibs/unix: Unix.times wrong under Mac OS X #3960
|
|
- otherlibs/unix: wrong doc for execvp and execvpe #3973
|
|
- otherlibs/win32unix: random crash in Unix.stat #3998
|
|
- stdlib: update_mod not found under Windows #3847
|
|
- stdlib: Filename.dirname/basename wrong on Win32 #3933
|
|
- stdlib: incomplete documentation of Pervasives.abs #3967
|
|
- stdlib: Printf bugs #3902, #3955
|
|
- tools/checkstack.c: missing include
|
|
- yacc: crash when given argument "-" #3956
|
|
|
|
New features:
|
|
- ported to MacOS X on Intel #3985
|
|
- configure: added support for GNU Hurd #3991
|
|
|
|
Objective Caml 3.09.1 (4 Jan 2006):
|
|
-----------------------------------
|
|
|
|
Bug fixes:
|
|
- compilers: raise not_found with -principal #3855
|
|
- compilers: assert failure in typeclass.cml #3856
|
|
- compilers: assert failure in typing/ctype.ml #3909
|
|
- compilers: fatal error exception Ctype.Unify #3918
|
|
- compilers: spurious warning Y in objects #3868
|
|
- compilers: spurious warning Z on loop index #3907
|
|
- compilers: error message that emacs cannot parse
|
|
- ocamlopt: problems with -for-pack/-pack #3825, #3826, #3919
|
|
- ocamlopt: can't produce shared libraries on x86_64 #3869, #3924
|
|
- ocamlopt: float alignment problem on SPARC #3944
|
|
- ocamlopt: can't compile on MIPS #3936
|
|
- runtime: missing dependence for ld.conf
|
|
- runtime: missing dependence for .depend.nt #3880
|
|
- runtime: memory leak in caml_register_named_value #3940
|
|
- runtime: crash in Marshal.to_buffer #3879
|
|
- stdlib: Sys.time giving wrong results on Mac OS X #3850
|
|
- stdlib: Weak.get_copy causing random crashes in rare cases
|
|
- stdlib, debugger, labltk: use TMPDIR if set #3895
|
|
- stdlib: scanf bug on int32 and nativeint #3932
|
|
- camlp4: mkcamlp4 option parsing problem #3941
|
|
- camlp4: bug in pretty-printing of lazy/assert/new
|
|
- camlp4: update the unmaintained makefile for _loc name
|
|
- ocamldoc: several fixes see ocamldoc/Changes.txt
|
|
- otherlibs/str: bug in long sequences of alternatives #3783
|
|
- otherlibs/systhreads: deadlock in Windows #3910
|
|
- tools: update dumpobj to handle new event format #3873
|
|
- toplevel: activate warning Y in toplevel #3832
|
|
|
|
New features:
|
|
- otherlibs/labltk: browser uses menu bars instead of menu buttons
|
|
|
|
Objective Caml 3.09.0 (27 Oct 2006):
|
|
------------------------------------
|
|
|
|
(Changes that can break existing programs are marked with a "*" )
|
|
|
|
Language features:
|
|
- Introduction of private row types, for abstracting the row in object
|
|
and variant types.
|
|
|
|
Type checking:
|
|
- Polymorphic variants with at most one constructor [< `A of t] are no
|
|
longer systematically promoted to the exact type [`A of t]. This was
|
|
more confusing than useful, and created problems with private row
|
|
types.
|
|
|
|
Both compilers:
|
|
- Added warnings 'Y' and 'Z' for local variables that are bound but
|
|
never used.
|
|
- Added warning for some uses non-returning functions (e.g. raise), when they
|
|
are passed extra arguments, or followed by extra statements.
|
|
- Pattern matching: more prudent compilation in case of guards; fixed #3780.
|
|
- Compilation of classes: reduction in size of generated code.
|
|
- Compilation of "module rec" definitions: fixed a bad interaction with
|
|
structure coercion (to a more restrictive signature).
|
|
|
|
Native-code compiler (ocamlopt):
|
|
* Revised implementation of the -pack option (packing of several compilation
|
|
units into one). The .cmx files that are to be packed with
|
|
"ocamlopt -pack -o P.cmx" must be compiled with "ocamlopt -for-pack P".
|
|
In exchange for this additional constraint, ocamlopt -pack is now
|
|
available on all platforms (no need for binutils).
|
|
* Fixed wrong evaluation order for arguments to certain inlined functions.
|
|
- Modified code generation for "let rec ... and ..." to reduce compilation
|
|
time (which was quadratic in the number of mutually-recursive functions).
|
|
- x86 port: support tail-calls for functions with up to 21 arguments.
|
|
- AMD64 port, Linux: recover from system stack overflow.
|
|
- Sparc port: more portable handling of out-of-bound conditions
|
|
on systems other than Solaris.
|
|
|
|
Standard library:
|
|
- Pervasives: faster implementation of close_in, close_out.
|
|
set_binary_mode_{out,in} now working correctly under Cygwin.
|
|
- Printf: better handling of partial applications of the printf functions.
|
|
- Scanf: new function sscanf_format to read a format from a
|
|
string. The type of the resulting format is dynamically checked and
|
|
should be the type of the template format which is the second argument.
|
|
- Scanf: no more spurious lookahead attempt when the end of file condition
|
|
is set and a correct token has already been read and could be returned.
|
|
|
|
Other libraries:
|
|
- System threads library: added Thread.sigmask; fixed race condition
|
|
in signal handling.
|
|
- Bigarray library: fixed bug in Array3.of_array.
|
|
- Unix library: use canonical signal numbers in results of Unix.wait*;
|
|
hardened Unix.establish_server against EINTR errors.
|
|
|
|
Run-time system:
|
|
- Support platforms where sizeof(void *) = 8 and sizeof(long) = 4.
|
|
- Improved and cleaned up implementation of signal handling.
|
|
|
|
Replay debugger:
|
|
- Improved handling of locations in source code.
|
|
|
|
OCamldoc:
|
|
- extensible {foo } syntax
|
|
- user can give .txt files on the command line, containing ocamldoc formatted
|
|
text, to be able to include bigger texts out of source files
|
|
- -o option is now used by the html generator to indicate the prefix
|
|
of generated index files (to avoid conflict when a Index module exists
|
|
on case-insensitive file systems).
|
|
|
|
Miscellaneous:
|
|
- Configuration information is installed in `ocamlc -where`/Makefile.config
|
|
and can be used by client Makefiles or shell scripts.
|
|
|
|
Objective Caml 3.08.4 (11 Aug 2005):
|
|
------------------------------------
|
|
|
|
New features:
|
|
- configure: find X11 config in some 64-bit Linux distribs
|
|
- ocamldoc: (**/**) can be canceled with another (**/**) #3665
|
|
- graphics: added resize_window
|
|
- graphics: check for invalid arguments to drawing primitives #3595
|
|
- ocamlbrowser: use windows subsystem on mingw
|
|
|
|
Bug fixes:
|
|
- ocamlopt: code generation problem on AMD64 #3640
|
|
- wrong code generated for some classes #3576
|
|
- fatal error when compiling some OO code #3745
|
|
- problem with comparison on constant constructors #3608
|
|
- camlp4: cryptic error message #3592
|
|
- camlp4: line numbers in multi-line antiquotations #3549
|
|
- camlp4: problem with make depend
|
|
- camlp4: parse error with :> #3561
|
|
- camlp4: ident conversion problem with val/contents/contents__
|
|
- camlp4: several small parsing problems #3688
|
|
- ocamldebug: handling of spaces in executable file name #3736
|
|
- emacs-mode: problem when caml-types-buffer is deleted by user #3704
|
|
- ocamldoc: extra backslash in ocamldoc man page #3687
|
|
- ocamldoc: improvements to HTML display #3698
|
|
- ocamldoc: escaping of @ in info files
|
|
- ocamldoc: escaping of . and \ in man pages #3686
|
|
- ocamldoc: better error reporting of misplaced comments
|
|
- graphics: fixed .depend file #3558
|
|
- graphics: segfault with threads and graphics #3651
|
|
- nums: several bugs: #3718, #3719, others
|
|
- nums: inline asm problems with gcc 4.0 #3604, #3637
|
|
- threads: problem with backtrace
|
|
- unix: problem with getaddrinfo #3565
|
|
- stdlib: documentation of Int32.rem and Int64.rem #3573
|
|
- stdlib: documentation of List.rev_map2 #3685
|
|
- stdlib: wrong order in Map.fold #3607
|
|
- stdlib: documentation of maximum float array length #3714
|
|
- better detection of cycles when using -rectypes
|
|
- missing case of module equality #3738
|
|
- better error messages for unbound type variables
|
|
- stack overflow while printing type error message #3705
|
|
- assert failure when typing some classes #3638
|
|
- bug in type_approx
|
|
- better error messages related to type variance checking
|
|
- yacc: avoid name capture for idents of the Parsing module
|
|
|
|
|
|
Objective Caml 3.08.3 (24 Mar 2005):
|
|
------------------------------------
|
|
|
|
New features:
|
|
- support for ocamlopt -pack under Mac OS X (#2634, #3320)
|
|
- ignore unknown warning options for forward and backward compatibility
|
|
- runtime: export caml_compare_unordered (#3479)
|
|
- camlp4: install argl.* files (#3439)
|
|
- ocamldoc: add -man-section option
|
|
- labltk: add the "solid" relief option (#3343)
|
|
|
|
Bug fixes:
|
|
- typing: fix unsoundness in type declaration variance inference.
|
|
Type parameters which are constrained must now have an explicit variant
|
|
annotation, otherwise they are invariant. This is not backward
|
|
compatible, so this might break code which either uses subtyping or
|
|
uses the relaxed value restriction (i.e. was not typable before 3.07)
|
|
- typing: erroneous partial match warning for polymorphic variants (#3424)
|
|
- runtime: handle the case of an empty command line (#3409, #3444)
|
|
- stdlib: make Sys.executable_name an absolute path in native code (#3303)
|
|
- runtime: fix memory leak in finalise.c
|
|
- runtime: auto-trigger compaction even if gc is called manually (#3392)
|
|
- stdlib: fix segfault in Obj.dup on zero-sized values (#3406)
|
|
- camlp4: correct parsing of the $ identifier (#3310, #3469)
|
|
- windows (MS tools): use link /lib instead of lib (#3333)
|
|
- windows (MS tools): change default install destination
|
|
- autoconf: better checking of SSE2 instructions (#3329, #3330)
|
|
- graphics: make close_graph close the X display as well as the window (#3312)
|
|
- num: fix big_int_of_string (empty string) (#3483)
|
|
- num: fix big bug on 64-bit architecture (#3299)
|
|
- str: better documentation of string_match and string_partial_match (#3395)
|
|
- unix: fix file descriptor leak in Unix.accept (#3423)
|
|
- unix: miscellaneous clean-ups
|
|
- unix: fix documentation of Unix.tm (#3341)
|
|
- graphics: fix problem when allocating lots of images under Windows (#3433)
|
|
- compiler: fix error message with -pack when .cmi is missing (#3028)
|
|
- cygwin: fix problem with compilation of camlheader (#3485)
|
|
- stdlib: Filename.basename doesn't return an empty string any more (#3451)
|
|
- stdlib: better documentation of Open_excl flag (#3450)
|
|
- ocamlcp: accept -thread option (#3511)
|
|
- ocamldep: handle spaces in file names (#3370)
|
|
- compiler: remove spurious warning in pattern-matching on variants (#3424)
|
|
- windows: better handling of InterpreterPath registry entry (#3334, #3432)
|
|
|
|
|
|
Objective Caml 3.08.2 (22 Nov 2004):
|
|
------------------------------------
|
|
|
|
Bug fixes:
|
|
- runtime: memory leak when unmarshalling big data structures (#3247)
|
|
- camlp4: incorrect line numbers in errors (#3188)
|
|
- emacs: xemacs-specific code, wrong call to "sit-for"
|
|
- ocamldoc: "Lexing: empty token" (#3173)
|
|
- unix: problem with close_process_* (#3191)
|
|
- unix: possible coredumps (#3252)
|
|
- stdlib: wrong order in Set.fold (#3161)
|
|
- ocamlcp: array out of bounds in profiled programs (#3267)
|
|
- yacc: problem with polymorphic variant types for grammar entries (#3033)
|
|
|
|
Misc:
|
|
- export <caml/printexc.h> for caml_format_exception (#3080)
|
|
- clean up caml_search_exe_in_path (maybe #3079)
|
|
- camlp4: new function "make_lexer" for new-style locations
|
|
- unix: added missing #includes (#3088)
|
|
|
|
|
|
Objective Caml 3.08.1 (19 Aug 2004):
|
|
------------------------------------
|
|
|
|
Licence:
|
|
- The emacs files are now under GPL
|
|
- Slightly relaxed some conditions of the QPL
|
|
|
|
Bug fixes:
|
|
- ld.conf now generated at compile-time instead of install-time
|
|
- fixed -pack on Windows XP (#2935)
|
|
- fixed Obj.tag (#2946)
|
|
- added support for multiple dlopen in Darwin
|
|
- run ranlib when installing camlp4 libraries (#2944)
|
|
- link camlp4opt with -linkall (#2949)
|
|
- camlp4 parsing of patterns now conforms to normal parsing (#3015)
|
|
- install camlp4 *.cmx files (#2955)
|
|
- fixed handling of linefeed in string constants in camlp4 (#3074)
|
|
- ocamldoc: fixed display of class parameters in HTML and LaTeX (#2994)
|
|
- ocamldoc: fixed display of link to class page in html (#2994)
|
|
- Windows toplevel GUI: assorted fixes (including #2932)
|
|
|
|
Misc:
|
|
- added -v option to ocamllex
|
|
- ocamldoc: new -intf and -impl options supported (#3036)
|
|
|
|
Objective Caml 3.08.0 (13 Jul 2004):
|
|
------------------------------------
|
|
|
|
(Changes that can break existing programs are marked with a "*" )
|
|
|
|
Language features:
|
|
- Support for immediate objects, i.e. objects defined without going
|
|
through a class. (Syntax is "object <fields and methods> end".)
|
|
|
|
Type-checking:
|
|
- When typing record construction and record patterns, can omit
|
|
the module qualification on all labels except one. I.e.
|
|
{ M.l1 = ...; l2 = ... } is interpreted as { M.l1 = ...; M.l2 = ... }
|
|
|
|
Both compilers:
|
|
- More compact compilation of classes.
|
|
- Much more efficient handling of class definitions inside functors
|
|
or local modules.
|
|
- Simpler representation for method tables. Objects can now be marshaled
|
|
between identical programs with the flag Marshal.Closures.
|
|
- Improved error messages for objects and variants.
|
|
- Improved printing of inferred module signatures (toplevel and ocamlc -i).
|
|
Recursion between type, class, class type and module definitions is now
|
|
correctly printed.
|
|
- The -pack option now accepts compiled interfaces (.cmi files) in addition
|
|
to compiled implementations (.cmo or .cmx).
|
|
* A compile-time error is signaled if an integer literal exceeds the
|
|
range of representable integers.
|
|
- Fixed code generation error for "module rec" definitions.
|
|
- The combination of options -c -o sets the name of the generated
|
|
.cmi / .cmo / .cmx files.
|
|
|
|
Bytecode compiler:
|
|
- Option -output-obj is now compatible with Dynlink and
|
|
with embedded toplevels.
|
|
|
|
Native-code compiler:
|
|
- Division and modulus by zero correctly raise exception Division_by_zero
|
|
(instead of causing a hardware trap).
|
|
- Improved compilation time for the register allocation phase.
|
|
- The float constant -0.0 was incorrectly treated as +0.0 on some processors.
|
|
- AMD64: fixed bugs in asm glue code for GC invocation and exception raising
|
|
from C.
|
|
- IA64: fixed incorrect code generated for "expr mod 1".
|
|
- PowerPC: minor performance tweaks for the G4 and G5 processors.
|
|
|
|
Standard library:
|
|
* Revised handling of NaN floats in polymorphic comparisons.
|
|
The polymorphic boolean-valued comparisons (=, <, >, etc) now treat
|
|
NaN as uncomparable, as specified by the IEEE standard.
|
|
The 3-valued comparison (compare) treats NaN as equal to itself
|
|
and smaller than all other floats. As a consequence, x == y
|
|
no longer implies x = y but still implies compare x y = 0.
|
|
* String-to-integer conversions now fail if the result overflows
|
|
the range of integers representable in the result type.
|
|
* All array and string access functions now raise
|
|
Invalid_argument("index out of bounds") when a bounds check fails.
|
|
In earlier releases, different exceptions were raised
|
|
in bytecode and native-code.
|
|
- Module Buffer: new functions Buffer.sub, Buffer.nth
|
|
- Module Int32: new functions Int32.bits_of_float, Int32.float_of_bits.
|
|
- Module Map: new functions is_empty, compare, equal.
|
|
- Module Set: new function split.
|
|
* Module Gc: in-order finalisation, new function finalise_release.
|
|
|
|
Other libraries:
|
|
- The Num library: complete reimplementation of the C/asm lowest
|
|
layer to work around potential licensing problems.
|
|
Improved speed on the PowerPC and AMD64 architectures.
|
|
- The Graphics library: improved event handling under MS Windows.
|
|
- The Str library: fixed bug in "split" functions with nullable regexps.
|
|
- The Unix library:
|
|
. Added Unix.single_write.
|
|
. Added support for IPv6.
|
|
. Bug fixes in Unix.closedir.
|
|
. Allow thread switching on Unix.lockf.
|
|
|
|
Runtime System:
|
|
* Name space depollution: all global C identifiers are now prefixed
|
|
with "caml" to avoid name clashes with other libraries. This
|
|
includes the "external" primitives of the standard runtime.
|
|
|
|
Ports:
|
|
- Windows ports: many improvements in the OCamlWin toplevel application
|
|
(history, save inputs to file, etc). Contributed by Christopher A. Watford.
|
|
- Native-code compilation supported for HPPA/Linux. Contributed by Guy Martin.
|
|
- Removed support for MacOS9. Mac OS 9 is obsolete and the port was not
|
|
updated since 3.05.
|
|
- Removed ocamlopt support for HPPA/Nextstep and Power/AIX.
|
|
|
|
Ocamllex:
|
|
- #line directives in the input file are now accepted.
|
|
- Added character set concatenation operator "cset1 # cset2".
|
|
|
|
Ocamlyacc:
|
|
- #line directives in the input file are now accepted.
|
|
|
|
Camlp4:
|
|
* Support for new-style locations (line numbers, not just character numbers).
|
|
- See camlp4/CHANGES and camlp4/ICHANGES for more info.
|
|
|
|
|
|
Objective Caml 3.07 (29 Sep 2003):
|
|
----------------------------------
|
|
|
|
Language features:
|
|
- Experimental support for recursive module definitions
|
|
module rec A : SIGA = StructA and B : SIGB = StructB and ...
|
|
- Support for "private types", or more exactly concrete data types
|
|
with private constructors or labels. These data types can be
|
|
de-structured normally in pattern matchings, but values of these
|
|
types cannot be constructed directly outside of their defining module.
|
|
- Added integer literals of types int32, nativeint, int64
|
|
(written with an 'l', 'n' or 'L' suffix respectively).
|
|
|
|
Type-checking:
|
|
- Allow polymorphic generalization of covariant parts of expansive
|
|
expressions. For instance, if f: unit -> 'a list, "let x = f ()"
|
|
gives "x" the generalized type forall 'a. 'a list, instead of '_a list
|
|
as before.
|
|
- The typing of polymorphic variants in pattern matching has changed.
|
|
It is intended to be more regular, sticking to the principle of "closing
|
|
only the variants which would be otherwise incomplete". Two potential
|
|
consequences: (1) some types may be left open which were closed before,
|
|
and the resulting type might not match the interface anymore (expected to
|
|
be rare); (2) in some cases an incomplete match may be generated.
|
|
- Lots of bug fixes in the handling of polymorphism and recursion inside
|
|
types.
|
|
- Added a new "-dtypes" option to ocamlc/ocamlopt, and an emacs extension
|
|
"emacs/caml-types.el". The compiler option saves inferred type information
|
|
to file *.annot, and the emacs extension allows the user to look at the
|
|
type of any subexpression in the source file. Works even in the case
|
|
of a type error (all the types computed up to the error are available).
|
|
This new feature is also supported by ocamlbrowser.
|
|
- Disable "method is overridden" warning when the method was explicitly
|
|
redefined as virtual beforehand (i.e. not through inheritance). Typing
|
|
and semantics are unchanged.
|
|
|
|
Both compilers:
|
|
- Added option "-dtypes" to dump detailed type information to a file.
|
|
- The "-i" option no longer generates compiled files, it only prints
|
|
the inferred types.
|
|
- The sources for the module named "Mod" can be placed either in Mod.ml or
|
|
in mod.ml.
|
|
- Compilation of "let rec" on non-functional values: tightened some checks,
|
|
relaxed some other checks.
|
|
- Fixed wrong code that was generated for "for i = a to max_int"
|
|
or "for i = a downto min_int".
|
|
- An explicit interface Mod.mli can now be provided for the module obtained
|
|
by ocamlc -pack -o Mod.cmo ... or ocamlopt -pack -o Mod.cmx ...
|
|
- Revised internal handling of source code locations, now handles
|
|
preprocessed code better.
|
|
- Pattern-matching bug on float literals fixed.
|
|
- Minor improvements on pattern-matching over variants.
|
|
- More efficient compilation of string comparisons and the "compare" function.
|
|
- More compact code generated for arrays of constants.
|
|
- Fixed GC bug with mutable record fields of type "exn".
|
|
- Added warning "E" for "fragile patterns": pattern matchings that would
|
|
not be flagged as partial if new constructors were added to the data type.
|
|
|
|
Bytecode compiler:
|
|
- Added option -vmthread to select the threads library with VM-level
|
|
scheduling. The -thread option now selects the system threads library.
|
|
|
|
Native-code compiler:
|
|
- New port: AMD64 (Opteron).
|
|
- Fixed instruction selection bug on expressions of the kind (raise Exn)(arg).
|
|
- Several bug fixes in ocamlopt -pack (tracking of imported modules,
|
|
command line too long).
|
|
- Signal handling bug fixed.
|
|
- x86 port:
|
|
Added -ffast-math option to use inline trigo and log functions.
|
|
Small performance tweaks for the Pentium 4.
|
|
Fixed illegal "imul" instruction generated by reloading phase.
|
|
- Sparc port:
|
|
Enhanced code generation for Sparc V8 (option -march=v8) and
|
|
Sparc V9 (option -march=v9).
|
|
Profiling support added for Solaris.
|
|
- PowerPC port:
|
|
Keep stack 16-aligned for compatibility with C calling conventions.
|
|
|
|
Toplevel interactive system:
|
|
- Tightened interface consistency checks between .cmi files, .cm[oa] files
|
|
loaded by #load, and the running toplevel.
|
|
- #trace on mutually-recursive functions was broken, works again.
|
|
- Look for .ocamlinit file in home directory in addition to the current dir.
|
|
|
|
Standard library:
|
|
- Match_failure and Assert_failure exceptions now report
|
|
(file, line, column), instead of (file, starting char, ending char).
|
|
- float_of_string, int_of_string: some ill-formed input strings were not
|
|
rejected.
|
|
- Added format concatenation, string_of_format, format_of_string.
|
|
- Module Arg: added new option handlers Set_string, Set_int, Set_float,
|
|
Symbol, Tuple.
|
|
- Module Format: tag handling is now turned off by default,
|
|
use [Format.set_tags true] to activate.
|
|
- Modules Lexing and Parsing: added better handling of positions
|
|
in source file. Added function Lexing.flush_input.
|
|
- Module Scanf: %n and %N formats to count characters / items read so far;
|
|
assorted bug fixes, %! to match end of input. New ``_'' special
|
|
flag to skip reresulting value.
|
|
- Module Format: tags are not activated by default.
|
|
- Modules Set and Map: fixed bugs causing trees to become unbalanced.
|
|
- Module Printf: less restrictive typing of kprintf.
|
|
- Module Random: better seeding; functions to generate random int32, int64,
|
|
nativeint; added support for explicit state management.
|
|
- Module Sys: added Sys.readdir for reading the contents of a directory.
|
|
|
|
Runtime system:
|
|
- output_value/input_value: fixed bug with large blocks (>= 4 Mwords)
|
|
produced on a 64-bit platform and incorrectly read back on a 32-bit
|
|
platform.
|
|
- Fixed memory compaction bug involving input_value.
|
|
- Added MacOS X support for dynamic linking of C libraries.
|
|
- Improved stack backtraces on uncaught exceptions.
|
|
- Fixed float alignment problem on Sparc V9 with gcc 3.2.
|
|
|
|
Other libraries:
|
|
- Dynlink:
|
|
By default, dynamically-loaded code now has access to all
|
|
modules defined by the program; new functions Dynlink.allow_only
|
|
and Dynlink.prohibit implement access control.
|
|
Fixed Dynlink problem with files generated with ocamlc -pack.
|
|
Protect against references to modules not yet fully initialized.
|
|
- LablTK/CamlTK: added support for TCL/TK 8.4.
|
|
- Str: reimplemented regexp matching engine, now less buggy, faster,
|
|
and LGPL instead of GPL.
|
|
- Graphics: fixed draw_rect and fill_rect bug under X11.
|
|
- System threads and bytecode threads libraries can be both installed.
|
|
- System threads: better implementation of Thread.exit.
|
|
- Bytecode threads: fixed two library initialization bugs.
|
|
- Unix: make Unix.openfile blocking to account for named pipes;
|
|
GC bug in Unix.*stat fixed; fixed problem with Unix.dup2 on Windows.
|
|
|
|
Ocamllex:
|
|
- Can name parts of the matched input text, e.g.
|
|
"0" (['0'-'7']+ as s) { ... s ... }
|
|
|
|
Ocamldebug:
|
|
- Handle programs that run for more than 2^30 steps.
|
|
|
|
Emacs mode:
|
|
- Added file caml-types.el to interactively display the type information
|
|
saved by option -dtypes.
|
|
|
|
Win32 ports:
|
|
- Cygwin port: recognize \ as directory separator in addition to /
|
|
- MSVC port: ocamlopt -pack works provided GNU binutils are installed.
|
|
- Graphics library: fixed bug in Graphics.blit_image; improved event handling.
|
|
|
|
OCamldoc:
|
|
- new ty_code field for types, to keep code of a type (with option -keep-code)
|
|
- new ex_code field for types, to keep code of an exception
|
|
(with option -keep-code)
|
|
- some fixes in html generation
|
|
- don't overwrite existing style.css file when generating HTML
|
|
- create the ocamldoc.sty file when generating LaTeX (if nonexistent)
|
|
- man pages are now installed in man/man3 rather than man/mano
|
|
- fix: empty [] in generated HTML indexes
|
|
|
|
|
|
Objective Caml 3.06 (20 Aug 2002):
|
|
----------------------------------
|
|
|
|
Type-checking:
|
|
- Apply value restriction to polymorphic record fields.
|
|
|
|
Run-time system:
|
|
- Fixed GC bug affecting lazy values.
|
|
|
|
Both compilers:
|
|
- Added option "-version" to print just the version number.
|
|
- Fixed wrong dependencies in .cmi generated with the -pack option.
|
|
|
|
Native-code compiler:
|
|
- Fixed wrong return value for inline bigarray assignments.
|
|
|
|
Libraries:
|
|
- Unix.getsockopt: make sure result is a valid boolean.
|
|
|
|
Tools:
|
|
- ocamlbrowser: improved error reporting; small Win32 fixes.
|
|
|
|
Windows ports:
|
|
- Fixed two problems with the Mingw port under Cygwin 1.3.
|
|
|
|
|
|
Objective Caml 3.05 (29 Jul 2002):
|
|
----------------------------------
|
|
|
|
Language features:
|
|
- Support for polymorphic methods and record fields.
|
|
- Allows _ separators in integer and float literals, e.g. 1_000_000.
|
|
|
|
Type-checker:
|
|
- New flag -principal to enforce principality of type inference.
|
|
- Fixed subtle typing bug with higher-order functors.
|
|
- Fixed several complexity problems; changed (again) the behaviour of
|
|
simple coercions.
|
|
- Fixed various bugs with objects and polymorphic variants.
|
|
- Improved some error messages.
|
|
|
|
Both compilers:
|
|
- Added option "-pack" to assemble several compilation units as one unit
|
|
having the given units as sub-modules.
|
|
- More precise detection of unused sub-patterns in "or" patterns.
|
|
- Warnings for ill-formed \ escapes in string and character literals.
|
|
- Protect against spaces and other special characters in directory names.
|
|
- Added interface consistency check when building a .cma or .cmxa library.
|
|
- Minor reduction in code size for class initialization code.
|
|
- Added option "-nostdlib" to ignore standard library entirely.
|
|
|
|
Bytecode compiler:
|
|
- Fixed issue with ocamlc.opt and dynamic linking.
|
|
|
|
Native-code compiler:
|
|
- Added link-time check for multiply-defined module names.
|
|
- Fixed GC bug related to constant constructors of polymorphic variant types.
|
|
- Fixed compilation bug for top-level "include" statements.
|
|
- PowerPC port: work around limited range for relative branches,
|
|
thus removing assembler failures on large functions.
|
|
- IA64 port: fixed code generation bug for 3-way constructor matching.
|
|
|
|
Toplevel interactive system:
|
|
- Can load object files given on command line before starting up.
|
|
- ocamlmktop: minimized possibility of name clashes with user-provided modules.
|
|
|
|
Run-time system:
|
|
- Minor garbage collector no longer recursive.
|
|
- Better support for lazy data in the garbage collector.
|
|
- Fixed issues with the heap compactor.
|
|
- Fixed issues with finalized Caml values.
|
|
- The type "int64" is now supported on all platforms: we use software
|
|
emulation if the C compiler doesn't support 64-bit integers.
|
|
- Support for float formats that are neither big-endian nor little-endian
|
|
(one known example: the ARM).
|
|
- Fixed bug in callback*_exn functions in the exception-catching case.
|
|
- Work around gcc 2.96 bug on RedHat 7.2 and Mandrake 8.0, 8.1 among others.
|
|
- Stub DLLs now installed in subdir stublibs/ of standard library dir.
|
|
|
|
Standard library:
|
|
- Protect against integer overflow in sub-string and sub-array bound checks.
|
|
- New module Complex implementing arithmetic over complex numbers.
|
|
- New module Scanf implementing format-based scanning a la scanf() in C.
|
|
- Module Arg: added alternate entry point Arg.parse_argv.
|
|
- Modules Char, Int32, Int64, Nativeint, String: added type "t" and function
|
|
"compare" so that these modules can be used directly with e.g. Set.Make.
|
|
- Module Digest: fixed issue with Digest.file on large files (>= 1Gb);
|
|
added Digest.to_hex.
|
|
- Module Filename: added Filename.open_temp_file to atomically create and
|
|
open the temp file; improved security of Filename.temp_file.
|
|
- Module Genlex: allow _ as first character of an identifier.
|
|
- Module Lazy: more efficient implementation.
|
|
- Module Lexing: improved performances for very large tokens.
|
|
- Module List: faster implementation of sorting functions.
|
|
- Module Printf:
|
|
added %S and %C formats (quoted, escaped strings and characters);
|
|
added kprintf (calls user-specified continuation on formatted string).
|
|
- Module Queue: faster implementation (courtesy of François Pottier).
|
|
- Module Random: added Random.bool.
|
|
- Module Stack: added Stack.is_empty.
|
|
- Module Pervasives:
|
|
added sub-module LargeFile to support files larger than 1Gb
|
|
(file offsets are int64 rather than int);
|
|
opening in "append" mode automatically sets "write" mode;
|
|
files are now opened in close-on-exec mode;
|
|
string_of_float distinguishes its output from a plain integer;
|
|
faster implementation of input_line for long lines.
|
|
- Module Sys:
|
|
added Sys.ocaml_version containing the OCaml version number;
|
|
added Sys.executable_name containing the (exact) path of the
|
|
file being executable;
|
|
Sys.argv.(0) is now unchanged w.r.t. what was provided as 0-th argument
|
|
by the shell.
|
|
- Module Weak: added weak hash tables.
|
|
|
|
Other libraries:
|
|
- Bigarray:
|
|
support for bigarrays of complex numbers;
|
|
added functions Genarray.dims,
|
|
{Genarray,Array1,Array2,Array3}.{kind,layout}.
|
|
- Dynlink: fixed bug with loading of mixed-mode Caml/C libraries.
|
|
- LablTK:
|
|
now supports also the CamlTK API (no labels);
|
|
support for Activate and Deactivate events;
|
|
support for virtual events;
|
|
added UTF conversion;
|
|
export the tcl interpreter as caml value, to avoid DLL dependencies.
|
|
- Unix:
|
|
added sub-module LargeFile to support files larger than 1Gb
|
|
(file offsets are int64 rather than int);
|
|
added POSIX opening flags (O_NOCTTY, O_*SYNC);
|
|
use reentrant functions for gethostbyname and gethostbyaddr when available;
|
|
fixed bug in Unix.close_process and Unix.close_process_full;
|
|
removed some overhead in Unix.select.
|
|
|
|
Tools:
|
|
- ocamldoc (the documentation generator) is now part of the distribution.
|
|
- Debugger: now supports the option -I +dir.
|
|
- ocamllex: supports the same identifiers as ocamlc; warns for
|
|
bad \ escapes in strings and characters.
|
|
- ocamlbrowser:
|
|
recenter the module boxes when showing a cross-reference;
|
|
include the current directory in the ocaml path.
|
|
|
|
Windows port:
|
|
- Can now compile with Mingw (the GNU compilers without the Cygwin
|
|
runtime library) in addition to MSVC.
|
|
- Toplevel GUI: wrong filenames were given to #use and #load commands;
|
|
read_line() was buggy for short lines (2 characters or less).
|
|
- OCamlBrowser: now fully functional.
|
|
- Graphics library: fixed several bugs in event handling.
|
|
- Threads library: fixed preemption bug.
|
|
- Unix library: better handling of the underlying differences between
|
|
sockets and regular file descriptors;
|
|
added Unix.lockf and a better Unix.rename (thanks to Tracy Camp).
|
|
- LablTk library: fixed a bug in Fileinput
|
|
|
|
|
|
Objective Caml 3.04 (13 Dec 2001):
|
|
----------------------------------
|
|
|
|
Type-checker:
|
|
- Allowed coercing self to the type of the current class, avoiding
|
|
an obscure error message about "Self type cannot be unified..."
|
|
|
|
Both compilers:
|
|
- Use OCAMLLIB environment variable to find standard library, falls
|
|
back on CAMLLIB if not defined.
|
|
- Report out-of-range ASCII escapes in character or string literals
|
|
such as "\256".
|
|
|
|
Byte-code compiler:
|
|
- The -use-runtime and -make-runtime flags are back by popular demand
|
|
(same behavior as in 3.02).
|
|
- Dynamic loading (of the C part of mixed Caml/C libraries): arrange that
|
|
linking in -custom mode uses the static libraries for the C parts,
|
|
not the shared libraries, for maximal robustness and compatibility with
|
|
3.02.
|
|
|
|
Native-code compiler:
|
|
- Fixed bug in link-time consistency checking.
|
|
|
|
Tools:
|
|
- ocamlyacc: added parser debugging support (set OCAMLRUNPARAM=p to get
|
|
a trace of the pushdown automaton actions).
|
|
- ocamlcp: was broken in 3.03 (Sys_error), fixed.
|
|
|
|
Run-time system:
|
|
- More work on dynamic loading of the C part of mixed Caml/C libraries.
|
|
- On uncaught exception, flush output channels before printing exception
|
|
message and backtrace.
|
|
- Corrected several errors in exception backtraces.
|
|
|
|
Standard library:
|
|
- Pervasives: integer division and modulus are now fully specified
|
|
on negative arguments (with round-towards-zero semantics).
|
|
- Pervasives.float_of_string: now raises Failure on ill-formed input.
|
|
- Pervasives: added useful float constants max_float, min_float, epsilon_float.
|
|
- printf functions in Printf and Format: added % formats for int32, nativeint,
|
|
int64; "*" in width and precision specifications now supported
|
|
(contributed by Thorsten Ohl).
|
|
- Added Hashtbl.copy, Stack.copy.
|
|
- Hashtbl: revised resizing strategy to avoid quadratic behavior
|
|
on Hashtbl.add.
|
|
- New module MoreLabels providing labelized versions of modules
|
|
Hashtbl, Map and Set.
|
|
- Pervasives.output_value and Marshal.to_* : improved hashing strategy
|
|
for internal data structures, avoid excessive slowness on
|
|
quasi-linearly-allocated inputs.
|
|
|
|
Other libraries:
|
|
- Num: fixed bug in big integer exponentiation (Big_int.power_*).
|
|
|
|
Windows port:
|
|
- New GUI for interactive toplevel (Jacob Navia).
|
|
- The Graphics library is now available for stand-alone executables
|
|
(Jacob Navia).
|
|
- Unix library: improved reporting of system error codes.
|
|
- Fixed error in "globbing" of * and ? patterns on command line.
|
|
|
|
Emacs mode: small fixes; special color highlighting for ocamldoc comments.
|
|
|
|
License: added special exception to the LGPL'ed code (libraries and
|
|
runtime system) allowing unrestricted linking, whether static or dynamic.
|
|
|
|
|
|
Objective Caml 3.03 ALPHA (12 Oct 2001):
|
|
----------------------------------------
|
|
|
|
Language:
|
|
- Removed built-in syntactic sugar for streams and stream patterns
|
|
[< ... >], now supported via CamlP4, which is now included in the
|
|
distribution.
|
|
- Switched the default behaviour to labels mode (labels are compulsory),
|
|
but allows omitting labels when a function application is complete.
|
|
-nolabels mode is available but deprecated for programming.
|
|
(See also scrapelabels and addlabels tools below.)
|
|
- Removed all labels in the standard libraries, except labltk.
|
|
Labelized versions are kept for ArrayLabels, ListLabels, StringLabels
|
|
and UnixLabels. "open StdLabels" gives access to the first three.
|
|
- Extended polymorphic variant type syntax, allowing union types and
|
|
row abbreviations for both sub- and super-types. #t deprecated in types.
|
|
- See the Upgrading file for how to adapt to all the changes above.
|
|
|
|
Type-checker:
|
|
- Fixed obscure bug in module typing causing the type-checker to loop
|
|
on signatures of the form
|
|
module type M
|
|
module A: sig module type T = sig module T: M end end
|
|
module B: A.T
|
|
- Improved efficiency of module type-checking via lazy computation of
|
|
certain signature summary information.
|
|
- An empty polymorphic variant type is now an error.
|
|
|
|
Both compilers:
|
|
- Fixed wrong code generated for "struct include M ... end" when M
|
|
contains one or several "external" declarations.
|
|
|
|
Byte-code compiler:
|
|
- Protect against VM stack overflow caused by module initialization code
|
|
with many local variables.
|
|
- Support for dynamic loading of the C part of mixed Caml/C libraries.
|
|
- Removed the -use-runtime and -make-runtime flags, obsoleted by dynamic
|
|
loading of C libraries.
|
|
|
|
Native-code compiler:
|
|
- Attempt to recover gracefully from system stack overflow. Currently
|
|
works on x86 under Linux and BSD.
|
|
- Alpha: work around "as" bug in Tru64 5.1.
|
|
|
|
Toplevel environment:
|
|
- Revised printing of inferred types and evaluation results
|
|
so that an external printer (e.g. Camlp4's) can be hooked in.
|
|
|
|
Tools:
|
|
- The CamlP4 pre-processor-pretty-printer is now included in the standard
|
|
distribution.
|
|
- New tool ocamlmklib to help build mixed Caml/C libraries.
|
|
- New tool scrapelabels and addlabels, to either remove (non-optional)
|
|
labels in interfaces, or automatically add them in the definitions.
|
|
They provide easy transition from classic mode ocaml 3.02 sources,
|
|
depending on whether you want to keep labels or not.
|
|
- ocamldep: added -pp option to handle preprocessed source files.
|
|
|
|
Run-time system:
|
|
- Support for dynamic loading of the C part of mixed Caml/C libraries.
|
|
Currently works under Linux, FreeBSD, Windows, Tru64, Solaris and Irix.
|
|
- Implemented registration of global C roots with a skip list,
|
|
runs much faster when there are many global C roots.
|
|
- Autoconfiguration script: fixed wrong detection of Mac OS X; problem
|
|
with the Sparc, gcc 3.0, and float alignment fixed.
|
|
|
|
Standard library:
|
|
- Added Pervasives.flush_all to flush all opened output channels.
|
|
|
|
Other libraries:
|
|
- All libraries revised to allow dynamic loading of the C part.
|
|
- Graphics under X Windows: revised event handling, should no longer lose
|
|
mouse events between two calls to wait_next_event(); wait_next_event()
|
|
now interruptible by signals.
|
|
- Bigarrays: fixed bug in marshaling of big arrays.
|
|
|
|
Windows port:
|
|
- Fixed broken Unix.{get,set}sockopt*
|
|
|
|
|
|
|
|
Objective Caml 3.02 (30 Jul 2001):
|
|
----------------------------------
|
|
|
|
Both compilers:
|
|
- Fixed embarrassing bug in pattern-matching compilation
|
|
(affected or-patterns containing variable bindings).
|
|
- More optimizations in pattern-matching compilation.
|
|
|
|
Byte-code compiler:
|
|
- Protect against VM stack overflow caused by functions with many local
|
|
variables.
|
|
|
|
Native-code compiler:
|
|
- Removed re-sharing of string literals, causes too many surprises with
|
|
in-place string modifications.
|
|
- Corrected wrong compilation of toplevel "include" statements.
|
|
- Fixed bug in runtime function "callbackN_exn".
|
|
- Signal handlers receive the conventional signal number as argument
|
|
instead of the system signal number (same behavior as with the
|
|
bytecode compiler).
|
|
- ARM port: fixed issue with immediate operand overflow in large functions.
|
|
|
|
Toplevel environment:
|
|
- User-definer printers (for #install_printer) now receive as first argument
|
|
the pretty-printer formatter where to print their second argument.
|
|
Old printers (with only one argument) still supported for backward
|
|
compatibility.
|
|
|
|
Standard library:
|
|
- Module Hashtbl: added Hashtbl.fold.
|
|
|
|
Other libraries:
|
|
- Dynlink: better error reporting in add_interfaces for missing .cmi files.
|
|
- Graphics: added more drawing functions (multiple points, polygons,
|
|
multiple lines, splines).
|
|
- Bytecode threads: the module Unix is now thread-safe, ThreadUnix is
|
|
deprecated. Unix.exec* now resets standard descriptors to blocking mode.
|
|
- Native threads: fixed a context-switch-during-GC problem causing
|
|
certain C runtime functions to fail, most notably input_value.
|
|
- Unix.inet_addr_of_string: call inet_aton() when available so as to
|
|
handle correctly the address 255.255.255.255.
|
|
- Unix: added more getsockopt and setsockopt functions to get/set
|
|
options that have values other than booleans.
|
|
- Num: added documentation for the Big_int module.
|
|
|
|
Tools:
|
|
- ocamldep: fixed wrong dependency issue with nested modules.
|
|
|
|
Run-time system:
|
|
- Removed floating-point error at start-up on some non-IEEE platforms
|
|
(e.g. FreeBSD prior to 4.0R).
|
|
- Stack backtrace mechanism now works for threads that terminate on
|
|
an uncaught exception.
|
|
|
|
Auto-configuration:
|
|
- Updated config.guess and config.sub scripts, should recognize a greater
|
|
number of recent platform.
|
|
|
|
Windows port:
|
|
- Fixed broken Unix.waitpid. Unix.file_descr can now be compared or hashed.
|
|
- Toplevel application: issue with spaces in name of stdlib directory fixed.
|
|
|
|
MacOS 9 port:
|
|
- Removed the last traces of support for 68k
|
|
|
|
|
|
Objective Caml 3.01 (09 Mar 2001):
|
|
----------------------------------
|
|
|
|
New language features:
|
|
- Variables are allowed in "or" patterns, e.g.
|
|
match l with [t] | [_;t] -> ... t ...
|
|
- "include <structure expression>" to re-export all components of a
|
|
structure inside another structure.
|
|
- Variance annotation on parameters of type declarations, e.g.
|
|
type (+'a,-'b,'c) t (covariant in 'a, contravariant in 'b, invariant in 'c)
|
|
|
|
New ports:
|
|
- Intel IA64/Itanium under Linux (including the native-code compiler).
|
|
- Cygwin under MS Windows. This port is an alternative to the earlier
|
|
Windows port of OCaml, which relied on MS compilers; the Cygwin
|
|
Windows port does not need MS Visual C++ nor MASM, runs faster
|
|
in bytecode, and has a better implementation of the Unix library,
|
|
but currently lacks threads and COM component support.
|
|
|
|
Type-checking:
|
|
- Relaxed "monomorphic restriction" on type constructors in a
|
|
mutually-recursive type definition, e.g. the following is again allowed
|
|
type u = C of int t | D of string t and 'a t = ...
|
|
- Fixed name-capture bug in "include SIG" and "SIG with ..." constructs.
|
|
- Improved implicit subtypes built by (... :> ty), closer to intuition.
|
|
- Several bug fixes in type-checking of variants.
|
|
- Typing of polymorphic variants is more restrictive:
|
|
do not allow conjunctive types inside the same pattern matching.
|
|
a type has either an upper bound, or all its tags are in the lower bound.
|
|
This may break some programs (this breaks lablgl-0.94).
|
|
|
|
Both compilers:
|
|
- Revised compilation of pattern matching.
|
|
- Option -I +<subdir> to search a subdirectory <subdir> of the standard
|
|
library directory (i.e. write "ocamlc -I +labltk" instead of
|
|
"ocamlc -I /usr/local/lib/ocaml/labltk").
|
|
- Option -warn-error to turn warnings into errors.
|
|
- Option -where to print the location of the standard library directory.
|
|
- Assertions are now type-checked even if the -noassert option is given,
|
|
thus -noassert can no longer change the types of modules.
|
|
|
|
Bytecode compiler and bytecode interpreter:
|
|
- Print stack backtrace when a program aborts due to an uncaught exception
|
|
(requires compilation with -g and running with ocamlrun -b or
|
|
OCAMLRUNPARAM="b=1").
|
|
|
|
Native-code compiler:
|
|
- Better unboxing optimizations on the int32, int64, and nativeint types.
|
|
- Tail recursion preserved for functions having more parameters than
|
|
available registers (but tail calls to other functions are still
|
|
turned off if parameters do not fit entirely in registers).
|
|
- Fixed name-capture bug in function inlining.
|
|
- Improved spilling/reloading strategy for conditionals.
|
|
- IA32, Alpha: better alignment of branch targets.
|
|
- Removed spurious dependency on the -lcurses library.
|
|
|
|
Toplevel environment:
|
|
- Revised handling of top-level value definitions, allows reclamation
|
|
of definitions that are shadowed by later definitions with the same names.
|
|
(E.g. "let x = <big list>;; let x = 1;;" allows <big list> to be reclaimed.)
|
|
- Revised the tracing facility so that for standard library functions,
|
|
only calls from user code are traced, not calls from the system.
|
|
- Added a "*" prompt when within a comment.
|
|
|
|
Runtime system:
|
|
- Fixed portability issue on bcopy() vs memmove(), affecting Linux RedHat 7.0
|
|
in particular.
|
|
- Structural comparisons (=, <>, <, <=, >, >=, compare) reimplemented
|
|
so as to avoid overflowing the C stack.
|
|
- Input/output functions: arrange so that reads and writes on closed
|
|
in_channel or out_channel raise Sys_error immediately.
|
|
|
|
Standard library:
|
|
- Module Gc: changed some counters to float in order to avoid overflow;
|
|
added alarms
|
|
- Module Hashtbl: added Hashtbl.replace.
|
|
- Module Int64: added bits_of_float, float_of_bits (access to IEEE 754
|
|
representation of floats).
|
|
- Module List: List.partition now tail-rec;
|
|
improved memory behavior of List.stable_sort.
|
|
- Module Nativeint: added Nativeint.size (number of bits in a nativeint).
|
|
- Module Obj: fixed incorrect resizing of float arrays in Obj.resize.
|
|
- Module Pervasives: added float constants "infinity", "neg_infinity", "nan";
|
|
added a "classify_float" function to test a float for NaN, infinity, etc.
|
|
- Pervasives.input_value: fixed bug affecting shared custom objects.
|
|
- Pervasives.output_value: fixed size bug affecting "int64" values.
|
|
- Pervasives.int_of_string, {Int32,Int64,Nativeint}.of_string:
|
|
fixed bug causing bad digits to be accepted without error.
|
|
- Module Random: added get_state and set_state to checkpoint the generator.
|
|
- Module Sys: signal handling functions are passed the system-independent
|
|
signal number rather than the raw system signal number whenever possible.
|
|
- Module Weak: added Weak.get_copy.
|
|
|
|
Other libraries:
|
|
- Bigarray: added Bigarray.reshape to take a view of the elements of a
|
|
bigarray with different dimensions or number of dimensions;
|
|
fixed bug causing "get" operations to be unavailable in custom
|
|
toplevels including Bigarray.
|
|
- Dynlink: raise an error instead of crashing when the loaded module
|
|
refers to the not-yet-initialized module performing a dynlink operation.
|
|
- Bytecode threads: added a thread-safe version of the Marshal module;
|
|
fixed a rare GC bug in the thread scheduler.
|
|
- POSIX threads: fixed compilation problem with threads.cmxa.
|
|
- Both thread libraries: better tail-recursion in Event.sync.
|
|
- Num library: fixed bug in square roots (Nat.sqrt_nat, Big_int.sqrt_big_int).
|
|
|
|
Tools:
|
|
- ocamldep: fixed missing dependencies on labels of record patterns and
|
|
record construction operations
|
|
|
|
Win32 port:
|
|
- Unix.waitpid now implements the WNOHANG option.
|
|
|
|
Mac OS ports:
|
|
- Mac OS X public beta is supported.
|
|
- Int64.format works on Mac OS 8/9.
|
|
|
|
|
|
Objective Caml 3.00 (25 Apr 2000):
|
|
----------------------------------
|
|
|
|
Language:
|
|
- OCaml/OLabl merger:
|
|
* Support for labeled and optional arguments for functions and classes.
|
|
* Support for variant types (sum types compared by structure).
|
|
See tutorial (chapter 2 of the OCaml manual) for more information.
|
|
- Syntactic change: "?" in stream error handlers changed to "??".
|
|
- Added exception renaming in structures (exception E = F).
|
|
- (OCaml 2.99/OLabl users only) Label syntax changed to preserve
|
|
backward compatibility with 2.0x (labeled function application
|
|
is f ~lbl:arg instead of f lbl:arg). A tool is provided to help
|
|
convert labelized programs to OCaml 3.00.
|
|
|
|
Both compilers:
|
|
- Option -labels to select commuting label mode (labels are mandatory,
|
|
but labeled arguments can be passed in a different order than in
|
|
the definition of the function; in default mode, labels may be omitted,
|
|
but argument reordering is only allowed for optional arguments).
|
|
- Libraries (.cma and .cmxa files) now "remember" C libraries given
|
|
at library construction time, and add them back at link time.
|
|
Allows linking with e.g. just unix.cma instead of
|
|
unix.cma -custom -cclib -lunix
|
|
- Revised printing of error messages, now use Format.fprintf; no visible
|
|
difference for users, but could facilitate internationalization later.
|
|
- Fixed bug in unboxing of records containing only floats.
|
|
- Fixed typing bug involving applicative functors as components of modules.
|
|
- Better error message for inconsistencies between compiled interfaces.
|
|
|
|
Bytecode compiler:
|
|
- New "modular" format for bytecode executables; no visible differences
|
|
for users, but will facilitate further extensions later.
|
|
- Fixed problems in signal handling.
|
|
|
|
Native-code compiler:
|
|
- Profiling support on x86 under FreeBSD
|
|
- Open-coding and unboxing optimizations for the new integer types
|
|
int32, int64, nativeint, and for bigarrays.
|
|
- Fixed instruction selection bug with "raise" appearing in arguments
|
|
of strict operators, e.g. "1 + raise E".
|
|
- Better error message when linking incomplete/incorrectly ordered set
|
|
of .cmx files.
|
|
- Optimized scanning of global roots during GC, can reduce total running
|
|
time by up to 8% on GC-intensive programs.
|
|
|
|
Interactive toplevel:
|
|
- Better printing of exceptions, including arguments, when possible.
|
|
- Fixed rare GC bug occurring during interpretation of scripts.
|
|
- Added consistency checks between interfaces and implementations
|
|
during #load.
|
|
|
|
Run-time system:
|
|
- Added support for "custom" heap blocks (heap blocks carrying
|
|
C functions for finalization, comparison, hashing, serialization
|
|
and deserialization).
|
|
- Support for finalisation functions written in Caml.
|
|
|
|
Standard library:
|
|
- New modules Int32, Int64, Nativeint for 32-bit, 64-bit and
|
|
platform-native integers
|
|
- Module Array: added Array.sort, Array.stable_sort.
|
|
- Module Gc: added Gc.finalise to attach Caml finalisation functions to
|
|
arbitrary heap-allocated data.
|
|
- Module Hashtbl: do not bomb when resizing very large table.
|
|
- Module Lazy: raise Lazy.Undefined when a lazy evaluation needs itself.
|
|
- Module List: added List.sort, List.stable_sort; fixed bug in List.rev_map2.
|
|
- Module Map: added mapi (iteration with key and data).
|
|
- Module Set: added iterators for_all, exists, filter, partition.
|
|
- Module Sort: still here but deprecated in favor of new sorting functions
|
|
in Array and List.
|
|
- Module Stack: added Stack.top
|
|
- Module String: fixed boundary condition on String.rindex_from
|
|
- Added labels on function arguments where appropriate.
|
|
|
|
New libraries and tools:
|
|
- ocamlbrowser: graphical browser for OCaml sources and compiled interfaces,
|
|
supports cross-referencing, editing, running the toplevel.
|
|
- LablTK: GUI toolkit based on TK, using labeled and optional arguments,
|
|
easier to use than CamlTK.
|
|
- Bigarray: large, multi-dimensional numerical arrays, facilitate
|
|
interfacing with C/Fortran numerical code, efficient support for
|
|
advanced array operations such as slicing and memory-mapping of files.
|
|
|
|
Other libraries:
|
|
- Bytecode threads: timer-based preemption was broken, works back again;
|
|
fixed bug in Pervasives.input_line; exported Thread.yield.
|
|
- System threads: several GC / reentrancy bugs fixed in buffered I/O
|
|
and Unix I/O; revised Thread.join implementation for strict POSIX
|
|
conformance; exported Thread.yield.
|
|
- Graphics: added support for double buffering; added, current_x, current_y,
|
|
rmoveto, rlineto, and draw_rect.
|
|
- Num: fixed bug in Num.float_of_num.
|
|
- Str: worked around potential symbol conflicts with C standard library.
|
|
- Dbm: fixed bug with Dbm.iter on empty database.
|
|
|
|
New or updated ports:
|
|
- Alpha/Digital Unix: lifted 256M limitation on total memory space
|
|
induced by -taso
|
|
- Port to AIX 4.3 on PowerPC
|
|
- Port to HPUX 10 on HPPA
|
|
- Deprecated 680x0 / SunOS port
|
|
|
|
Macintosh port:
|
|
- Implemented the Unix and Thread libraries.
|
|
- The toplevel application does not work on 68k Macintoshes; maybe
|
|
later if there's a demand.
|
|
- Added a new tool, ocamlmkappli, to build an application from a
|
|
program written in O'Caml.
|
|
|
|
|
|
Objective Caml 2.04 (26 Nov 1999):
|
|
----------------------------------
|
|
|
|
- C interface: corrected inconsistent change in the CAMLparam* macros.
|
|
- Fixed internal error in ocamlc -g.
|
|
- Fixed type-checking of "S with ...", where S is a module type name
|
|
abbreviating another module type name.
|
|
- ocamldep: fixed stdout/stderr mismatch after failing on one file.
|
|
- Random.self_init more random.
|
|
- Windows port:
|
|
- Toplevel application: fixed spurious crash on exit.
|
|
- Native-code compiler: fixed bug in assembling certain
|
|
floating-point constants (masm doesn't grok 2e5, wants 2.0e5).
|
|
|
|
Objective Caml 2.03 (19 Nov 1999):
|
|
----------------------------------
|
|
|
|
New ports:
|
|
- Ported to BeOS / Intel x86 (bytecode and native-code).
|
|
- BSD / Intel x86 port now supports both a.out and ELF binary formats.
|
|
- Added support for {Net,Open}BSD / Alpha.
|
|
- Revamped Rhapsody port, now works on MacOS X server.
|
|
|
|
Syntax:
|
|
- Warning for "(*)" and "*)" outside comment.
|
|
- Removed "#line LINENO", too ambiguous with a method invocation;
|
|
the equivalent "# LINENO" is still supported.
|
|
|
|
Typing:
|
|
- When an incomplete pattern-matching is detected, report also a
|
|
value or value template that is not covered by the cases of
|
|
the pattern-matching.
|
|
- Several bugs in class type matching and in type error reporting fixed.
|
|
- Added an option -rectypes to support general recursive types,
|
|
not just those involving object types.
|
|
|
|
Bytecode compiler:
|
|
- Minor cleanups in the bytecode emitter.
|
|
- Do not remove "let x = y" bindings in -g mode; makes it easier to
|
|
debug the code.
|
|
|
|
Native-code compiler:
|
|
- Fixed bug in grouping of allocations performed in the same basic block.
|
|
- Fixed bug in constant propagation involving expressions containing
|
|
side-effects.
|
|
- Fixed incorrect code generation for "for" loops whose upper bound is
|
|
a reference assigned inside the loop.
|
|
- MIPS code generator: work around a bug in the IRIX 6 assembler.
|
|
|
|
Toplevel:
|
|
- Fixed incorrect redirection of standard formatter to stderr
|
|
while executing toplevel scripts.
|
|
|
|
Standard library:
|
|
- Added List.rev_map, List.rev_map2.
|
|
- Documentation of List functions now says which functions are
|
|
tail-rec, and how much stack space is needed for non-tailrec functions.
|
|
- Wrong type for Printf.bprintf fixed.
|
|
- Fixed weird behavior of Printf.sprintf and Printf.bprintf in case of
|
|
partial applications.
|
|
- Added Random.self_init, which initializes the PRNG from the system date.
|
|
- Sort.array: serious bugs fixed.
|
|
- Stream.count: fixed incorrect behavior with ocamlopt.
|
|
|
|
Run-time system and external interface:
|
|
- Fixed weird behavior of signal handlers w.r.t. signal masks and exceptions
|
|
raised from the signal handler.
|
|
- Fixed bug in the callback*_exn() functions.
|
|
|
|
Debugger:
|
|
- Fixed wrong printing of float record fields and elements of float arrays.
|
|
- Supports identifiers starting with '_'.
|
|
|
|
Profiler:
|
|
- Handles .mli files, so ocamlcp can be used to replace ocamlc (e.g. in a
|
|
makefile).
|
|
- Now works on programs that use stream expressions and stream parsers.
|
|
|
|
Other libraries:
|
|
- Graphics: under X11, treat all mouse buttons equally; fixed problem
|
|
with current font reverting to the default font when the graphics
|
|
window is resized.
|
|
- Str: fixed reentrancy bugs in Str.replace and Str.full_split.
|
|
- Bytecode threads: set standard I/O descriptors to non-blocking mode.
|
|
- OS threads: revised implementation of Thread.wait_signal.
|
|
- All threads: added Event.wrap_abort, Event.choose [].
|
|
- Unix.localtime, Unix.gmtime: check for errors.
|
|
- Unix.create_process: now supports arbitrary redirections of std descriptors.
|
|
- Added Unix.open_process_full.
|
|
- Implemented Unix.chmod under Windows.
|
|
- Big_int.square_big_int now gives the proper sign to its result.
|
|
|
|
Others:
|
|
- ocamldep: don't stop at first error, skip to next file.
|
|
- Emacs mode: updated with Garrigue and Zimmerman's snapshot of 1999/10/18.
|
|
- configure script: added -prefix option.
|
|
- Windows toplevel application: fixed problem with graphics library
|
|
not loading properly.
|
|
|
|
|
|
Objective Caml 2.02 (04 Mar 1999):
|
|
----------------------------------
|
|
|
|
* Type system:
|
|
- Check that all components of a signature have unique names.
|
|
- Fixed bug in signature matching involving a type component and
|
|
a module component, both sharing an abstract type.
|
|
- Bug involving recursive classes constrained by a class type fixed.
|
|
- Fixed bugs in printing class types and in printing unification errors.
|
|
|
|
* Compilation:
|
|
- Changed compilation scheme for "{r with lbl = e}" when r has many fields
|
|
so as to avoid code size explosion.
|
|
|
|
* Native-code compiler:
|
|
- Better constant propagation in boolean expressions and in conditionals.
|
|
- Removal of unused arguments during function inlining.
|
|
- Eliminated redundant tagging/untagging in bit shifts.
|
|
- Static allocation of closures for functions without free variables,
|
|
reduces the size of initialization code.
|
|
- Revised compilation scheme for definitions at top level of compilation
|
|
units, so that top level functions have no free variables.
|
|
- Coalesced multiple allocations of heap blocks inside one expression
|
|
(e.g. x :: y :: z allocates the two conses in one step).
|
|
- Ix86: better handling of large integer constants in instruction selection.
|
|
- MIPS: fixed wrong asm generated for String.length "literal".
|
|
|
|
* Standard library:
|
|
- Added the "ignore" primitive function, which just throws away its
|
|
argument and returns "()". It allows to write
|
|
"ignore(f x); y" if "f x" doesn't have type unit and you don't
|
|
want the warning caused by "f x; y".
|
|
- Added the "Buffer" module (extensible string buffers).
|
|
- Module Format: added formatting to buffers and to strings.
|
|
- Added "mem" functions (membership test) to Hashtbl and Map.
|
|
- Module List: added find, filter, partition.
|
|
Renamed remove and removeq to remove_assoc and remove_assq.
|
|
- Module Marshal: fixed bug in marshaling functions when passed functional
|
|
values defined by mutual recursion with other functions.
|
|
- Module Printf: added Printf.bprintf (print to extensible buffer);
|
|
added %i format as synonymous for %d (as per the docs).
|
|
- Module Sort: added Sort.array (Quicksort).
|
|
|
|
* Runtime system:
|
|
- New callback functions for callbacks with arbitrary many arguments
|
|
and for catching Caml exceptions escaping from a callback.
|
|
|
|
* The ocamldep dependency generator: now performs full parsing of the
|
|
sources, taking into account the scope of module bindings.
|
|
|
|
* The ocamlyacc parser generator: fixed sentinel error causing wrong
|
|
tables to be generated in some cases.
|
|
|
|
* The str library:
|
|
- Added split_delim, full_split as variants of split that control
|
|
more precisely what happens to delimiters.
|
|
- Added replace_matched for separate matching and replacement operations.
|
|
|
|
* The graphics library:
|
|
- Bypass color lookup for 16 bpp and 32 bpp direct-color displays.
|
|
- Larger color cache.
|
|
|
|
* The thread library:
|
|
- Bytecode threads: more clever use of non-blocking I/O, makes I/O
|
|
operations faster.
|
|
- POSIX threads: gcc-ism removed, should now compile on any ANSI C compiler.
|
|
- Both: avoid memory leak in the Event module when a communication
|
|
offer is never selected.
|
|
|
|
* The Unix library:
|
|
- Fixed inversion of ctime and mtime in Unix.stat, Unix.fstat, Unix.lstat.
|
|
- Unix.establish_connection: properly reclaim socket if connect fails.
|
|
|
|
* The DBM library: no longer crashes when calling Dbm.close twice.
|
|
|
|
* Emacs mode:
|
|
- Updated with Garrigue and Zimmerman's latest version.
|
|
- Now include an "ocamltags" script for using etags on OCaml sources.
|
|
|
|
* Win32 port:
|
|
- Fixed end-of-line bug in ocamlcp causing problems with generated sources.
|
|
|
|
|
|
Objective Caml 2.01 (09 Dec 1998):
|
|
----------------------------------
|
|
|
|
* Typing:
|
|
- Added warning for expressions of the form "a; b" where a does not have
|
|
type "unit"; catches silly mistake such as
|
|
"record.lbl = newval; ..." instead of "record.lbl <- newval; ...".
|
|
- Typing bug in "let module" fixed.
|
|
|
|
* Compilation:
|
|
- Fixed bug in compilation of recursive and mutually recursive classes.
|
|
- Option -w to turn specific warnings on/off.
|
|
- Option -cc to choose the C compiler used with ocamlc -custom and ocamlopt.
|
|
|
|
* Bytecode compiler and bytecode interpreter:
|
|
- Intel x86: removed asm declaration causing "fixed or forbidden register
|
|
spilled" error with egcs and gcc 2.8 (but not with gcc 2.7, go figure).
|
|
- Revised handling of debugging information, allows faster linking with -g.
|
|
|
|
* Native-code compiler:
|
|
- Fixed bugs in integer constant propagation.
|
|
- Out-of-bound accesses in array and strings now raise an Invalid_argument
|
|
exception (like the bytecode system) instead of stopping the program.
|
|
- Corrected scheduling of bound checks.
|
|
- Port to the StrongARM under Linux (e.g. Corel Netwinder).
|
|
- I386: fixed bug in profiled code (ocamlopt -p).
|
|
- Mips: switched to -n32 model under IRIX; dropped the Ultrix port.
|
|
- Sparc: simplified the addressing modes, allows for better scheduling.
|
|
- Fixed calling convention bug for Pervasives.modf.
|
|
|
|
* Toplevel:
|
|
- #trace works again.
|
|
- ocamlmktop: use matching ocamlc, not any ocamlc from the search path.
|
|
|
|
* Memory management:
|
|
- Fixed bug in heap expansion that could cause the GC to loop.
|
|
|
|
* C interface:
|
|
- New macros CAMLparam... and CAMLlocal... to simplify the handling
|
|
of local roots in C code.
|
|
- Simplified procedure for allocating and filling Caml blocks from C.
|
|
- Declaration of string_length in <caml/mlvalues.h>.
|
|
|
|
* Standard library:
|
|
- Module Format: added {get,set}_all_formatter_output_functions,
|
|
formatter_of_out_channel, and the control sequence @<n> in printf.
|
|
- Module List: added mem_assoc, mem_assq, remove, removeq.
|
|
- Module Pervasives: added float_of_int (synonymous for float),
|
|
int_of_float (truncate), int_of_char (Char.code), char_of_int (Char.chr),
|
|
bool_of_string.
|
|
- Module String: added contains, contains_from, rcontains_from.
|
|
|
|
* Unix library:
|
|
- Unix.lockf: added F_RLOCK, F_TRLOCK; use POSIX locks whenever available.
|
|
- Unix.tc{get,set}attr: added non-standard speeds 57600, 115200, 230400.
|
|
- Unix.chroot: added.
|
|
|
|
* Threads:
|
|
- Bytecode threads: improved speed of I/O scheduling.
|
|
- Native threads: fixed a bug involving signals and exceptions
|
|
generated from C.
|
|
|
|
* The "str" library:
|
|
- Added Str.string_partial_match.
|
|
- Bumped size of internal stack.
|
|
|
|
* ocamlyacc: emit correct '# lineno' directive for prelude part of .mly file.
|
|
|
|
* Emacs editing mode: updated with Jacques Garrigue's newest code.
|
|
|
|
* Windows port:
|
|
- Added support for the "-cclib -lfoo" option (instead of
|
|
-cclib /full/path/libfoo.lib as before).
|
|
- Threads: fixed a bug at initialization time.
|
|
|
|
* Macintosh port: source code for Macintosh application merged in.
|
|
|
|
|
|
Objective Caml 2.00 (19 Aug 1998):
|
|
----------------------------------
|
|
|
|
* Language:
|
|
- New class language. See http://caml.inria.fr/ocaml/refman/
|
|
for a tutorial (chapter 2) and for the reference manual (section 4.9).
|
|
- Local module definitions "let module X = <module-expr> in <expr>".
|
|
- Record copying with update "{r with lbl1 = expr1; ...}".
|
|
- Array patterns "[|pat1; ...;patN|]" in pattern-matchings.
|
|
- New reserved keywords: "object", "initializer".
|
|
- No longer reserved: "closed", "protected".
|
|
|
|
* Bytecode compiler:
|
|
- Use the same compact memory representations for float arrays, float
|
|
records and recursive closures as the native-code compiler.
|
|
- More type-dependent optimizations.
|
|
- Added the -use_runtime and -make_runtime flags to build separately
|
|
and reuse afterwards custom runtime systems
|
|
(inspired by Fabrice Le Fessant's patch).
|
|
|
|
* Native-code compiler:
|
|
- Cross-module constant propagation of integer constants.
|
|
- More type-dependent optimizations.
|
|
- More compact code generated for "let rec" over data structures.
|
|
- Better code generated for "for" loops (test at bottom of code).
|
|
- More aggressive scheduling of stores.
|
|
- Added -p option for time profiling with gprof
|
|
(fully supported on Intel x86/Linux and Alpha/Digital Unix only)
|
|
(inspired by Aleksey Nogin's patch).
|
|
- A case of bad spilling with high register pressure fixed.
|
|
- Fixed GC bug when GC called from C without active Caml code.
|
|
- Alpha: $gp handling revised to follow Alpha's standard conventions,
|
|
allow running "atom" and "pixie" on ocamlopt-generated binaries.
|
|
- Intel x86: use movzbl and movsbl systematically to load 8-bit and 16-bit
|
|
quantities, no more hacks with partial registers (better for the
|
|
Pentium Pro, worse for the Pentium).
|
|
- PowerPC: more aggressive scheduling of return address reloading.
|
|
- Sparc: scheduling bug related to register pairs fixed.
|
|
|
|
* Runtime system:
|
|
- Better printing of uncaught exceptions (print a fully qualified
|
|
name whenever possible).
|
|
|
|
* New ports:
|
|
- Cray T3E (bytecode only) (in collaboration with CEA).
|
|
- PowerMac under Rhapsody.
|
|
- SparcStations under Linux.
|
|
|
|
* Standard library:
|
|
- Added set_binary_mode_in and set_binary_mode_out in Pervasives
|
|
to toggle open channels between text and binary modes.
|
|
- output_value and input_value check that the given channel is in
|
|
binary mode.
|
|
- input_value no longer fails on very large marshalled data (> 16 Mbytes).
|
|
- Module Arg: added option Rest.
|
|
- Module Filename: temp_file no longer loops if temp dir doesn't exist.
|
|
- Module List: added rev_append (tail-rec alternative to @).
|
|
- Module Set: tell the truth about "elements" returning a sorted list;
|
|
added min_elt, max_elt, singleton.
|
|
- Module Sys: added Sys.time for simple measuring of CPU time.
|
|
|
|
* ocamllex:
|
|
- Check for overflow when generating the tables for the automaton.
|
|
- Error messages in generated .ml file now point to .mll source.
|
|
- Added "let <id> = <regexp>" to name regular expressions
|
|
(inspired by Christian Lindig's patch).
|
|
|
|
* ocamlyacc:
|
|
- Better error recovery in presence of EOF tokens.
|
|
- Error messages in generated .ml file now point to .mly source.
|
|
- Generated .ml file now type-safe even without the generated .mli file.
|
|
|
|
* The Unix library:
|
|
- Use float instead of int to represent Unix times (number of seconds
|
|
from the epoch). This fixes a year 2005 problem on 32-bit platforms.
|
|
Functions affected: stat, lstat, fstat, time, gmtime, localtime,
|
|
mktime, utimes.
|
|
- Added putenv.
|
|
- Better handling of "unknown" error codes (EUNKNOWNERR).
|
|
- Fixed endianness bug in getservbyport.
|
|
- win32unix (the Win32 implementation of the Unix library) now has
|
|
the same interface as the unix implementation, this allows exchange
|
|
of compiled .cmo and .cmi files between Unix and Win32.
|
|
|
|
* The thread libraries:
|
|
- Bytecode threads: bug with escaping exceptions fixed.
|
|
- System threads (POSIX, Win32): malloc/free bug fixed; signal bug fixed.
|
|
- Both: added Thread.wait_signal to wait synchronously for signals.
|
|
|
|
* The graph library: bigger color cache.
|
|
|
|
* The str library: added Str.quote, Str.regexp_string,
|
|
Str.regexp_string_case_fold.
|
|
|
|
* Emacs mode:
|
|
- Fixed bug with paragraph fill.
|
|
- Fixed bug with next-error under Emacs 20.
|
|
|
|
|
|
Objective Caml 1.07 (11 Dec 1997):
|
|
----------------------------------
|
|
|
|
* Native-code compiler:
|
|
- Revised interface between generated code and GC, fixes serious GC
|
|
problems with signals and native threads.
|
|
- Added "-thread" option for compatibility with ocamlc.
|
|
|
|
* Debugger: correctly print instance variables of objects.
|
|
|
|
* Run-time system: ported to OpenBSD.
|
|
|
|
* Standard library: fixed wrong interface for Marshal.to_buffer and
|
|
Obj.unmarshal.
|
|
|
|
* Num library: added Intel x86 optimized asm code (courtesy of
|
|
Bernard Serpette).
|
|
|
|
* Thread libraries:
|
|
- Native threads: fixed GC bugs and installation procedure.
|
|
- Bytecode threads: fixed problem with "Marshal" module.
|
|
- Both: added Event.always.
|
|
|
|
* MS Windows port: better handling of long command lines in Sys.command
|
|
|
|
Objective Caml 1.06 (18 Nov 1997):
|
|
----------------------------------
|
|
|
|
* Language:
|
|
- Added two new keywords: "assert" (check assertion) and "lazy"
|
|
(delay evaluation).
|
|
- Allow identifiers to start with "_" (such identifiers are treated
|
|
as lowercase idents).
|
|
|
|
* Objects:
|
|
- Added "protected" methods (visible only from subclasses, can be hidden
|
|
in class type declared in module signature).
|
|
- Objects can be compared using generic comparison functions.
|
|
- Fixed compilation of partial application of object constructors.
|
|
|
|
* Type system:
|
|
- Occur-check now more strict (all recursions must traverse an object).
|
|
- A few bugs fixed.
|
|
|
|
* Run-time system:
|
|
- A heap compactor was implemented, so long-running programs can now
|
|
fight fragmentation.
|
|
- The meaning of the "space_overhead" parameter has changed.
|
|
- The macros Push_roots and Pop_roots are superseded by Begin_roots* and
|
|
End_roots.
|
|
- Bytecode executable includes list of primitives used, avoids crashes
|
|
on version mismatch.
|
|
- Reduced startup overhead for marshalling, much faster marshalling of
|
|
small objects.
|
|
- New exception Stack_overflow distinct from Out_of_memory.
|
|
- Maximum stack size configurable.
|
|
- I/O revised for compatibility with compactor and with native threads.
|
|
- All C code ANSIfied (new-style function declarations, etc).
|
|
- Threaded code work on all 64-bit processors, not just Alpha/Digital Unix.
|
|
- Better printing of uncaught exceptions.
|
|
|
|
* Both compilers:
|
|
- Parsing: more detailed reporting of syntax errors (e.g. shows
|
|
unmatched opening parenthesis on missing closing parenthesis).
|
|
- Check consistency between interfaces (.cmi).
|
|
- Revised rules for determining dependencies between modules.
|
|
- Options "-verbose" for printing calls to C compiler, "-noassert"
|
|
for turning assertion checks off.
|
|
|
|
* Native-code compiler:
|
|
- Machine-dependent parts rewritten using inheritance instead of
|
|
parameterized modules.
|
|
- GC bug in value let rec fixed.
|
|
- Port to Linux/Alpha.
|
|
- Sparc: cleaned up use of %g registers, now compatible with Solaris threads.
|
|
|
|
* Top-level interactive system:
|
|
- Can execute Caml script files given on command line.
|
|
- Reads commands from ./.ocamlinit on startup.
|
|
- Now thread-compatible.
|
|
|
|
* Standard library:
|
|
- New library module: Lazy (delayed computations).
|
|
- New library module: Marshal. Allows marshalling to strings and
|
|
transmission of closures between identical programs (SPMD parallelism).
|
|
- Filename: "is_absolute" is superseded by "is_implicit" and "is_relative".
|
|
To adapt old programs, change "is_absolute x" to "not (is_implicit x)"
|
|
(but the new "is_relative" is NOT the opposite of the old "is_absolute").
|
|
- Array, Hashtbl, List, Map, Queue, Set, Stack, Stream:
|
|
the "iter" functions now take as argument a unit-returning function.
|
|
- Format: added "printf" interface to the formatter (see the documentation).
|
|
Revised behaviour of simple boxes: no more than one new line is output
|
|
when consecutive break hints should lead to multiple line breaks.
|
|
- Stream: revised implementation, renamed Parse_failure to Failure and
|
|
Parse_error to Error (don't you love gratuitous changes?).
|
|
- String: added index, rindex, index_from, rindex_from.
|
|
- Array: added mapi, iteri, fold_left, fold_right, init.
|
|
- Added Map.map, Set.subset, Printexc.to_string.
|
|
|
|
* ocamllex: lexers generated by ocamllex can now handle all characters,
|
|
including '\000'.
|
|
|
|
* ocamlyacc: fixed bug with function closures returned by parser rules.
|
|
|
|
* Debugger:
|
|
- Revised generation of events.
|
|
- Break on function entrance.
|
|
- New commands start/previous.
|
|
- The command loadprinter now try to recursively load required
|
|
modules.
|
|
- Numerous small fixes.
|
|
|
|
* External libraries:
|
|
- systhreads: can now use POSIX threads; POSIX and Win32 threads are
|
|
now supported by the native-code compiler.
|
|
- dbm and graph: work in native code.
|
|
- num: fixed bug in Nat.nat_of_string.
|
|
- str: fixed deallocation bug with case folding.
|
|
- win32unix: use Win32 handles instead of (buggy) VC++ emulation of Unix
|
|
file handles; added gettimeofday.
|
|
|
|
* Emacs editing mode and debugger interface updated to July '97 version.
|
|
|
|
Objective Caml 1.05 (21 Mar 1997):
|
|
----------------------------------
|
|
|
|
* Typing: fixed several bugs causing spurious type errors.
|
|
|
|
* Native-code compiler: fixed instruction selection bug causing GC to
|
|
see ill-formed pointers; fixed callbacks to support invocation from a
|
|
main program in C.
|
|
|
|
* Standard library: fixed String.lowercase; Weak now resists integers.
|
|
|
|
* Toplevel: multiple phrases without intermediate ";;" now really supported;
|
|
fixed value printing problems where the wrong printer was selected.
|
|
|
|
* Debugger: fixed printing problem with local references; revised
|
|
handling of checkpoints; various other small fixes.
|
|
|
|
* Macintosh port: fixed signed division problem in bytecomp/emitcode.ml
|
|
|
|
Objective Caml 1.04 (11 Mar 1997):
|
|
----------------------------------
|
|
|
|
* Replay debugger ported from Caml Light; added debugger support in
|
|
compiler (option -g) and runtime system. Debugger is alpha-quality
|
|
and needs testing.
|
|
|
|
* Parsing:
|
|
- Support for "# linenum" directives.
|
|
- At toplevel, allow several phrases without intermediate ";;".
|
|
|
|
* Typing:
|
|
- Allow constraints on datatype parameters, e.g.
|
|
type 'a foo = ... constraint 'a = 'b * 'c.
|
|
- Fixed bug in signature matching in presence of free type variables '_a.
|
|
- Extensive cleanup of internals of type inference.
|
|
|
|
* Native-code compilation:
|
|
- Inlining of small functions at point of call (fairly conservative).
|
|
- MIPS code generator ported to SGI IRIX 6.
|
|
- Better code generated for large integer constants.
|
|
- Check for urgent GC when allocating large objects in major heap.
|
|
- PowerPC port: better scheduling, reduced TOC consumption.
|
|
- HPPA port: handle long conditional branches gracefully,
|
|
several span-dependent bugs fixed.
|
|
|
|
* Standard library:
|
|
- More floating-point functions (all ANSI C float functions now available).
|
|
- Hashtbl: added functorial interface (allow providing own equality
|
|
and hash functions); rehash when resizing, avoid memory leak on
|
|
Hashtbl.remove.
|
|
- Added Char.uppercase, Char.lowercase, String.uppercase, String.lowercase,
|
|
String.capitalize, String.uncapitalize.
|
|
- New module Weak for manipulating weak pointers.
|
|
- New module Callback for registering closures and exceptions to be
|
|
used from C.
|
|
|
|
* Foreign interface:
|
|
- Better support for callbacks (C calling Caml), exception raising
|
|
from C, and main() in C. Added function to remove a global root.
|
|
- Option -output-obj to package Caml code as a C library.
|
|
|
|
* Thread library: fixed bug in timed_read and timed_write operations;
|
|
Lexing.from_function and Lexing.from_channel now reentrant.
|
|
|
|
* Unix interface: renamed EACCESS to EACCES (the POSIX name); added setsid;
|
|
fixed bug in inet_addr_of_string for 64-bit platforms.
|
|
|
|
* Ocamlyacc: default error function no longer prevents error recovery.
|
|
|
|
* Ocamllex: fixed reentrancy problem w.r.t. exceptions during refill;
|
|
fixed output problem (\r\r\n) under Win32.
|
|
|
|
* Macintosh port:
|
|
- The makefiles are provided for compiling and installing O'Caml on
|
|
a Macintosh with MPW 3.4.1.
|
|
- An application with the toplevel in a window is forthcoming.
|
|
|
|
* Windows NT/95 port: updated toplevel GUI to that of Caml Light 0.73.
|
|
|
|
* Emacs editing mode and debugger interface included in distribution.
|
|
|
|
|
|
Objective Caml 1.03 (29 Oct 1996):
|
|
----------------------------------
|
|
|
|
* Typing:
|
|
- bug with type names escaping their scope via unification with
|
|
non-generalized type variables '_a completely fixed;
|
|
- fixed bug in occur check : it was too restrictive;
|
|
- fixed bug of coercion operators;
|
|
- check that no two types of the same name are generated in a module
|
|
(there was no check for classes);
|
|
- "#install_printer" works again;
|
|
- fixed bug in printing of subtyping errors;
|
|
- in class interfaces, construct "method m" (without type) change
|
|
the status of method m from abstract to concrete;
|
|
- in a recursive definition of class interfaces, a class can now
|
|
inherit from a previous class;
|
|
- typing of a method make use of an eventual previously given type
|
|
of this method, yielding clearer type errors.
|
|
|
|
* Compilation (ocamlc and ocamlopt):
|
|
- fixed bug in compilation of classes.
|
|
|
|
* Native-code compilation:
|
|
- optimization of functions taking tuples of arguments;
|
|
- code emitter for the Motorola 680x0 processors (retrocomputing week);
|
|
- Alpha/OSF1: generate frame descriptors, avoids crashes when e.g.
|
|
exp() or log() cause a domain error; fixed bug with
|
|
String.length "literal";
|
|
- Sparc, Mips, HPPA: removed marking of scanned stack frames
|
|
(benefits do not outweigh cost).
|
|
|
|
* Standard library:
|
|
- Arg.parse now prints documentation for command-line options;
|
|
- I/O buffers (types in_channel and out_channel) now heap-allocated,
|
|
avoids crashing when closing a channel several times;
|
|
- Overflow bug in compare() fixed;
|
|
- GC bug in raising Sys_error from I/O functions fixed;
|
|
- Parsing.symbol_start works even for epsilon productions.
|
|
|
|
* Foreign interface: main() in C now working, fixed bug in library
|
|
order at link time.
|
|
|
|
* Thread library: guard against calling thread functions before Thread.create.
|
|
|
|
* Unix library: fixed getsockopt, setsockopt, open_process_{in,out}.
|
|
|
|
* Perl-free, cpp-free, cholesterol-free installation procedure.
|
|
|
|
|
|
Objective Caml 1.02 (27 Sep 1996):
|
|
----------------------------------
|
|
|
|
* Typing:
|
|
- fixed bug with type names escaping their scope via unification
|
|
with non-generalized type variables '_a;
|
|
- keep #class abbreviations longer;
|
|
- faster checking of well-formed abbreviation definitions;
|
|
- stricter checking of "with" constraints over signatures (arity
|
|
mismatch, overriding of an already manifest type).
|
|
|
|
* Compilation (ocamlc and ocamlopt):
|
|
- fixed bug in compilation of recursive classes;
|
|
- [|...|] and let...rec... allowed inside definitions of recursive
|
|
data structures;
|
|
|
|
* Bytecode compilation: fixed overflow in linker for programs with
|
|
more than 65535 globals and constants.
|
|
|
|
* Native-code compilation:
|
|
- ocamlopt ported to HPPA under HP/UX, Intel x86 under Solaris 2,
|
|
PowerMacintosh under MkLinux;
|
|
- fixed two bugs related to floating-point arrays (one with "t array"
|
|
where t is an abstract type implemented as float, one with
|
|
comparison between two float arrays on 32 bit platforms);
|
|
- fixed reloading/spilling problem causing non-termination of
|
|
register allocation;
|
|
- fixed bugs in handling of () causing loss of tail recursion;
|
|
- fixed reloading bug in indirect calls.
|
|
|
|
* Windows NT/95 port:
|
|
- complete port of the threads library (Pascal Cuoq);
|
|
- partial port of the Unix library (Pascal Cuoq);
|
|
- expansion of *, ? and @ on the command line.
|
|
|
|
* Standard library:
|
|
- bug in in List.exists2 fixed;
|
|
- bug in "Random.int n" for very large n on 64-bit machines fixed;
|
|
- module Format: added a "general purpose" type of box (open_box);
|
|
can output on several formatters at the same time.
|
|
|
|
* The "threads" library:
|
|
- implementation on top of native threads available for Win32 and
|
|
POSIX 1003.1c;
|
|
- added -thread option to select a thread-safe version of the
|
|
standard library, the ThreadIO module is no longer needed.
|
|
|
|
* The "graph" library: avoid invalid pixmaps when doing
|
|
open_graph/close_graph several times.
|
|
|
|
* The "dynlink" library: support for "private" (no re-export) dynamic loading.
|
|
|
|
* ocamlyacc: skip '...' character literals correctly.
|
|
|
|
* C interface: C code linked with O'Caml code can provide its own main()
|
|
and call caml_main() later.
|
|
|
|
|
|
Objective Caml 1.01 (12 Jun 1996):
|
|
----------------------------------
|
|
|
|
* Typing: better report of type incompatibilities;
|
|
non-generalizable type variables in a struct...end no longer flagged
|
|
immediately as an error;
|
|
name clashes during "open" avoided.
|
|
|
|
* Fixed bug in output_value where identical data structures
|
|
could have different external representations; this bug caused wrong
|
|
"inconsistent assumptions" errors when checking compatibility of
|
|
interfaces at link-time.
|
|
|
|
* Standard library: fixed bug in Array.blit on overlapping array sections
|
|
|
|
* Unmarshaling from strings now working.
|
|
|
|
* ocamlc, ocamlopt: new flags -intf and -impl to force compilation as
|
|
an implementation/an interface, regardless of file extension;
|
|
overflow bug on wide-range integer pattern-matchings fixed.
|
|
|
|
* ocamlc: fixed bytecode generation bug causing problems with compilation
|
|
units defining more than 256 values
|
|
|
|
* ocamlopt, all platforms:
|
|
fixed GC bug in "let rec" over data structures;
|
|
link startup file first, fixes "undefined symbol" errors with some
|
|
libraries.
|
|
|
|
* ocamlopt, Intel x86:
|
|
more efficient calling sequence for calling C functions;
|
|
floating-point wars, chapter 5: don't use float stack for holding
|
|
float pseudo-registers, stack-allocating them is just as efficient.
|
|
|
|
* ocamlopt, Alpha and Intel x86: more compact calling sequence for garbage
|
|
collection.
|
|
|
|
* ocamllex: generated automata no longer use callbacks for refilling
|
|
the input buffer (works better with threads); character literals
|
|
correctly skipped inside actions.
|
|
|
|
* ocamldep: "-I" directories now searched in the right order
|
|
|
|
* Thread library: incompatibilities with callbacks, signals, and
|
|
dynamic linking removed; scheduling bug with Thread.wait fixed.
|
|
|
|
* New "dbm" library, interfaces with NDBM.
|
|
|
|
* Object-oriented extensions:
|
|
instance variables can now be omitted in class types;
|
|
some error messages have been made clearer;
|
|
several bugs fixes.
|
|
|
|
Objective Caml 1.00 (9 May 1996):
|
|
---------------------------------
|
|
|
|
* Merge of Jérôme Vouillon and Didier Rémy's object-oriented
|
|
extensions.
|
|
|
|
* All libraries: all "new" functions renamed to "create" because "new"
|
|
is now a reserved keyword.
|
|
|
|
* Compilation of "or" patterns (pat1 | pat2) completely revised to
|
|
avoid code size explosion.
|
|
|
|
* Compiler support for preprocessing source files (-pp flag).
|
|
|
|
* Library construction: flag -linkall to force linking of all units in
|
|
a library.
|
|
|
|
* Native-code compiler: port to the Sparc under NetBSD.
|
|
|
|
* Toplevel: fixed bug when tracing several times the same function
|
|
under different names.
|
|
|
|
* New format for marshaling arbitrary data structures, allows
|
|
marshaling to/from strings.
|
|
|
|
* Standard library: new module Genlex (configurable lexer for streams)
|
|
|
|
* Thread library: much better support for I/O and blocking system calls.
|
|
|
|
* Graphics library: faster reclamation of unused pixmaps.
|
|
|
|
* Unix library: new functions {set,clear}_nonblock, {set,clear}_close_on_exec,
|
|
{set,get}itimer, inet_addr_any, {get,set}sockopt.
|
|
|
|
* Dynlink library: added support for linking libraries (.cma files).
|
|
|
|
Caml Special Light 1.15 (15 Mar 1996):
|
|
--------------------------------------
|
|
|
|
* Caml Special Light now runs under Windows NT and 95. Many thanks to
|
|
Kevin Gallo (Microsoft Research) who contributed his initial port.
|
|
|
|
* csllex now generates tables for a table-driven automaton.
|
|
The resulting lexers are smaller and run faster.
|
|
|
|
* Completely automatic configuration script.
|
|
|
|
* Typing: more stringent checking of module type definitions against
|
|
manifest module type specifications.
|
|
|
|
* Toplevel: recursive definitions of values now working.
|
|
|
|
* Native-code compiler, all platforms:
|
|
toplevel "let"s with refutable patterns now working;
|
|
fixed bug in assignment to float record fields;
|
|
direct support for floating-point negation and absolute value.
|
|
|
|
* Native-code compiler, x86: fixed bug with tail calls (with more than
|
|
4 arguments) from a function with a one-word stack frame.
|
|
|
|
* Native-code compiler, Sparc: problem with -compact fixed.
|
|
|
|
* Thread library: support for non-blocking writes; scheduler revised.
|
|
|
|
* Unix library: bug in gethostbyaddr fixed; bounds checking for read,
|
|
write, etc.
|
|
|
|
Caml Special Light 1.14 (8 Feb 1996):
|
|
-------------------------------------
|
|
|
|
* cslopt ported to the PowerPC/RS6000 architecture. Better support for
|
|
AIX in the bytecode system as well.
|
|
|
|
* cslopt, all platforms: fixed bug in live range splitting around catch/exit.
|
|
|
|
* cslopt for the Intel (floating-point wars, chapter 4):
|
|
implemented Ershov's algorithm to minimize floating-point stack usage;
|
|
out-of-order pops fixed.
|
|
|
|
* Several bug fixes in callbacks and signals.
|
|
|
|
Caml Special Light 1.13 (4 Jan 1996):
|
|
-------------------------------------
|
|
|
|
* Pattern-matching compilation revised to factor out accesses inside
|
|
matched structures.
|
|
|
|
* Callbacks and signals now supported in cslopt.
|
|
Signals are only detected at allocation points, though.
|
|
Added callback functions with 2 and 3 arguments.
|
|
|
|
* More explicit error messages when a native-code program aborts due
|
|
to array or string bound violations.
|
|
|
|
* In patterns, "C _" allowed even if the constructor C has several arguments.
|
|
|
|
* && and || allowed as alternate syntax for & and or.
|
|
|
|
* cslopt for the Intel: code generation for floating-point
|
|
operations entirely redone for the third time (a pox on whomever at
|
|
Intel decided to organize the floating-point registers as a stack).
|
|
|
|
* cslopt for the Sparc: don't use Sparc V8 smul and sdiv instructions,
|
|
emulation on V7 processors is abysmal.
|
|
|
|
Caml Special Light 1.12 (30 Nov 1995):
|
|
--------------------------------------
|
|
|
|
* Fixed an embarrassing bug with references to floats.
|
|
|
|
Caml Special Light 1.11 (29 Nov 1995):
|
|
--------------------------------------
|
|
|
|
* Streams and stream parsers a la Caml Light are back (thanks to
|
|
Daniel de Rauglaudre).
|
|
|
|
* User-level concurrent threads, with low-level shared memory primitives
|
|
(locks and conditions) as well as channel-based communication primitives
|
|
with first-class synchronous events, in the style of Reppy's CML.
|
|
|
|
* The native-code compiler has been ported to the HP PA-RISC processor
|
|
running under NextStep (sorry, no HPUX, its linker keeps dumping
|
|
core on me).
|
|
|
|
* References not captured in a function are optimized into variables.
|
|
|
|
* Fixed several bugs related to exceptions.
|
|
|
|
* Floats behave a little more as specified in the IEEE standard
|
|
(believe it or not, but x < y is not the negation of x >= y).
|
|
|
|
* Lower memory consumption for the native-code compiler.
|
|
|
|
Caml Special Light 1.10 (07 Nov 1995):
|
|
--------------------------------------
|
|
|
|
* Many bug fixes (too many to list here).
|
|
|
|
* Module language: introduction of a "with module" notation over
|
|
signatures for concise sharing of all type components of a signature;
|
|
better support for concrete types in signatures.
|
|
|
|
* Native-code compiler: the Intel 386 version has been ported to
|
|
NextStep and FreeBSD, and generates better code (especially for
|
|
floats)
|
|
|
|
* Tools and libraries: the Caml Light profiler and library for
|
|
arbitrary-precision arithmetic have been ported (thanks to John
|
|
Malecki and Victor Manuel Gulias Fernandez); better docs for the Unix
|
|
and regexp libraries.
|
|
|
|
Caml Special Light 1.07 (20 Sep 1995):
|
|
--------------------------------------
|
|
|
|
* Syntax: optional ;; allowed in compilation units and structures
|
|
(back by popular demand)
|
|
|
|
* cslopt:
|
|
generic handling of float arrays fixed
|
|
direct function application when the function expr is not a path fixed
|
|
compilation of "let rec" over values fixed
|
|
multiple definitions of a value name in a module correctly handled
|
|
no calls to ranlib in Solaris
|
|
|
|
* csltop: #trace now working
|
|
|
|
* Standard library: added List.memq; documentation of Array fixed.
|
|
|
|
Caml Special Light 1.06 (12 Sep 1995):
|
|
--------------------------------------
|
|
|
|
* First public release.
|