Merge branch '4.03' into trunk

master
alainfrisch 2016-03-21 23:29:54 +01:00
commit 166ba71479
3 changed files with 290 additions and 10 deletions

268
Changes
View File

@ -40,8 +40,11 @@ OCaml 4.03.0:
(Changes that can break existing programs are marked with a "*") (Changes that can break existing programs are marked with a "*")
Language features: Language features:
==================
- PR#5528: inline records for constructor arguments - PR#5528: inline records for constructor arguments
(Alain Frisch) (Alain Frisch)
- PR#6220, PR#6403, PR#6437, PR#6801: - PR#6220, PR#6403, PR#6437, PR#6801:
Improved redundancy and exhaustiveness checks for GADTs. Improved redundancy and exhaustiveness checks for GADTs.
Namely, the redundancy checker now checks whether the uncovered pattern Namely, the redundancy checker now checks whether the uncovered pattern
@ -50,67 +53,86 @@ Language features:
Additionally, one can now write unreachable cases, of the form Additionally, one can now write unreachable cases, of the form
"pat -> .", which are treated by the redundancy check. "pat -> .", which are treated by the redundancy check.
(Jacques Garrigue) (Jacques Garrigue)
- PR#6374: allow "_ t" as a short-hand for "(_, _, ..) t" for n-ary type - PR#6374: allow "_ t" as a short-hand for "(_, _, ..) t" for n-ary type
constructors constructors
(Alain Frisch) (Alain Frisch)
- PR#6714: allow [@@ocaml.warning] on most structure and signature items: - PR#6714: allow [@@ocaml.warning] on most structure and signature items:
values, modules, module types values, modules, module types
(whitequark) (whitequark)
- PR#6806: Syntax shortcut for putting a type annotation on a record field: - PR#6806: Syntax shortcut for putting a type annotation on a record field:
{ f1 : typ = e } is sugar for { f1 = (e : typ) } { f1 : typ = e } is sugar for { f1 = (e : typ) }
{ f1 : typ } is sugar for { f1 = (f1 : typ) } { f1 : typ } is sugar for { f1 = (f1 : typ) }
(Valentin Gatien-Baron, review by Jérémie Dimino) (Valentin Gatien-Baron, review by Jérémie Dimino)
- PR#6806: Allow type annotations before the "->" in "fun <args> -> <expr>" - PR#6806: Allow type annotations before the "->" in "fun <args> -> <expr>"
fun x y : (int * int) -> (x, y) fun x y : (int * int) -> (x, y)
(Valentin Gatien-Baron, review by Jérémie Dimino) (Valentin Gatien-Baron, review by Jérémie Dimino)
- GPR#26: support for "(type a b)" as syntactic sugar for "(type a) (type b)" - GPR#26: support for "(type a b)" as syntactic sugar for "(type a) (type b)"
(Gabriel Scherer) (Gabriel Scherer)
- GPR#42: short functor type syntax: "S -> T" for "functor (_ : S) -> T" - GPR#42: short functor type syntax: "S -> T" for "functor (_ : S) -> T"
(Leo White) (Leo White)
- GPR#88: allow field punning in object copying expressions: - GPR#88: allow field punning in object copying expressions:
{< x; y; >} is sugar for {< x = x; y = y; >} {< x; y; >} is sugar for {< x = x; y = y; >}
(Jeremy Yallop) (Jeremy Yallop)
- GPR#112: octal escape sequences for char and string literals - GPR#112: octal escape sequences for char and string literals
"Make it \o033[1mBOLD\o033[0m" "Make it \o033[1mBOLD\o033[0m"
(Rafaël Bocquet, request by John Whitingthon) (Rafaël Bocquet, request by John Whitingthon)
- GPR#167: allow to annotate externals' arguments and result types so - GPR#167: allow to annotate externals' arguments and result types so
they can be unboxed or untagged: [@unboxed], [@untagged]. Supports they can be unboxed or untagged: [@unboxed], [@untagged]. Supports
untagging int and unboxing int32, int64, nativeint and float. untagging int and unboxing int32, int64, nativeint and float.
(Jérémie Dimino, Mark Shinwell) (Jérémie Dimino, Mark Shinwell)
- GPR#173: [@inline] and [@inlined] attributes (for function declarations - GPR#173: [@inline] and [@inlined] attributes (for function declarations
and call sites respectively) to control inlining and call sites respectively) to control inlining
(Pierre Chambart, Mark Shinwell) (Pierre Chambart, Mark Shinwell)
- GPR#188: accept [@@immediate] attribute on type declarations to mark types - GPR#188: accept [@@immediate] attribute on type declarations to mark types
that are represented at runtime by an integer that are represented at runtime by an integer
(Will Crichton, reviewed by Leo White) (Will Crichton, reviewed by Leo White)
* GPR#234: allow "[]" as a user-defined constructor. Demand parenthesis * GPR#234: allow "[]" as a user-defined constructor. Demand parenthesis
around "::" when using "::" as user-defined constructor: around "::" when using "::" as user-defined constructor:
code using "| :: of ..." must change to "| (::) of ...". code using "| :: of ..." must change to "| (::) of ...".
(Runhang Li, review by Damien Doligez) (Runhang Li, review by Damien Doligez)
- GPR#240: replace special annotations on externals by attributes: - GPR#240: replace special annotations on externals by attributes:
* "float" is generalized to [@@unboxed] * "float" is generalized to [@@unboxed]
* "noalloc" becomes [@@noalloc] * "noalloc" becomes [@@noalloc]
Deprecate "float" and "noalloc". Deprecate "float" and "noalloc".
(Jérémie Dimino) (Jérémie Dimino)
- GPR#254: @ocaml.warn_on_literal_pattern attribute on constructors to - GPR#254: @ocaml.warn_on_literal_pattern attribute on constructors to
warn when the argument is matches against a constant pattern. This warn when the argument is matches against a constant pattern. This
attribute is applied on predefined exception constructors which attribute is applied on predefined exception constructors which
carry purely informational (with no stability guarantee) messages. carry purely informational (with no stability guarantee) messages.
(Alain Frisch) (Alain Frisch)
- GPR#268: hexadecimal notation for floating-point literals: -0x1.ffffp+987 - GPR#268: hexadecimal notation for floating-point literals: -0x1.ffffp+987
In OCaml source code, FP literals can be written using the hexadecimal In OCaml source code, FP literals can be written using the hexadecimal
notation 0x<mantissa in hex>p<exponent> from ISO C99. notation 0x<mantissa in hex>p<exponent> from ISO C99.
(Xavier Leroy) (Xavier Leroy)
- GPR#273: allow to get the extension slot of an extension constructor - GPR#273: allow to get the extension slot of an extension constructor
by writing [%extension_constructor <path>] by writing [%extension_constructor <path>]
(Jérémie Dimino) (Jérémie Dimino)
- GPR#282: change short-paths penalty heuristic to assign the same cost to - GPR#282: change short-paths penalty heuristic to assign the same cost to
idents containing double underscores as to idents starting with an underscore idents containing double underscores as to idents starting with an underscore
(Thomas Refis, Leo White) (Thomas Refis, Leo White)
- PR#6681 GPR#326: signature items are now accepted as payloads for - PR#6681 GPR#326: signature items are now accepted as payloads for
extension and attributes, using the syntax [%foo: SIG ] or [@foo: SIG ]. extension and attributes, using the syntax [%foo: SIG ] or [@foo: SIG ].
Examples: "[%%client: val foo : int]" or "val%client foo : int". Examples: "[%%client: val foo : int]" or "val%client foo : int".
(Alain Frisch and Gabriel Radanne) (Alain Frisch and Gabriel Radanne)
* GPR#342: Allow shortcuts for extension and attributes on all keywords: * GPR#342: Allow shortcuts for extension and attributes on all keywords:
module%foo, class[@foo], etc. module%foo, class[@foo], etc.
The attribute in "let[@foo] .. in .." is now attached to the value binding, The attribute in "let[@foo] .. in .." is now attached to the value binding,
@ -118,127 +140,175 @@ Language features:
(Gabriel Radanne) (Gabriel Radanne)
Compilers: Compilers:
==========
* PR#4231, PR#5461: warning 31 is now fatal by default * PR#4231, PR#5461: warning 31 is now fatal by default
(Warning 31: A module is linked twice in the same executable.) (Warning 31: A module is linked twice in the same executable.)
This is an interim solution; double-linking of modules has dangerous semantics, This is an interim solution; double-linking of modules has dangerous semantics,
eg. exception constructors end up with two distinct declarations. eg. exception constructors end up with two distinct declarations.
(Alain Frisch) (Alain Frisch)
- PR#4800: better compilation of tuple assignment - PR#4800: better compilation of tuple assignment
(Gabriel Scherer and Alain Frisch) (Gabriel Scherer and Alain Frisch)
- PR#5995: keep -for-pack into account to name exceptions; - PR#5995: keep -for-pack into account to name exceptions;
-for-pack should now be used during bytecode compilation as well -for-pack should now be used during bytecode compilation as well
(Alain Frisch, report by Christophe Troestler) (Alain Frisch, report by Christophe Troestler)
- PR#6400: better error message for '_' used as an expression - PR#6400: better error message for '_' used as an expression
(Alain Frisch, report by whitequark) (Alain Frisch, report by whitequark)
- PR#6501: harden the native-code generator against certain uses of "%identity" - PR#6501: harden the native-code generator against certain uses of "%identity"
(Xavier Leroy, report by Antoine Miné) (Xavier Leroy, report by Antoine Miné)
- PR#6636: add --version option - PR#6636: add --version option
(whitequark) (whitequark)
- PR#6679: fix pprintast printing of constraints in type declarations - PR#6679: fix pprintast printing of constraints in type declarations
(Alain Frisch, report by Jun Furuse) (Alain Frisch, report by Jun Furuse)
- PR#6737: fix Typedtree attributes on (fun x -> body) expressions - PR#6737: fix Typedtree attributes on (fun x -> body) expressions
(Alain Frisch, report by Oleg Kiselyov) (Alain Frisch, report by Oleg Kiselyov)
* PR#6865: remove special case for parsing "let _ = expr" in structures * PR#6865: remove special case for parsing "let _ = expr" in structures
(Jérémie Dimino, Alain Frisch) (Jérémie Dimino, Alain Frisch)
* PR#6438, PR#7059, GPR#315: Pattern guard disables exhaustiveness check * PR#6438, PR#7059, GPR#315: Pattern guard disables exhaustiveness check
(function Some x when x = 0 -> ()) will now raise warning 8 (non-exhaustive) (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. 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 Projects that set warning 8 as an error may fail to compile (presumably
this is the semantics they wanted). this is the semantics they wanted).
(Alain Frisch, request by Martin Jambon and John Whitington) (Alain Frisch, request by Martin Jambon and John Whitington)
- PR#6920: fix debug informations around uses of %apply or %revapply - PR#6920: fix debug informations around uses of %apply or %revapply
(Jérémie Dimino, report by Daniel Bünzli) (Jérémie Dimino, report by Daniel Bünzli)
- PR#6939: Segfault with improper use of let-rec - PR#6939: Segfault with improper use of let-rec
(Alain Frisch) (Alain Frisch)
- PR#6943: native-code generator for POWER/PowerPC 64 bits, both in - PR#6943: native-code generator for POWER/PowerPC 64 bits, both in
big-endian (ppc64) and little-endian (ppc64le) configuration. big-endian (ppc64) and little-endian (ppc64le) configuration.
(Xavier Leroy, with inspiration from RedHat's unofficial ppc64 and ppc64le (Xavier Leroy, with inspiration from RedHat's unofficial ppc64 and ppc64le
ports) ports)
- PR#6979: better code generation in x86-32 backend for copying floats to - PR#6979: better code generation in x86-32 backend for copying floats to
the stack the stack
(Marc Lasson, review by Xavier Leroy) (Marc Lasson, review by Xavier Leroy)
- PR#7018: fix missing identifier renaming during inlining - PR#7018: fix missing identifier renaming during inlining
(Alain Frisch, review by Xavier Leroy) (Alain Frisch, review by Xavier Leroy)
- PR#7022, GPR#259: unbox float and boxed ints earlier, avoid second pass - PR#7022, GPR#259: unbox float and boxed ints earlier, avoid second pass
(Alain Frisch) (Alain Frisch)
- PR#7026, GPR#288: remove write barrier for polymorphic variants without - PR#7026, GPR#288: remove write barrier for polymorphic variants without
arguments arguments
(Simon Cruanes) (Simon Cruanes)
- PR#7031: new warning 57, ambiguous guarded or-patterns - PR#7031: new warning 57, ambiguous guarded or-patterns
(Luc Maranget, Gabriel Scherer, report by Martin Clochard and Claude Marché) (Luc Maranget, Gabriel Scherer, report by Martin Clochard and Claude Marché)
- PR#7064, GPR#316: allowing to mark compilation units and sub-modules as - PR#7064, GPR#316: allowing to mark compilation units and sub-modules as
deprecated deprecated
(Alain Frisch) (Alain Frisch)
- PR#7067: fix performance regression (wrt. 4.01) in the native compiler - PR#7067: fix performance regression (wrt. 4.01) in the native compiler
for long nested structures for long nested structures
(Alain Frisch, report by Daniel Bünzli, review by Jacques Garrigue) (Alain Frisch, report by Daniel Bünzli, review by Jacques Garrigue)
- PR#7097: fix strange syntax error message around illegal packaged module - PR#7097: fix strange syntax error message around illegal packaged module
signature constraints signature constraints
(Alain Frisch, report by Jun Furuse) (Alain Frisch, report by Jun Furuse)
- PR#7118, PR#7120, GPR#408, GPR#476: Bug fixed in stack unwinding - PR#7118, PR#7120, GPR#408, GPR#476: Bug fixed in stack unwinding
metadata generation. Was a cause of crashes in GUI programs on OS X. metadata generation. Was a cause of crashes in GUI programs on OS X.
(Bart Jacobs, review by Mark Shinwell) (Bart Jacobs, review by Mark Shinwell)
- GPR#17: some cmm optimizations of integer operations with constants - GPR#17: some cmm optimizations of integer operations with constants
(Stephen Dolan, review by Pierre Chambart) (Stephen Dolan, review by Pierre Chambart)
- GPR#89: improve type-specialization of unapplied primitives: - GPR#89: improve type-specialization of unapplied primitives:
unapplied annotations (compare : int -> _), unapplied annotations (compare : int -> _),
type propagation (List.sort compare [1;2;3]) type propagation (List.sort compare [1;2;3])
and propagation from module signatures now lead to specialization and propagation from module signatures now lead to specialization
(Frédéric Bour, review by Gabriel Scherer) (Frédéric Bour, review by Gabriel Scherer)
- GPR#107: Prevent more unnecessary float boxing, especially in `if` and `match` - GPR#107: Prevent more unnecessary float boxing, especially in `if` and `match`
(Vladimir Brankov, review by Alain Frisch) (Vladimir Brankov, review by Alain Frisch)
- GPR#109: new (lazy) unboxing strategy for float and int references - GPR#109: new (lazy) unboxing strategy for float and int references
(Vladimir Brankov, review by Alain Frisch) (Vladimir Brankov, review by Alain Frisch)
- GPR#115: More precise typing of values at the C-- and Mach level. - GPR#115: More precise typing of values at the C-- and Mach level.
(Xavier Leroy, review by Pierre Chambart) (Xavier Leroy, review by Pierre Chambart)
- GPR#132: Flambda: new intermediate language and "middle-end" optimizers - GPR#132: Flambda: new intermediate language and "middle-end" optimizers
(Pierre Chambart, Mark Shinwell, Leo White) (Pierre Chambart, Mark Shinwell, Leo White)
- GPR#207: Colors in compiler messages (warnings, errors) - GPR#207: Colors in compiler messages (warnings, errors)
configure with -color {auto|always|never} or TERM=dumb configure with -color {auto|always|never} or TERM=dumb
(Simon Cruanes, review by Gabriel Scherer) (Simon Cruanes, review by Gabriel Scherer)
- GPR#258: more precise information on PowerPC instruction sizes - GPR#258: more precise information on PowerPC instruction sizes
(Pierre Chambart, Xavier Leroy) (Pierre Chambart, Xavier Leroy)
- GPR#263: improve code generation for if-equivalents of (&&) and (||) - GPR#263: improve code generation for if-equivalents of (&&) and (||)
(Pierre Chambart) (Pierre Chambart)
- GPR#270: Make [transl_exception_constructor] generate [Immutable] blocks - GPR#270: Make [transl_exception_constructor] generate [Immutable] blocks
(Mark Shinwell) (Mark Shinwell)
- GPR#271: Fix incorrect mutability flag when records are built using "with" - GPR#271: Fix incorrect mutability flag when records are built using "with"
(Mark Shinwell) (Mark Shinwell)
- GPR#275: native-code generator for IBM z System running Linux. - GPR#275: native-code generator for IBM z System running Linux.
In memoriam Gene Amdahl, 1922-2015. In memoriam Gene Amdahl, 1922-2015.
(Bill O'Farrell, Tristan Amini, Xavier Leroy) (Bill O'Farrell, Tristan Amini, Xavier Leroy)
- GPR#282: relax short-paths safety check in presence of module aliases, take - GPR#282: relax short-paths safety check in presence of module aliases, take
penalty into account while building the printing map. penalty into account while building the printing map.
(Thomas Refis, Leo White) (Thomas Refis, Leo White)
- GPR#306: Instrument the compiler to debug performance regressions - GPR#306: Instrument the compiler to debug performance regressions
(Pierre Chambart) (Pierre Chambart)
- GPR#319: add warning 58 for missing cmx files, and - GPR#319: add warning 58 for missing cmx files, and
extend -opaque option to mli files: a missing .cmx does not warn extend -opaque option to mli files: a missing .cmx does not warn
if the corresponding .cmi is compiled -opaque. if the corresponding .cmi is compiled -opaque.
(Leo White) (Leo White)
- GPR#388: OCAML_FLEXLINK environment variable allows overriding flexlink - GPR#388: OCAML_FLEXLINK environment variable allows overriding flexlink
command (David Allsopp) command (David Allsopp)
- GPR#392: put all parsetree invariants in a new module Ast_invariants - GPR#392: put all parsetree invariants in a new module Ast_invariants
(Jérémie Dimino) (Jérémie Dimino)
- GPR#407: don't display the name of compiled .c files when calling the - GPR#407: don't display the name of compiled .c files when calling the
Microsoft C Compiler (same as the assembler). Microsoft C Compiler (same as the assembler).
(David Allsopp) (David Allsopp)
- GPR#431: permit constant float arrays to be eligible for pattern match - GPR#431: permit constant float arrays to be eligible for pattern match
branch merging branch merging
(Pierre Chambart) (Pierre Chambart)
- GPR#455: provide more debugging information to Js_of_ocaml - GPR#455: provide more debugging information to Js_of_ocaml
(Jérôme Vouillon) (Jérôme Vouillon)
Runtime system: Runtime system:
===============
- PR#3612, PR#92: allow allocating custom block with finalizers - PR#3612, PR#92: allow allocating custom block with finalizers
in the minor heap. in the minor heap.
(Pierre Chambart) (Pierre Chambart)
* PR#6517: use ISO C99 types {,u}int{32,64}_t in preference to our homegrown * PR#6517: use ISO C99 types {,u}int{32,64}_t in preference to our homegrown
types {,u}int{32,64}. types {,u}int{32,64}.
C stubs may have to be updated as {,u}int{32,64}_t are not defined anymore. C stubs may have to be updated as {,u}int{32,64}_t are not defined anymore.
(Xavier Leroy) (Xavier Leroy)
- PR#6760: closures evaluated in the toplevel can now be marshalled - PR#6760: closures evaluated in the toplevel can now be marshalled
(whitequark, review by Jacques-Henri Jourdan) (whitequark, review by Jacques-Henri Jourdan)
- PR#6902, GPR#210: emit a runtime warning on stderr - PR#6902, GPR#210: emit a runtime warning on stderr
when finalizing an I/O channel which is still open: when finalizing an I/O channel which is still open:
"channel opened on file '...' dies without being closed" "channel opened on file '...' dies without being closed"
@ -246,458 +316,642 @@ Runtime system:
The behavior of affected program is not changed, The behavior of affected program is not changed,
but they should still be fixed. but they should still be fixed.
(Alain Frisch, review by Damien Doligez) (Alain Frisch, review by Damien Doligez)
- Signal handling: for read-and-clear, use GCC/Clang atomic builtins - Signal handling: for read-and-clear, use GCC/Clang atomic builtins
if available. if available.
(Xavier Leroy) (Xavier Leroy)
- PR#6910, GPR#224: marshaling (output_value, input_value, et al) - PR#6910, GPR#224: marshaling (output_value, input_value, et al)
now support marshaled data bigger than 4 Gb. now support marshaled data bigger than 4 Gb.
(Xavier Leroy) (Xavier Leroy)
* GPR#226: select higher levels of optimization for GCC >= 3.4 and Clang * GPR#226: select higher levels of optimization for GCC >= 3.4 and Clang
when compiling the run-time system and C stub code. when compiling the run-time system and C stub code.
"-std=gnu99 -O2 -fno-strict-aliasing -fwrapv" is used by default. "-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" This also affects default flags for user stubs compiled with "ocamlc -c foo.c"
and may uncover bugs in them. and may uncover bugs in them.
(Xavier Leroy) (Xavier Leroy)
- GPR#262: Multiple GC roots per compilation unit - GPR#262: Multiple GC roots per compilation unit
(Pierre Chambart, Mark Shinwell, review by Damien Doligez) (Pierre Chambart, Mark Shinwell, review by Damien Doligez)
- GPR#297: Several changes to improve the worst-case GC pause time. - GPR#297: Several changes to improve the worst-case GC pause time.
(Damien Doligez, with help from Leo White and Francois Bobot) (Damien Doligez, with help from Leo White and Francois Bobot)
- GPR#325: Add v=0x400 flag to OCAMLRUNPARAM to display GC stats on exit - GPR#325: Add v=0x400 flag to OCAMLRUNPARAM to display GC stats on exit
(Louis Gesbert, review by Alain Frisch) (Louis Gesbert, review by Alain Frisch)
Standard library: Standard library:
- PR#1460, GPR#230: Array.map2, Array.iter2 - PR#1460, GPR#230: Array.map2, Array.iter2
(John Christopher McAlpine) (John Christopher McAlpine)
- PR#5197, GPR#63: Arg: allow flags such as --flag=arg as well as --flag arg - PR#5197, GPR#63: Arg: allow flags such as --flag=arg as well as --flag arg
(Richard Jones) (Richard Jones)
- PR#6017, PR#7034, GPR#267: More efficient ifprintf implementation - PR#6017, PR#7034, GPR#267: More efficient ifprintf implementation
(Jeremy Yallop, review by Gabriel Scherer) (Jeremy Yallop, review by Gabriel Scherer)
- PR#6296: Some documentation on the floating-point representations - PR#6296: Some documentation on the floating-point representations
recognized by Pervasives.float_of_string recognized by Pervasives.float_of_string
(Xavier Leroy) (Xavier Leroy)
- PR#6316: Scanf.scanf failure on %u formats when reading big integers - PR#6316: Scanf.scanf failure on %u formats when reading big integers
(Xavier Leroy, Benoît Vaugon) (Xavier Leroy, Benoît Vaugon)
- PR#6321: guarantee that "hypot infinity nan = infinity" - PR#6321: guarantee that "hypot infinity nan = infinity"
(for conformance with ISO C99) (for conformance with ISO C99)
(Xavier Leroy) (Xavier Leroy)
- PR#6390, GPR#36: expose Sys.{int_size,max_wosize} for js_of_ocaml portability - PR#6390, GPR#36: expose Sys.{int_size,max_wosize} for js_of_ocaml portability
(Hugo Heuzard) (Hugo Heuzard)
- PR#6449: Add Map.union - PR#6449: Add Map.union
(Alain Frisch) (Alain Frisch)
* PR#6494: Add 'equal' functions in modules * PR#6494: Add 'equal' functions in modules
Bytes, Char, Digest, Int32, Int64, Nativeint, and String Bytes, Char, Digest, Int32, Int64, Nativeint, and String
Users defining their own modules with signature 'module type of Int32' Users defining their own modules with signature 'module type of Int32'
have to extend their implementation. have to extend their implementation.
(Romain Calascibetta) (Romain Calascibetta)
* PR#6524, GPR#79: Filename: Optional ?perms argument to open_temp_file * PR#6524, GPR#79: Filename: Optional ?perms argument to open_temp_file
May break partial applications of the function (fix by passing ?perms:None) May break partial applications of the function (fix by passing ?perms:None)
(Daniel Bünzli, review by Jacques-Pascal Deplaix) (Daniel Bünzli, review by Jacques-Pascal Deplaix)
* PR#6525, GPR#80: Add Uchar module to the standard library * PR#6525, GPR#80: Add Uchar module to the standard library
May introduce module name conflicts with existing projects. May introduce module name conflicts with existing projects.
(Daniel Bünzli, review by Yoriyuki Yamagata and Damien Doligez) (Daniel Bünzli, review by Yoriyuki Yamagata and Damien Doligez)
- PR#6577: improve performance of %L, %l, %n, %S, %C format specifiers - PR#6577: improve performance of %L, %l, %n, %S, %C format specifiers
(Alain Frisch) (Alain Frisch)
- PR#6585: fix memory leak in win32unix/createprocess.c - PR#6585: fix memory leak in win32unix/createprocess.c
(Alain Frisch, report by user 'aha') (Alain Frisch, report by user 'aha')
- PR#6645, GPR#174: Guarantee that Set.add, Set.remove, Set.filter - PR#6645, GPR#174: Guarantee that Set.add, Set.remove, Set.filter
return the original set if no change is required return the original set if no change is required
(Alain Frisch, Mohamed Iguernlala) (Alain Frisch, Mohamed Iguernlala)
- PR#6649, GPR#222: accept (int_of_string "+3") - PR#6649, GPR#222: accept (int_of_string "+3")
(John Christopher McAlpine) (John Christopher McAlpine)
- PR#6694, PR#6695, GPR#124: deprecate functions using ISO-8859-1 character set - PR#6694, PR#6695, GPR#124: deprecate functions using ISO-8859-1 character set
in Char, Bytes, String and provide alternatives *_acii using US-ASCII. in Char, Bytes, String and provide alternatives *_acii using US-ASCII.
Affected functions: Affected functions:
{Char,String,Bytes}.{uppercase,lowercase}, {Char,String,Bytes}.{uppercase,lowercase},
{String,Bytes}.{capitalize,uncaptialize} {String,Bytes}.{capitalize,uncaptialize}
(whitequark, review by Damien Doligez) (whitequark, review by Damien Doligez)
- GPR#22: Add the Ephemeron module that implements ephemerons and weak - GPR#22: Add the Ephemeron module that implements ephemerons and weak
hash table hash table
(François Bobot, review by Damien Doligez, Daniel Bünzli, (François Bobot, review by Damien Doligez, Daniel Bünzli,
Alain Frisch, Pierre Chambart) Alain Frisch, Pierre Chambart)
- GPR#164: more efficient (branchless) implementation of Pervasives.compare - GPR#164: more efficient (branchless) implementation of Pervasives.compare
specialized at type 'float'. specialized at type 'float'.
(Vladimir Brankov) (Vladimir Brankov)
- GPR#175: Guarantee that Map.add, Map.remove, Map.filter - GPR#175: Guarantee that Map.add, Map.remove, Map.filter
return the original map if no change is required. return the original map if no change is required.
(Mohamed Iguernlala) (Mohamed Iguernlala)
- GPR#201: generalize types of Printf.{ifprintf,ikfprintf} - GPR#201: generalize types of Printf.{ifprintf,ikfprintf}
(Maxence Guesdon) (Maxence Guesdon)
- GPR#216: add the missing POSIX.1-2001 signals in Sys - GPR#216: add the missing POSIX.1-2001 signals in Sys
(Guillaume Bury) (Guillaume Bury)
- GPR#239: remove type-unsafe code from Stream - GPR#239: remove type-unsafe code from Stream
(Pierre Chambart, review by Gabriel Scherer and Jeremy Yallop) (Pierre Chambart, review by Gabriel Scherer and Jeremy Yallop)
- GPR#250: Check for negative start element in Array.sub - GPR#250: Check for negative start element in Array.sub
(Jeremy Yallop) (Jeremy Yallop)
- GPR#265: new implementation of Queue avoiding Obj.magic - GPR#265: new implementation of Queue avoiding Obj.magic
(Jérémie Dimino) (Jérémie Dimino)
- GPR#268, GPR#303: '%h' and '%H' modifiers for printf and scanf to - GPR#268, GPR#303: '%h' and '%H' modifiers for printf and scanf to
support floating-point numbers in hexadecimal notation support floating-point numbers in hexadecimal notation
(Xavier Leroy, Benoît Vaugon) (Xavier Leroy, Benoît Vaugon)
- GPR#272: Switch classify_float to [@@unboxed] - GPR#272: Switch classify_float to [@@unboxed]
(Alain Frisch) (Alain Frisch)
- Improve speed of classify_float by not going through fpclassify() - Improve speed of classify_float by not going through fpclassify()
(Alain Frisch, Xavier Leroy) (Alain Frisch, Xavier Leroy)
- GPR#277: Switch the following externals to [@@unboxed]: - GPR#277: Switch the following externals to [@@unboxed]:
* {Nativeint,Int32,Int64}.{of,to}_float * {Nativeint,Int32,Int64}.{of,to}_float
* Int{32,64}.float_of_bits * Int{32,64}.float_of_bits
* Int{32,64}.bits_of_float * Int{32,64}.bits_of_float
(Jérémie Dimino) (Jérémie Dimino)
- GPR#281: Switch the following externals to [@@unboxed]: - GPR#281: Switch the following externals to [@@unboxed]:
* Sys.time (and [@@noalloc]) * Sys.time (and [@@noalloc])
* Pervasives.ldexp (and [@@noalloc]) * Pervasives.ldexp (and [@@noalloc])
* Pervasives.compare for float, nativeint, int32, int64. * Pervasives.compare for float, nativeint, int32, int64.
(François Bobot) (François Bobot)
- PR#3622, GPR#195: add function Stack.fold - PR#3622, GPR#195: add function Stack.fold
(Simon Cruanes) (Simon Cruanes)
- GPR#329: Add exists, for_all, mem and memq functions in Array - GPR#329: Add exists, for_all, mem and memq functions in Array
(Bernhard Schommer) (Bernhard Schommer)
- GPR#337: Add [Hashtbl.filter_map_inplace] - GPR#337: Add [Hashtbl.filter_map_inplace]
(Alain Frisch) (Alain Frisch)
- GPR#356: Add [Format.kasprintf] - GPR#356: Add [Format.kasprintf]
(Jérémie Dimino, Mark Shinwell) (Jérémie Dimino, Mark Shinwell)
Type system: Type system:
============
- PR#5545: Type annotations on methods cannot control the choice of abbreviation - PR#5545: Type annotations on methods cannot control the choice of abbreviation
(Jacques Garrigue) (Jacques Garrigue)
* PR#6465: allow incremental weakening of module aliases. * PR#6465: allow incremental weakening of module aliases.
This is done by adding equations to submodules when expanding 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 In theory this may be incompatible is some corner cases defining a module
type through inference, but no breakage known on published code. type through inference, but no breakage known on published code.
(Jacques Garrigue) (Jacques Garrigue)
- PR#6593: Functor application in tests/basic-modules fails after commit 15405 - PR#6593: Functor application in tests/basic-modules fails after commit 15405
(Jacques Garrigue) (Jacques Garrigue)
Toplevel and debugger: Toplevel and debugger:
======================
- PR#6113: Add descriptions to directives, and display them via #help - PR#6113: Add descriptions to directives, and display them via #help
(Nick Giannarakis, Berke Durak, Francis Southern and Gabriel Scherer) (Nick Giannarakis, Berke Durak, Francis Southern and Gabriel Scherer)
- PR#6396: Warnings-as-errors not properly flushed in the toplevel - PR#6396: Warnings-as-errors not properly flushed in the toplevel
(Alain Frisch) (Alain Frisch)
- PR#6401: use proper error reporting for toplevel environment initialization: - PR#6401: use proper error reporting for toplevel environment initialization:
no more Env.Error(_) at start time no more Env.Error(_) at start time
(Gabriel Scherer, Alain Frisch) (Gabriel Scherer, Alain Frisch)
- PR#6468: toplevel now supports backtraces if invoked with OCAMLRUNPARAM=b - PR#6468: toplevel now supports backtraces if invoked with OCAMLRUNPARAM=b
(whitequark and Jake Donham, (whitequark and Jake Donham,
review by Gabriel Scherer and Jacques-Henri Jourdan) review by Gabriel Scherer and Jacques-Henri Jourdan)
- PR#6935, GPR#298: crash in debugger when load_printer is given a directory - PR#6935, GPR#298: crash in debugger when load_printer is given a directory
(Junsong Li, review by Gabriel Scherer) (Junsong Li, review by Gabriel Scherer)
- PR#7081: report preprocessor warnings in the toplevel - PR#7081: report preprocessor warnings in the toplevel
(Valentin Gatien-Baron, review by Jérémie Dimino) (Valentin Gatien-Baron, review by Jérémie Dimino)
- PR#7098: Loss of ppx context in toplevel after an exception - PR#7098: Loss of ppx context in toplevel after an exception
(Alain Frisch, report by whitequark) (Alain Frisch, report by whitequark)
- PR#7101: The toplevel does not close in_channel for libraries specified on - PR#7101: The toplevel does not close in_channel for libraries specified on
its command line its command line
(Alain Frisch) (Alain Frisch)
- PR#7119: the toplevel does not respect [@@@warning] - PR#7119: the toplevel does not respect [@@@warning]
(Alain Frisch, report by Gabriel Radanne) (Alain Frisch, report by Gabriel Radanne)
Other libraries: Other libraries:
================
* Unix library: channels created by Unix.in_channel_of_descr or * Unix library: channels created by Unix.in_channel_of_descr or
Unix.out_channel_of_descr no longer support text mode under Windows. Unix.out_channel_of_descr no longer support text mode under Windows.
Calling [set_binary_mode_{in,out} chan false] on these channels Calling [set_binary_mode_{in,out} chan false] on these channels
now causes an error. now causes an error.
(Xavier Leroy) (Xavier Leroy)
- PR#4023 and GPR#68: add Unix.sleepf (sleep with sub-second resolution) - PR#4023 and GPR#68: add Unix.sleepf (sleep with sub-second resolution)
(Evgenii Lepikhin and Xavier Leroy) (Evgenii Lepikhin and Xavier Leroy)
* Protect Unix.sleep against interruptions by handled signals. * Protect Unix.sleep against interruptions by handled signals.
Before, a handled signal could cause Unix.sleep to return early. Before, a handled signal could cause Unix.sleep to return early.
Now, the sleep is restarted until the given time is elapsed. Now, the sleep is restarted until the given time is elapsed.
(Xavier Leroy) (Xavier Leroy)
* PR#6120, GPR#462: implement Unix.symlink and Unix.readlink on * PR#6120, GPR#462: implement Unix.symlink and Unix.readlink on
Windows. Unix.symlink has a new optional argument to_dir (ignored on Windows. Unix.symlink has a new optional argument to_dir (ignored on
non-native Windows platforms). stat functions reimplemented to avoid non-native Windows platforms). stat functions reimplemented to avoid
buggy Microsoft CRT implementations (native Windows only) buggy Microsoft CRT implementations (native Windows only)
(David Allsopp, review by Daniel Bünzli) (David Allsopp, review by Daniel Bünzli)
- PR#6263: add kind_size_in_bytes and size_in_bytes functions - PR#6263: add kind_size_in_bytes and size_in_bytes functions
to Bigarray module. to Bigarray module.
(Runhang Li, review by Mark Shinwell) (Runhang Li, review by Mark Shinwell)
- PR#6289: Unix.utimes uses the current time only if both arguments - PR#6289: Unix.utimes uses the current time only if both arguments
are exactly 0.0. Also, use sub-second resolution if available. are exactly 0.0. Also, use sub-second resolution if available.
(Xavier Leroy, report by Christophe Troestler) (Xavier Leroy, report by Christophe Troestler)
- PR#6896: serious reimplementation of Big_int.float_of_big_int and - PR#6896: serious reimplementation of Big_int.float_of_big_int and
Ratio.float_of_ratio, ensuring that the result is correctly rounded. Ratio.float_of_ratio, ensuring that the result is correctly rounded.
(Xavier Leroy) (Xavier Leroy)
- PR#6989: in Str library, make sure that all \(...\) groups are binding - PR#6989: in Str library, make sure that all \(...\) groups are binding
and can be consulted with Str.matched_group. There used to be and can be consulted with Str.matched_group. There used to be
a limitation to 32 binding groups. a limitation to 32 binding groups.
(Xavier Leroy) (Xavier Leroy)
- PR#7013: spurious wake-up in the Event module - PR#7013: spurious wake-up in the Event module
(Xavier Leroy) (Xavier Leroy)
- PR#7024: in documentation of Str regular expressions, clarify what - PR#7024: in documentation of Str regular expressions, clarify what
"end of line" means for "^" and "$" regexps. "end of line" means for "^" and "$" regexps.
(Xavier Leroy, question by Fredrik Lindgren) (Xavier Leroy, question by Fredrik Lindgren)
OCamldep: OCamldep:
=========
- GPR#286: add support for module aliases - GPR#286: add support for module aliases
(Jacques Garrigue) (Jacques Garrigue)
Manual: Manual:
=======
- GPR#302: The OCaml reference manual is now included in the manual/ - GPR#302: The OCaml reference manual is now included in the manual/
subdirectory of the main OCaml source repository. Contributions to subdirectory of the main OCaml source repository. Contributions to
the manual are warmly welcome. the manual are warmly welcome.
(François Bobot, review by Florian Angeletti) (François Bobot, review by Florian Angeletti)
- PR#6676: ongoing simplification of the "Language Extensions" section - PR#6676: ongoing simplification of the "Language Extensions" section
(Alain Frisch, John Whitington) (Alain Frisch, John Whitington)
- PR#7092, GPR#379: Add missing documentation for new 4.03 features - PR#7092, GPR#379: Add missing documentation for new 4.03 features
(Florian Angeletti) (Florian Angeletti)
- PR#7109, GPR#380: Fix bigarray documentation layout - PR#7109, GPR#380: Fix bigarray documentation layout
(Florian Angeletti, Leo White) (Florian Angeletti, Leo White)
Bug fixes: Bug fixes:
==========
- PR#3612: memory leak in bigarray read from file - PR#3612: memory leak in bigarray read from file
(Pierre Chambart, report by Gary Huber) (Pierre Chambart, report by Gary Huber)
* PR#4166, PR#6956: force linking when calling external C primitives * PR#4166, PR#6956: force linking when calling external C primitives
(Jacques Garrigue, reports by Markus Mottl and Christophe Troestler) (Jacques Garrigue, reports by Markus Mottl and Christophe Troestler)
* PR#4466, PR#5325: under Windows, concurrent read and write operations * PR#4466, PR#5325: under Windows, concurrent read and write operations
on the same socket could block unexpectedly. Fixed by keeping sockets on the same socket could block unexpectedly. Fixed by keeping sockets
in asynchronous mode rather than creating them in synchronous mode. in asynchronous mode rather than creating them in synchronous mode.
(Xavier Leroy) (Xavier Leroy)
* PR#4539: change exception string raised when comparing functional values * PR#4539: change exception string raised when comparing functional values
May break programs matching on the string argument of Invalid_argument. May break programs matching on the string argument of Invalid_argument.
Matching on the string argument of Invalid_argument or Failure is a Matching on the string argument of Invalid_argument or Failure is a
programming mistake: these strings may change in future versions. programming mistake: these strings may change in future versions.
(Nicolas Braud-Santoni, report by Eric Cooper) (Nicolas Braud-Santoni, report by Eric Cooper)
- PR#4832: Filling bigarrays may block out runtime - PR#4832: Filling bigarrays may block out runtime
(Markus Mottl) (Markus Mottl)
- PR#5663: program rejected due to nongeneralizable type variable that - PR#5663: program rejected due to nongeneralizable type variable that
appears nowhere appears nowhere
(Jacques Garrigue, report by Stephen Weeks) (Jacques Garrigue, report by Stephen Weeks)
- PR#5780: report more informative type names in GADTs error messages - PR#5780: report more informative type names in GADTs error messages
(Jacques Garrigue, report by Sebastien Furic) (Jacques Garrigue, report by Sebastien Furic)
- PR#5887: move the byterun/*.h headers to byterun/caml/*.h to avoid header - PR#5887: move the byterun/*.h headers to byterun/caml/*.h to avoid header
name clashes name clashes
(Jérôme Vouillon and Adrien Nader and whitequark) (Jérôme Vouillon and Adrien Nader and whitequark)
* PR#6081: ocaml now adds script's directory to search path, not current * PR#6081: ocaml now adds script's directory to search path, not current
directory directory
(Thomas Leonard and Damien Doligez) (Thomas Leonard and Damien Doligez)
- PR#6108, PR#6802: fail cleanly if dynlink.cma or ocamltoplevel.cma - PR#6108, PR#6802: fail cleanly if dynlink.cma or ocamltoplevel.cma
are loaded inside the toplevel loop. are loaded inside the toplevel loop.
(Xavier Leroy) (Xavier Leroy)
- PR#6171: Confusing error message when a type escapes its scope. - PR#6171: Confusing error message when a type escapes its scope.
(Jacques Garrigue and Leo White, report by John Whitington) (Jacques Garrigue and Leo White, report by John Whitington)
- PR#6340: Incorrect handling of \r when processing "Windows" source files - PR#6340: Incorrect handling of \r when processing "Windows" source files
(Damien Doligez, report by David Allsopp) (Damien Doligez, report by David Allsopp)
- PR#6342: Incorrect error message when type constraints differ - PR#6342: Incorrect error message when type constraints differ
(Alain Frisch, report by Philippe Wang) (Alain Frisch, report by Philippe Wang)
* PR#6521: {Bytes,Char,String}.escaped were locale-dependent * PR#6521: {Bytes,Char,String}.escaped were locale-dependent
we now escape all non-ASCII-printable instead of a locale-dependent subset. we now escape all non-ASCII-printable instead of a locale-dependent subset.
(Damien Doligez, report by Jun Furuse) (Damien Doligez, report by Jun Furuse)
- PR#6526: ocamllex should not warn on unescaped newline inside comments - PR#6526: ocamllex should not warn on unescaped newline inside comments
(Damien Doligez, report by user 'dhekir') (Damien Doligez, report by user 'dhekir')
- PR#6341: ocamldoc -colorize-code adds spurious <br> tags to <pre> blocks - PR#6341: ocamldoc -colorize-code adds spurious <br> tags to <pre> blocks
(Maxence Guesdon, report by Damien Doligez) (Maxence Guesdon, report by Damien Doligez)
- PR#6560: Wrong failure message for {Int32,Int64,NativeInt}.of_string - PR#6560: Wrong failure message for {Int32,Int64,NativeInt}.of_string
It reported (Failure "int_of_string"), now "Int32.of_string" etc. It reported (Failure "int_of_string"), now "Int32.of_string" etc.
(Maxime Dénès and Gabriel Scherer) (Maxime Dénès and Gabriel Scherer)
- PR#6648: show_module should indicate its elision - PR#6648: show_module should indicate its elision
(Jacques Garrigue, report by Leo White) (Jacques Garrigue, report by Leo White)
- PR#6650: Cty_constr not handled correctly by Subst - PR#6650: Cty_constr not handled correctly by Subst
(Jacques Garrigue, report by Leo White) (Jacques Garrigue, report by Leo White)
- PR#6651: Failing component lookup - PR#6651: Failing component lookup
(Jacques Garrigue, report by Leo White) (Jacques Garrigue, report by Leo White)
* PR#6664: Crash when finalising lazy values of the wrong type. * PR#6664: Crash when finalising lazy values of the wrong type.
(Damien Doligez) (Damien Doligez)
- PR#6672: Unused variance specification allowed in with constraint - PR#6672: Unused variance specification allowed in with constraint
(Jacques Garrigue, report by Leo White) (Jacques Garrigue, report by Leo White)
- PR#6677: Allow to disable warning 39 (useless "rec") with [@ocaml.warning] - PR#6677: Allow to disable warning 39 (useless "rec") with [@ocaml.warning]
applied to the first value binding of the would-be "rec" declaration applied to the first value binding of the would-be "rec" declaration
(Alain Frisch, report by Jun Furuse) (Alain Frisch, report by Jun Furuse)
- PR#6744: Univars can escape through polymorphic variants (partial fix) - PR#6744: Univars can escape through polymorphic variants (partial fix)
(Jacques Garrigue, report by Leo White) (Jacques Garrigue, report by Leo White)
- PR#6752: Extensible variant types and scope escaping - PR#6752: Extensible variant types and scope escaping
A side-effect of the fix is that (ocamlc -i) sometimes reports A side-effect of the fix is that (ocamlc -i) sometimes reports
(type-sound) invalid signature, with a type used before its declaration. (type-sound) invalid signature, with a type used before its declaration.
(Jacques Garrigue, report by Maxence Guesdon) (Jacques Garrigue, report by Maxence Guesdon)
- PR#6762: improve warning 45 in presence of re-exported type definitions - PR#6762: improve warning 45 in presence of re-exported type definitions
(Warning 45: open statement shadows the constructor) (Warning 45: open statement shadows the constructor)
(Alain Frisch, report by Olivier Andrieu) (Alain Frisch, report by Olivier Andrieu)
- PR#6776: Failure to kill the "tick" thread, segfault when exiting the runtime - PR#6776: Failure to kill the "tick" thread, segfault when exiting the runtime
(Damien Doligez, report by Thomas Braibant) (Damien Doligez, report by Thomas Braibant)
- PR#6780: Poor error message for wrong -farch and -ffpu options (ocamlopt, ARM) - PR#6780: Poor error message for wrong -farch and -ffpu options (ocamlopt, ARM)
(Xavier Leroy, report by whitequark) (Xavier Leroy, report by whitequark)
- PR#6805: Duplicated expression in case of hole in a non-failing switch. - PR#6805: Duplicated expression in case of hole in a non-failing switch.
(Luc Maranget) (Luc Maranget)
- PR#6808: the parsing of OCAMLRUNPARAM is too lax - PR#6808: the parsing of OCAMLRUNPARAM is too lax
(Damien Doligez) (Damien Doligez)
- PR#6874: Inefficient code generated for module function arguments - PR#6874: Inefficient code generated for module function arguments
(Jacques Garrigue, report by Markus Mottl) (Jacques Garrigue, report by Markus Mottl)
- PR#6888: The list command of ocamldebug uses the wrong file - PR#6888: The list command of ocamldebug uses the wrong file
(Damien Doligez, report by Pierre-Marie Pédrot) (Damien Doligez, report by Pierre-Marie Pédrot)
- PR#6897: Bad error message for some pattern matching on extensible variants - PR#6897: Bad error message for some pattern matching on extensible variants
(Alain Frisch, report by Gabriel Radanne) (Alain Frisch, report by Gabriel Radanne)
- PR#6899: Optional parameters and non generalizable type variables - PR#6899: Optional parameters and non generalizable type variables
(Thomas Refis and Leo White) (Thomas Refis and Leo White)
- PR#6907: Stack overflow printing error in class declaration - PR#6907: Stack overflow printing error in class declaration
(Jacques Garrigue, report by Ivan Gotovchits) (Jacques Garrigue, report by Ivan Gotovchits)
- PR#6931: Incorrect error message on type error inside record construction - PR#6931: Incorrect error message on type error inside record construction
(Damien Doligez, report by Leo White) (Damien Doligez, report by Leo White)
- PR#6938: fix regression on "%047.27{l,L,n}{d,i,x,X,o,u}" - PR#6938: fix regression on "%047.27{l,L,n}{d,i,x,X,o,u}"
(Benoît Vaugon, report by Arduino Cascella) (Benoît Vaugon, report by Arduino Cascella)
- PR#6944: let module X = Path in … is not typed as a module alias - PR#6944: let module X = Path in … is not typed as a module alias
(Jacques Garrigue, report by Frédéric Bour) (Jacques Garrigue, report by Frédéric Bour)
- PR#6945 and GPR#227: protect Sys and Unix functions against string - PR#6945 and GPR#227: protect Sys and Unix functions against string
arguments containing the null character '\000' arguments containing the null character '\000'
(Simon Cruanes and Xavier Leroy, report by Daniel Bünzli) (Simon Cruanes and Xavier Leroy, report by Daniel Bünzli)
- PR#6946: Uncaught exception with wrong type for "%ignore" - PR#6946: Uncaught exception with wrong type for "%ignore"
(Jacques Garrigue, report by Leo White) (Jacques Garrigue, report by Leo White)
- PR#6954: Infinite loop in type checker with module aliases - PR#6954: Infinite loop in type checker with module aliases
(Jacques Garrigue, report by Mark Mottl) (Jacques Garrigue, report by Mark Mottl)
- PR#6972, GPR#276: 4.02.3 regression on documentation comments in .cmt files - PR#6972, GPR#276: 4.02.3 regression on documentation comments in .cmt files
(Leo White, report by Olivier Andrieu) (Leo White, report by Olivier Andrieu)
- PR#6977: String literals in comments interpret escape sequences - PR#6977: String literals in comments interpret escape sequences
(Damien Doligez, report by Daniel Bünzli and David Sheets) (Damien Doligez, report by Daniel Bünzli and David Sheets)
- PR#6980: Assert failure from polymorphic variants and existentials - PR#6980: Assert failure from polymorphic variants and existentials
(Jacques Garrigue, report by Leo White) (Jacques Garrigue, report by Leo White)
- PR#6981: Ctype.Unify(_) with associated functor arg refering to previous one - PR#6981: Ctype.Unify(_) with associated functor arg refering to previous one
(Jacques Garrigue, report by Nicholas Labich) (Jacques Garrigue, report by Nicholas Labich)
- PR#6982: unexpected type error when packing a module alias - PR#6982: unexpected type error when packing a module alias
(Jacques Garrigue, report by Valentin Gatien-Baron) (Jacques Garrigue, report by Valentin Gatien-Baron)
- PR#6985: `module type of struct include Bar end exposes - PR#6985: `module type of struct include Bar end exposes
%s#row when Bar contains private row types %s#row when Bar contains private row types
(Jacques Garrigue, report by Nicholas Labich) (Jacques Garrigue, report by Nicholas Labich)
- PR#6992: Segfault from bug in GADT/module typing - PR#6992: Segfault from bug in GADT/module typing
(Jacques Garrigue, report by Stephen Dolan) (Jacques Garrigue, report by Stephen Dolan)
- PR#6993: Segfault from recursive modules violating exhaustiveness assumptions - PR#6993: Segfault from recursive modules violating exhaustiveness assumptions
(Jacques Garrigue, report by Stephen Dolan) (Jacques Garrigue, report by Stephen Dolan)
- PR#6998: Typer fails reading unnecessary cmis with -no-alias-deps and -w -49 - PR#6998: Typer fails reading unnecessary cmis with -no-alias-deps and -w -49
(Leo White, report by Valentin Gatien-Baron) (Leo White, report by Valentin Gatien-Baron)
- PR#7003: String.sub may cause segmentation fault on sizes above 2^31 - PR#7003: String.sub may cause segmentation fault on sizes above 2^31
(Damien Doligez, report by Radek Micek) (Damien Doligez, report by Radek Micek)
- PR#7008: Fatal error in ocamlc with empty compilation unit name - PR#7008: Fatal error in ocamlc with empty compilation unit name
(Damien Doligez, report by Cesar Kunz) (Damien Doligez, report by Cesar Kunz)
- PR#7012: Variable name forgotten when it starts with a capital letter - PR#7012: Variable name forgotten when it starts with a capital letter
(Jacques Garrigue, Gabriel Scherer, (Jacques Garrigue, Gabriel Scherer,
report by Thomas Leonard and Florian Angeletti) report by Thomas Leonard and Florian Angeletti)
- PR#7016: fix Stack overflow in GADT typing - PR#7016: fix Stack overflow in GADT typing
Note: Equi-recursive types are considered when checking GADT pattern Note: Equi-recursive types are considered when checking GADT pattern
exhaustiveness, even when -rectypes is not used. exhaustiveness, even when -rectypes is not used.
(Jacques Garrigue, report by Mikhail Mandrykin) (Jacques Garrigue, report by Mikhail Mandrykin)
- PR#7030: libasmrun_shared.so fails to build on SPARC Solaris - PR#7030: libasmrun_shared.so fails to build on SPARC Solaris
(report and fix by Patrick Star) (report and fix by Patrick Star)
- PR#7036: Module alias is not taken into account when checking module - PR#7036: Module alias is not taken into account when checking module
type compatibility (in a class type) type compatibility (in a class type)
(Jacques Garrigue) (Jacques Garrigue)
- PR#7037: more reproducible builds, don't put temp file names into objects - PR#7037: more reproducible builds, don't put temp file names into objects
(Xavier Leroy) (Xavier Leroy)
- PR#7038: out of memory condition in caml_io_mutex_lock - PR#7038: out of memory condition in caml_io_mutex_lock
(Xavier Leroy, report by Marc Lasson) (Xavier Leroy, report by Marc Lasson)
- PR#7039: Unix.getsockname returns garbage for unnamed PF_UNIX sockets - PR#7039: Unix.getsockname returns garbage for unnamed PF_UNIX sockets
(Xavier Leroy) (Xavier Leroy)
- PR#7042 and GPR#295: CSE optimization confuses the FP literals +0.0 and -0.0 - PR#7042 and GPR#295: CSE optimization confuses the FP literals +0.0 and -0.0
(Xavier Leroy) (Xavier Leroy)
- PR#7075: Fix repetitions in ocamldoc generated documentation - PR#7075: Fix repetitions in ocamldoc generated documentation
(Florian Angeletti) (Florian Angeletti)
- PR#7082: Object type in recursive module's `with` annotation - PR#7082: Object type in recursive module's `with` annotation
(Jacques Garrigue and Alain Frisch, report by Nicholas Labich) (Jacques Garrigue and Alain Frisch, report by Nicholas Labich)
- PR#7096: ocamldoc uses an incorrect subscript/superscript style - PR#7096: ocamldoc uses an incorrect subscript/superscript style
(Gabriel Scherer, report by user 'pierpa') (Gabriel Scherer, report by user 'pierpa')
- PR#7108: ocamldoc, have -html preserve custom/extended html generators - PR#7108: ocamldoc, have -html preserve custom/extended html generators
(Armaël Guéneau) (Armaël Guéneau)
- PR#7111: reject empty let bindings instead of printing incorrect syntax - PR#7111: reject empty let bindings instead of printing incorrect syntax
(Jérémie Dimino) (Jérémie Dimino)
* PR#7113: -safe-string can break GADT compatibility check * PR#7113: -safe-string can break GADT compatibility check
bytes and string are now considered compatible even with -safe-string, bytes and string are now considered compatible even with -safe-string,
which may break exhaustivity for code assuming they were disjoint which may break exhaustivity for code assuming they were disjoint
(Jacques Garrigue, report by Jeremy Yallop) (Jacques Garrigue, report by Jeremy Yallop)
- PR#7115: shadowing in a branch of a GADT match breaks unused variable warning - PR#7115: shadowing in a branch of a GADT match breaks unused variable warning
(Alain Frisch, report by Valentin Gatien-Baron) (Alain Frisch, report by Valentin Gatien-Baron)
- PR#7133, GPR#450: generate local jump labels on OS X - PR#7133, GPR#450: generate local jump labels on OS X
(Bart Jacobs) (Bart Jacobs)
- PR#7135: only warn about ground coercions in -principal mode - PR#7135: only warn about ground coercions in -principal mode
(Jacques Garrigue, report by Jeremy Yallop) (Jacques Garrigue, report by Jeremy Yallop)
- PR#7152: Typing equality involving non-generalizable type variable - PR#7152: Typing equality involving non-generalizable type variable
(Jacques Garrigue, report by François Bobot) (Jacques Garrigue, report by François Bobot)
- PR#7160: Type synonym definitions can weaken gadt constructor types - PR#7160: Type synonym definitions can weaken gadt constructor types
(Jacques Garrigue, report by Mikhail Mandrykin) (Jacques Garrigue, report by Mikhail Mandrykin)
- PR#7182: Assertion failure with recursive modules and externals - PR#7182: Assertion failure with recursive modules and externals
(Jacques Garrigue, report by Jeremy Yallop) (Jacques Garrigue, report by Jeremy Yallop)
- GPR#205: Clear caml_backtrace_last_exn before registering as root - GPR#205: Clear caml_backtrace_last_exn before registering as root
(report and fix by Frederic Bour) (report and fix by Frederic Bour)
- GPR#220: minor -dsource error on recursive modules - GPR#220: minor -dsource error on recursive modules
(Hongbo Zhang) (Hongbo Zhang)
- GPR#228: fix a dangling internal pointer in (bytecode )debug_info - GPR#228: fix a dangling internal pointer in (bytecode )debug_info
(Gabriel Scherer and Mark Shinwell and Xavier Leroy) (Gabriel Scherer and Mark Shinwell and Xavier Leroy)
- GPR#233: Make CamlinternalMod.init_mod robust to optimization - GPR#233: Make CamlinternalMod.init_mod robust to optimization
(Pierre Chambart, Mark Shinwell) (Pierre Chambart, Mark Shinwell)
- GPR#249: fix a few hardcoded ar commands - GPR#249: fix a few hardcoded ar commands
(Daniel Bünzli) (Daniel Bünzli)
- GPR#251: fix cross-compilation with ocamldoc enabled - GPR#251: fix cross-compilation with ocamldoc enabled
(whitequark) (whitequark)
- GPR#280: Fix stdlib dependencies for .p.cmx - GPR#280: Fix stdlib dependencies for .p.cmx
(Pierre Chambart, Mark Shinwell) (Pierre Chambart, Mark Shinwell)
- GPR#283: Fix memory leaks in intern.c when OOM is raised - GPR#283: Fix memory leaks in intern.c when OOM is raised
(Marc Lasson, review by Alain Frisch) (Marc Lasson, review by Alain Frisch)
- GPR#22: Fix the cleaning of weak pointers. In very rare cases - GPR#22: Fix the cleaning of weak pointers. In very rare cases
accessing a value during the cleaning of the weak pointers could accessing a value during the cleaning of the weak pointers could
result in the value being removed from one weak arrays and kept in 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 another one. That breaks the property that a value is removed from a
weak pointer only when it is dead and garbage collected. weak pointer only when it is dead and garbage collected.
(François Bobot, review by Damien Doligez) (François Bobot, review by Damien Doligez)
- GPR#313: Prevent quadratic cases in CSE - GPR#313: Prevent quadratic cases in CSE
(Pierre Chambart, review by Xavier Leroy) (Pierre Chambart, review by Xavier Leroy)
- PR#6795, PR#6996: Make ocamldep report errors passed in - PR#6795, PR#6996: Make ocamldep report errors passed in
[%ocaml.error] extension points [%ocaml.error] extension points
(Jérémie Dimino) (Jérémie Dimino)
- GPR#355: make ocamlnat build again - GPR#355: make ocamlnat build again
(Jérémie Dimino, Thomas Refis) (Jérémie Dimino, Thomas Refis)
- GPR#405: fix compilation under Visual Studio 2015 - GPR#405: fix compilation under Visual Studio 2015
(David Allsopp) (David Allsopp)
- GPR#441: better type error location in presence of type constraints - GPR#441: better type error location in presence of type constraints
(Thomas Refis, report by Arseniy Alekseyev) (Thomas Refis, report by Arseniy Alekseyev)
- GPR#477: reallow docstrings inside object types, and inside polymorphic - GPR#477: reallow docstrings inside object types, and inside polymorphic
variant and arrow types variant and arrow types
(Thomas Refis) (Thomas Refis)
Features wishes: Features wishes:
================
- PR#4518, GPR#29: change location format for reporting errors in ocamldoc - PR#4518, GPR#29: change location format for reporting errors in ocamldoc
(Sergei Lebedev) (Sergei Lebedev)
- PR#4714: List.cons - PR#4714: List.cons
- PR#5418 (comments) : generate dependencies with $(CC) instead of gcc - PR#5418 (comments) : generate dependencies with $(CC) instead of gcc
(Damien Doligez, report by Michael Grünewald) (Damien Doligez, report by Michael Grünewald)
- PR#6167: OCAMLPARAM support for disabling PIC generation ("pic=0") - PR#6167: OCAMLPARAM support for disabling PIC generation ("pic=0")
(Gabor Pali) (Gabor Pali)
- PR#6367, GPR#25: introduce Asttypes.arg_label to encode labelled arguments - PR#6367, GPR#25: introduce Asttypes.arg_label to encode labelled arguments
(Frédéric Bour and Jacques Garrigue) (Frédéric Bour and Jacques Garrigue)
- PR#6452, GPR#140: add internal suport for custom printing formats - PR#6452, GPR#140: add internal suport for custom printing formats
(Jérémie Dimino) (Jérémie Dimino)
- PR#6611: remove the option wrapper on optional arguments in the syntax tree - PR#6611: remove the option wrapper on optional arguments in the syntax tree
(Alain Frisch, review by Damien Doligez, request by whitequark) (Alain Frisch, review by Damien Doligez, request by whitequark)
- PR#6635: support M.[], M.(), M.{< >} and M.[| |] - PR#6635: support M.[], M.(), M.{< >} and M.[| |]
(Jeremy Yallop, review by Gabriel Radanne) (Jeremy Yallop, review by Gabriel Radanne)
- PR#6691: install .cmt[i] files for stdlib and compiler-libs - PR#6691: install .cmt[i] files for stdlib and compiler-libs
(David Sheets, request by Gabriel Radanne) (David Sheets, request by Gabriel Radanne)
- PR#6722: compatibility with x32 architecture (x86-64 in ILP32 mode). - PR#6722: compatibility with x32 architecture (x86-64 in ILP32 mode).
ocamlopt is not supported, but bytecode compiles cleanly. ocamlopt is not supported, but bytecode compiles cleanly.
(Adam Borowski and Xavier Leroy) (Adam Borowski and Xavier Leroy)
- PR#6742: remove duplicate virtual_flag information from Tstr_class - PR#6742: remove duplicate virtual_flag information from Tstr_class
(Gabriel Radanne and Jacques Garrigue) (Gabriel Radanne and Jacques Garrigue)
- PR#6719: improve Buffer.add_channel when not enough input is available - PR#6719: improve Buffer.add_channel when not enough input is available
(Simon Cruanes) (Simon Cruanes)
* PR#6816: reject integer and float literals directly followed by an identifier. * PR#6816: reject integer and float literals directly followed by an identifier.
This was prevously read as two separate tokens. This was prevously read as two separate tokens.
[let abc = 1 in (+) 123abc] was accepted and is now rejected. [let abc = 1 in (+) 123abc] was accepted and is now rejected.
(Hugo Heuzard) (Hugo Heuzard)
- PR#6876: improve warning 6 by listing the omitted labels. - PR#6876: improve warning 6 by listing the omitted labels.
(Warning 6: Label omitted in function application) (Warning 6: Label omitted in function application)
(Eyyüb Sari) (Eyyüb Sari)
- PR#6924: tiny optim to avoid some spilling of floats in x87 - PR#6924: tiny optim to avoid some spilling of floats in x87
(Alain Frisch) (Alain Frisch)
- GPR#111: `(f [@taillcall]) x y` warns if `f x y` is not a tail-call - GPR#111: `(f [@taillcall]) x y` warns if `f x y` is not a tail-call
(Simon Cruanes) (Simon Cruanes)
- GPR#118: ocamldep -allow-approx: fallback to a lexer-based approximation - GPR#118: ocamldep -allow-approx: fallback to a lexer-based approximation
(Frédéric Bour) (Frédéric Bour)
- GPR#137: add untypeast.ml (in open recursion style) to compiler-libs - GPR#137: add untypeast.ml (in open recursion style) to compiler-libs
(Gabriel Radanne) (Gabriel Radanne)
- GPR#142: add a CAMLdrop macro for undoing CAMLparam*/CAMLlocal* - GPR#142: add a CAMLdrop macro for undoing CAMLparam*/CAMLlocal*
(Thomas Braibant and Damien Doligez) (Thomas Braibant and Damien Doligez)
- GPR#145: speeedup bigarray access by optimizing Cmmgen.bigarray_indexing - GPR#145: speeedup bigarray access by optimizing Cmmgen.bigarray_indexing
(Vladimir Brankov, review by Gabriel Scherer) (Vladimir Brankov, review by Gabriel Scherer)
- GPR#147: [type 'a result = Ok of 'a | Error of 'b] in Pervasives - GPR#147: [type 'a result = Ok of 'a | Error of 'b] in Pervasives
(Yaron Minsky) (Yaron Minsky)
- GPR#156, GPR#279: optimize caml_frame_descriptors realloc (dynlink speedup) - GPR#156, GPR#279: optimize caml_frame_descriptors realloc (dynlink speedup)
(Pierre Chambart, Alain Frisch, (Pierre Chambart, Alain Frisch,
review by François Bobot, Xavier Leroy and Damien Doligez) review by François Bobot, Xavier Leroy and Damien Doligez)
- GPR#165, GPR#221: fix windows compilation warnings - GPR#165, GPR#221: fix windows compilation warnings
(Bernhard Schommer, Gabriel Scherer, report by Alain Frisch) (Bernhard Schommer, Gabriel Scherer, report by Alain Frisch)
* GPR#170: Parse arbitrary precision integers. * GPR#170: Parse arbitrary precision integers.
Accept a single [A-Za-z] as modifier for integers (generalizing 'l','L','n') Accept a single [A-Za-z] as modifier for integers (generalizing 'l','L','n')
and floats. and floats.
@ -705,35 +959,49 @@ Features wishes:
This changes PR#6816 a little bit by reading the literal [123a] as a single This changes PR#6816 a little bit by reading the literal [123a] as a single
token that can later be rewritten by a ppx preprocessor. token that can later be rewritten by a ppx preprocessor.
(Hugo Heuzard) (Hugo Heuzard)
- GPR#189: Added .dylib and .so as extensions for ocamlmklib - GPR#189: Added .dylib and .so as extensions for ocamlmklib
(Edgar Aroutiounian, whitequark) (Edgar Aroutiounian, whitequark)
- GPR#191: Making gc.h and some part of memory.h public - GPR#191: Making gc.h and some part of memory.h public
(Thomas Refis) (Thomas Refis)
- GPR#196: Make [Thread.id] and [Thread.self] [noalloc] - GPR#196: Make [Thread.id] and [Thread.self] [noalloc]
(Clark Gaebel) (Clark Gaebel)
- GPR#237: a CONTRIBUTING document - GPR#237: a CONTRIBUTING document
(François Bobot, Gabriel Scherer, review by Xavier Leroy) (François Bobot, Gabriel Scherer, review by Xavier Leroy)
- GPR#245: remove a few remaining French comments - GPR#245: remove a few remaining French comments
(Florian Angeletti) (Florian Angeletti)
- GPR#252: improve build instructions in MSVC Windows README - GPR#252: improve build instructions in MSVC Windows README
(Philip Daian) (Philip Daian)
- GPR#308: add experimental support for NetBSD/arm (verified on RaspberryPi) - GPR#308: add experimental support for NetBSD/arm (verified on RaspberryPi)
(Rich Neswold) (Rich Neswold)
- GPR#335: Type error messages specifies if a type is abstract - GPR#335: Type error messages specifies if a type is abstract
because no corresponding cmi could be found. because no corresponding cmi could be found.
(Hugo Heuzard) (Hugo Heuzard)
- GPR#365: prevent printing just a single type variable on one side - GPR#365: prevent printing just a single type variable on one side
of a type error clash. of a type error clash.
(Hugo Heuzard) (Hugo Heuzard)
- GPR#383: configure: define _ALL_SOURCE for build on AIX7.1 - GPR#383: configure: define _ALL_SOURCE for build on AIX7.1
(tkob) (tkob)
- GPR#401: automatically retry failed test directories in the testsuite - GPR#401: automatically retry failed test directories in the testsuite
(David Allsopp) (David Allsopp)
- GPR#451: an optional 'parallel' target in testsuite/Makefile using the - GPR#451: an optional 'parallel' target in testsuite/Makefile using the
GNU parallel tool to run tests in parallel. GNU parallel tool to run tests in parallel.
(Gabriel Scherer) (Gabriel Scherer)
Build system: Build system:
=============
- GPR#388: FlexDLL added as a Git submodule and bootstrappable with the compiler - GPR#388: FlexDLL added as a Git submodule and bootstrappable with the compiler
(David Allsopp) (David Allsopp)

View File

@ -71,6 +71,7 @@ type error =
| No_value_clauses | No_value_clauses
| Exception_pattern_below_toplevel | Exception_pattern_below_toplevel
| Inlined_record_escape | Inlined_record_escape
| Inlined_record_expected
| Unrefuted_pattern of pattern | Unrefuted_pattern of pattern
| Invalid_extension_constructor_payload | Invalid_extension_constructor_payload
| Not_an_extension_constructor | Not_an_extension_constructor
@ -120,11 +121,6 @@ let rp node =
;; ;;
let is_recarg d =
match (repr d.val_type).desc with
| Tconstr(p, _, _) -> Path.is_constructor_typath p
| _ -> false
type recarg = type recarg =
| Allowed | Allowed
| Required | Required
@ -1937,10 +1933,22 @@ and type_expect_ ?in_function ?(recarg=Rejected) env sexp ty_expected =
let name = Path.name ~paren:Oprint.parenthesized_ident path in let name = Path.name ~paren:Oprint.parenthesized_ident path in
Stypes.record (Stypes.An_ident (loc, name, annot)) Stypes.record (Stypes.An_ident (loc, name, annot))
end; end;
begin match is_recarg desc, recarg with let is_recarg =
| _, Allowed | true, Required | false, Rejected -> () match (repr desc.val_type).desc with
| true, Rejected | false, Required -> | Tconstr(p, _, _) -> Path.is_constructor_typath p
raise (Error (loc, env, Inlined_record_escape)); | _ -> false
in
begin match is_recarg, recarg, (repr desc.val_type).desc with
| _, Allowed, _
| true, Required, _
| false, Rejected, _
-> ()
| true, Rejected, _
| false, Required, Tvar _ ->
raise (Error (loc, env, Inlined_record_escape))
| false, Required, _ ->
() (* will fail later *)
end; end;
rue { rue {
exp_desc = exp_desc =
@ -3655,7 +3663,7 @@ and type_construct env loc lid sarg ty_expected attrs =
Pexp_record (_, (Some {pexp_desc = Pexp_ident _}| None))}] -> Pexp_record (_, (Some {pexp_desc = Pexp_ident _}| None))}] ->
Required Required
| _ -> | _ ->
raise (Error(loc, env, Inlined_record_escape)) raise (Error(loc, env, Inlined_record_expected))
end end
in in
let args = let args =
@ -4320,6 +4328,9 @@ let report_error env ppf = function
fprintf ppf fprintf ppf
"@[This form is not allowed as the type of the inlined record could \ "@[This form is not allowed as the type of the inlined record could \
escape.@]" escape.@]"
| Inlined_record_expected ->
fprintf ppf
"@[This constructor expects an inlined record argument.@]"
| Unrefuted_pattern pat -> | Unrefuted_pattern pat ->
fprintf ppf fprintf ppf
"@[%s@ %s@ %a@]" "@[%s@ %s@ %a@]"

View File

@ -116,6 +116,7 @@ type error =
| No_value_clauses | No_value_clauses
| Exception_pattern_below_toplevel | Exception_pattern_below_toplevel
| Inlined_record_escape | Inlined_record_escape
| Inlined_record_expected
| Unrefuted_pattern of Typedtree.pattern | Unrefuted_pattern of Typedtree.pattern
| Invalid_extension_constructor_payload | Invalid_extension_constructor_payload
| Not_an_extension_constructor | Not_an_extension_constructor