1OCaml 4.05.0 (13 Jul 2017):
2---------------------------
3
4(Changes that can break existing programs are marked with a "*")
5
6### Language features:
7
8### Code generation and optimizations:
9
10- MPR#7201, GPR#954: Correct wrong optimisation of "0 / <expr>"
11  and "0 mod <expr>" in the case when <expr> was a non-constant
12  evaluating to zero
13  (Mark Shinwell, review by Gabriel Scherer, Leo White and Xavier Leroy)
14
15- MPR#7357, GPR#832: Improve compilation time for toplevel
16  include(struct ... end : sig ... end)
17  (Alain Frisch, report by Hongbo Zhang, review by Jacques Garrigue)
18
19- MPR#7533, GPR#1173: Correctly perform side effects for certain
20  cases of "/" and "mod"
21  (Mark Shinwell, report by Jan Mitgaard)
22
23- GPR#504: Instrumentation support for fuzzing with afl-fuzz.
24  (Stephen Dolan, review by Alain Frisch, Pierre Chambart, Mark
25  Shinwell, Gabriel Scherer and Damien Doligez)
26
27- GPR#863, GPR#1068, GPR#1069: Optimise matches with constant
28  results to lookup tables.
29  (Stephen Dolan, review by Gabriel Scherer, Pierre Chambart,
30  Mark Shinwell, and bug report by Gabriel Scherer)
31
32- GPR#1150: Fix typo in arm64 assembler directives
33  (KC Sivaramakrishnan)
34
35### Runtime system:
36
37- MPR#385, GPR#953: Add caml_startup_exn
38  (Mark Shinwell)
39
40- MPR#7423, GPR#946: expose new exception-raising functions
41  `void caml_{failwith,invalid_argument}_value(value msg)`
42  in addition to
43  `void caml_{failwith,invalid_argument}(char const *msg)`.
44  The previous functions would not free their message argument, so
45  were inconvient for dynamically-allocated messages; the messages
46  passed to the new functions are handled by the garbage collector.
47  (Gabriel Scherer, review by Mark Shinwell, request by Immanuel Litzroth)
48
49- MPR#7557, GPR#1213: More security for getenv
50  (Damien Doligez, reports by Seth Arnold and Eric Milliken, review by
51  Xavier Leroy, David Allsopp, Stephen Dolan, Hannes Mehnert)
52
53- GPR#795: remove 256-character limitation on Sys.executable_name
54  (Xavier Leroy)
55
56- GPR#891: Use -fno-builtin-memcmp when building runtime with gcc.
57  (Leo White)
58
59### Type system:
60
61- MPR#6608, GPR#901: unify record types when overriding all fields
62  (Tadeu Zagallo and Gabriel Scherer, report by Jeremy Yallop,
63  review by David Allsopp, Jacques Garrigue)
64
65* MPR#7414, GPR#929: Soundness bug with non-generalized type variables and
66  functors.
67  (Jacques Garrigue, report by Leo White)
68
69### Compiler user-interface and warnings:
70
71- MPR#7050, GPR#748 GPR#843 GPR#864: new `-args/-args0 <file>` parameters to
72  provide extra command-line arguments in a file -- see documentation.
73  User programs may implement similar options using the new `Expand`
74  constructor of the `Arg` module.
75  (Bernhard Schommer, review by Jérémie Dimino, Gabriel Scherer
76   and Damien Doligez, discussion with Alain Frisch and Xavier Leroy,
77   feature request from the Coq team)
78
79- MPR#7137, GPR#960: "-open" command line flag now accepts
80  a module path (not a module name)
81  (Arseniy Alekseyev and Leo White)
82
83- MPR#7172, GPR#970: add extra (ocamlc -config) options
84  int_size, word_size, ext_exe
85  (Gabriel Scherer, request by Daniel Bünzli)
86
87- MPR#7315, GPR#736: refine some error locations
88  (Gabriel Scherer and Alain Frisch, report by Matej Košík)
89
90- MPR#7473, GPR#1025: perform proper globbing for command-line arguments on
91  Windows
92  (Jonathan Protzenko)
93
94- MPR#7479: make sure "ocamlc -pack" is only given .cmo and .cmi files,
95  and that "ocamlopt -pack" is only given .cmx and .cmi files.
96  (Xavier Leroy)
97
98- GPR#796: allow compiler plugins to declare their own arguments.
99  (Fabrice Le Fessant)
100
101- GPR#829: better error when opening a module aliased to a functor
102  (Alain Frisch)
103
104- GPR#911: ocamlc/ocamlopt do not pass warnings-related options to C
105  compiler when called to compile third-party C source files
106  (Sébastien Hinderer, review by Adrien Nader and David Allsopp)
107
108- GPR#915: fix -dsource (pprintast.ml) bugs
109  (Runhang Li, review by Alain Frisch)
110
111* GPR#933: ocamlopt -p now reports an error on platforms that do not
112  support profiling with gprof; dummy profiling libraries are no longer
113  installed on such platforms.
114  This can be tested with ocamlopt -config
115  (Sébastien Hinderer)
116
117- GPR#1009: "ocamlc -c -linkall" and "ocamlopt -c -linkall" can now be used
118  to set the "always link" flag on individual compilation units.  This
119  controls linking with finer granularity than "-a -linkall", which sets
120  the "always link" flag on all units of the given library.
121  (Xavier Leroy)
122
123- GPR#1015: add option "-plugin PLUGIN" to ocamldep too. Use compilerlibs
124  to build ocamldep.
125  (Fabrice Le Fessant)
126
127- GPR#1027: various improvements to -dtimings, mostly including time
128  spent in subprocesses like preprocessors
129  (Valentin Gatien-Baron, review by Gabriel Scherer)
130
131- GPR#1098: the compiler now takes the boolean "OCAML_COLOR" environment
132  variable into account if "-color" is not provided.  This allows users
133  to override the default behaviour without modifying invocations of ocaml
134  manually.
135  (Hannes Mehnert, Guillaume Bury,
136   review by Daniel Bünzli, Gabriel Scherer, Damien Doligez)
137
138### Standard library:
139
140- MPR#6975, GPR#902: Truncate function added to stdlib Buffer module
141  (Dhruv Makwana, review by Alain Frisch and Gabriel Scherer)
142
143- MPR#7279, GPR#710: `Weak.get_copy` `Ephemeron.*_copy` doesn't copy
144  custom blocks anymore
145  (François Bobot, Alain Frisch, bug reported by Martin R. Neuhäußer,
146  review by Thomas Braibant and Damien Doligez)
147
148* MPR#7500, GPR#1081: Remove Uchar.dump
149  (Daniel Bünzli)
150
151- GPR#760: Add a functions List.compare_lengths and
152  List.compare_length_with to avoid full list length computations
153  (Fabrice Le Fessant, review by Leo White, Josh Berdine and Gabriel Scherer)
154
155- GPR#778: Arg: added option Expand that allows to expand a string
156  argument to a string array of new arguments
157  (Bernhard Schommer, review by Gabriel Scherer and Jérémie Dimino)
158
159- GPR#849: Expose a Spacetime.enabled value
160  (Leo White)
161
162- GPR#885: Option-returning variants of stdlib functions
163  (Alain Frisch, review by David Allsopp and Bart Jacobs)
164
165- GPR#869: Add find_first, find_first_opt, find_last, find_last_opt to
166  maps and sets.  Find the first or last binding or element
167  satisfying a monotonic predicate.
168  (Gabriel de Perthuis, with contributions from Alain Frisch, review by
169  Hezekiah M. Carty and Simon Cruanes, initial report by Gerd Stolpmann)
170
171- GPR#875: Add missing functions to ArrayLabels, BytesLabels,
172  ListLabels, MoreLabels, StringLabels so they are compatible with
173  non-labeled counterparts. Also add missing @@ocaml.deprecated attributes
174  in StringLabels and BytesLabels.
175  (Roma Sokolov, review by Gabriel Scherer, Jacques Garrigue,
176   Gabriel Radanne, Alain Frisch)
177
178- GPR#999: Arg, do not repeat the usage message thrice when reporting an error
179  (this was a regression in 4.03)
180  (Florian Angeletti, review by Gabriel Scherer)
181
182- GPR#1042: Fix escaping of command-line arguments in
183  Unix.create_process{,_env} under Windows.  Arguments with tabs should now
184  be received verbatim by the child process.
185  (Nicolas Ojeda Bar, Andreas Hauptmann review by Xavier Leroy)
186
187### Debugging and profiling:
188
189- MPR#7258: ocamldebug's "install_printer" command had problems with
190  module aliases
191  (Xavier Leroy)
192
193- GPR#378: Add [Printexc.raise_with_backtrace] to raise an exception using
194  an explicit backtrace
195  (François Bobot, review by Gabriel Scherer, Xavier Leroy, Damien Doligez,
196   Frédéric Bour)
197
198### Manual and documentation:
199
200- MPR#6597, GPR#1030: add forward references to language extensions
201  that extend non-terminal symbols in the language reference section.
202  (Florian Angeletti, review by Gabriel Scherer)
203
204- MPR#7497, GPR#1095: manual, enable numbering for table of contents
205  (Florian Angeletti, request by Daniel Bünzli)
206
207- MPR#7539, GPR#1181: manual, update dead links in ocamldoc chapter
208  (Florian Angeletti)
209
210- GPR#633: manpage and manual documentation for the `-opaque` option
211  (Konstantin Romanov, Gabriel Scherer, review by Mark Shinwell)
212
213- GPR#751, GPR#925: add a HACKING.adoc file to contain various
214  tips and tricks for people hacking on the repository. See also
215  CONTRIBUTING.md for advice on sending contributions upstream.
216  (Gabriel Scherer and Gabriel Radanne, review by David Allsopp,
217  inspired by John Whitington)
218
219- GPR#916: new tool lintapidiff, use it to update the manual with
220  @since annotations for API changes introduced between 4.00-4.05.
221  (Edwin Török, review by Gabriel Scherer, discussion with Alain Frisch,
222   David Allsopp, Sébastien Hinderer, Damien Doligez and Xavier Leroy)
223
224- GPR#939: activate the caml_example environment in the language
225  extensions section of the manual. Convert some existing code
226  examples to this format.
227  (Florian Angeletti)
228
229- GPR#1082: clarify that the use of quoted string for preprocessed
230  foreign quotations still requires the use of an extension node
231  [%foo ...] to mark non-standard interpretation.
232  (Gabriel Scherer, request by Matthew Wahab in GPR#1066,
233   review by Florian Angeletti)
234
235### Other libraries:
236
237- MPR#7158: Event.sync, Mutex.create, Condition.create cause too many GCs.
238  The fix is to no longer consider mutexes and condition variables
239  as rare kernel resources.
240  (Xavier Leroy)
241
242- MPR#7264: document the different behaviors of Unix.lockf under POSIX
243  and under Win32.
244  (Xavier Leroy, report by David Allsopp)
245
246- MPR#7339, GPR#787: Support the '0 dimension' case for bigarrays
247  (see Bigarray documentation)
248  (Laurent Mazare,
249   review by Gabriel Scherer, Alain Frisch and Hezekiah M. Carty)
250
251* MPR#7342, GPR#797: fix Unix.read on pipes with no data left on Windows
252  it previously raised an EPIPE error, it now returns 0 like other OSes
253  (Jonathan Protzenko, review by Andreas Hauptmann and Damien Doligez)
254
255- GPR#650: in the Unix library, add `?cloexec:bool` optional arguments to
256  functions that create file descriptors (`dup`, `dup2`, `pipe`, `socket`,
257  `socketpair`, `accept`).  Implement these optional arguments in the
258  most atomic manner provided by the operating system to set (or clear)
259  the close-on-exec flag at the same time the file descriptor is created,
260  reducing the risk of race conditions with `exec` or `create_process`
261  calls running in other threads, and improving security.  Also: add a
262  `O_KEEPEXEC` flag for `openfile` by symmetry with `O_CLOEXEC`.
263  (Xavier Leroy, review by Mark Shinwell, David Allsopp and Alain Frisch,
264   request by Romain Beauxis)
265
266- GPR#996: correctly update caml_top_of_stack in systhreads
267  (Fabrice Le Fessant)
268
269### Toplevel:
270
271- MPR#7060, GPR#1035: Print exceptions in installed custom printers
272  (Tadeu Zagallo, review by David Allsopp)
273
274### Tools:
275
276- MPR#5163: ocamlobjinfo, dump globals defined by bytecode executables
277  (Stéphane Glondu)
278
279- MPR#7333: ocamldoc, use the first sentence of text file as
280  a short description in overviews.
281  (Florian Angeletti)
282
283- GPR#848: ocamldoc, escape link targets in HTML output
284  (Etienne Millon, review by Gabriel Scherer, Florian Angeletti and
285  Daniel Bünzli)
286
287- GPR#986: ocamldoc, use relative paths in error message
288  to solve ocamlbuild+doc usability issue (ocaml/ocamlbuild#79)
289  (Gabriel Scherer, review by Florian Angeletti, discussion with Daniel Bünzli)
290
291- GPR#1017: ocamldoc, add an option to detect code fragments that could be
292  transformed into a cross-reference to a known element.
293  (Florian Angeletti, review and suggestion by David Allsopp)
294
295- clarify ocamldoc text parsing error messages
296  (Gabriel Scherer)
297
298### Compiler distribution build system:
299
300- MPR#7377: remove -std=gnu99 for newer gcc versions
301  (Damien Doligez, report by ygrek)
302
303- MPR#7452, GPR#1228: tweak GCC options to try to avoid the
304  Skylake/Kaby lake bug
305  (Damien Doligez, review by David Allsopp, Xavier Leroy and Mark Shinwell)
306
307- GPR#693: fail on unexpected errors or warnings within caml_example
308  environment.
309  (Florian Angeletti)
310
311- GPR#803: new ocamllex-based tool to extract bytecode compiler
312  opcode information from C headers.
313  (Nicolas Ojeda Bar)
314
315- GPR#827: install missing mli and cmti files, new make target
316  install-compiler-sources for installation of compiler-libs ml files
317  (Hendrik Tews)
318
319- GPR#887: allow -with-frame-pointers if clang is used as compiler on Linux
320  (Bernhard Schommer)
321
322- GPR#898: fix locale-dependence of primitive list order,
323  detected through reproducible-builds.org.
324  (Hannes Mehnert, review by Gabriel Scherer and Ximin Luo)
325
326- GPR#907: Remove unused variable from the build system
327  (Sébastien Hinderer, review by whitequark, Gabriel Scherer, Adrien Nader)
328
329- GPR#911: Clarify the use of C compiler related variables in the build system.
330  (Sébastien Hinderer, review by Adrien Nader, Alain Frisch, David Allsopp)
331
332- GPR#919: use clang as preprocessor assembler if clang is used as compiler
333  (Bernhard Schommer)
334
335- GPR#927: improve the detection of hashbang support in the configure script
336  (Armaël Guéneau)
337
338- GPR#932: install ocaml{c,lex}->ocaml{c,lex}.byte symlink correctly
339  when the opt target is built but opt.opt target is not.
340  (whitequark, review by Gabriel Scherer)
341
342- GPR#935: allow build in Android's termux
343  (ygrek, review by Gabriel Scherer)
344
345- GPR#984: Fix compilation of compiler distribution when Spacetime
346  enabled
347  (Mark Shinwell)
348
349- GPR#991: On Windows, fix installation when native compiler is not
350  built
351  (Sébastien Hinderer, review by David Allsopp)
352
353- GPR#1033: merge Unix and Windows build systems in the root directory
354  (Sébastien Hinderer, review by Damien Doligez and Adrien Nader)
355
356- GPR#1047: Make .depend files generated for C sources more portable
357  (Sébastien Hinderer, review by Xavier Leroy and David Allsopp)
358
359- GPR#1076: Simplify ocamlyacc's build system
360  (Sébastien Hinderer, review by David Allsopp)
361
362### Compiler distribution build system: Makefile factorization
363
364The compiler distribution build system (the set of Makefiles used to
365build the compiler distribution) traditionally had separate Makefiles
366for Unix and Windows, which lead to some amount of duplication and
367subtle differences and technical debt in general -- for people working
368on the compiler distribution, but also cross-compilation or porting to
369new systems. During the 4.05 development period, Sébastien Hinderer
370worked on harmonizing the build rules and merging the two build
371systems.
372
373* Some changes were made to the config/Makefile file which
374  is exported as $(ocamlc -where)/Makefile.config, and on
375  which some advanced users might rely. The changes are
376  as follows:
377  - a BYTERUN variable was added that points to the installed ocamlrun
378  - the PARTIALLD variable was removed (PACKLD is more complete)
379  - the always-empty DLLCCCOMPOPTS was removed
380  - the SHARED variable was removed; its value is "shared" or "noshared",
381    which duplicates the existing and more convenient
382    SUPPORTS_SHARED_LIBRARIES variable whose value is "true" or "false".
383
384  Note that Makefile.config may change further in the future and relying
385  on it is a bit fragile. We plan to make `ocamlc -config` easier to use
386  for scripting purposes, and have a stable interface there. If you rely
387  on Makefile.config, you may want to get in touch with Sébastien Hinderer
388  or participate to MPR#7116 (Allow easy retrieval of Makefile.config's values)
389  or MPR#7172 (More information in ocamlc -config).
390
391The complete list of changes is listed below.
392
393- GPR#705: update Makefile.nt so that ocamlnat compiles
394  for non-Cygwin Windows ports.
395  (Sébastien Hinderer, review by Alain Frisch)
396
397- GPR#729: Make sure ocamlnat is built with a $(EXE) extension, merge
398  rules between Unix and Windows Makefiles
399  (Sébastien Hinderer, review by Alain Frisch)
400
401- GPR#762: Merge build systems in the yacc/ directory.
402  (Sébastien Hinderer, review by David Allsopp, Alain Frisch)
403
404- GPR#764: Merge build systems in the debugger/ directory.
405  (Sébastien Hinderer, review by Alain Frisch)
406
407- GPR#785: Merge build systems in otherlibs/systhreads/
408  (Sébastien Hinderer, review by Alain Frisch, David Allsopp,
409   testing and regression fix by Jérémie Dimino)
410
411- GPR#788: Merge build systems in subdirectories of otherlibs/.
412  (Sébastien Hinderer, review by Alain Frisch)
413
414- GPR#808, GPR#906: Merge Unix and Windows build systems
415  in the ocamldoc/ directory
416  (Sébastien Hinderer, review by Alain Frisch)
417
418- GPR#812: Merge build systems in the tools/ subdirectory
419  (Sébastien Hinderer, review by Alain Frisch)
420
421- GPR#866: Merge build systems in the stdlib/ directory
422  (Sébastien Hinderer, review by David Allsopp and Adrien Nader)
423
424- GPR#941: Merge Unix and Windows build systems in the asmrun/ directory
425  (Sébastien Hinderer, review by Mark Shinwell, Adrien Nader,
426   Xavier Leroy, David Allsopp, Damien Doligez)
427
428- GPR#981: Merge build systems in the byterun/ directory
429  (Sébastien Hinderer, review by Adrien Nader)
430
431- GPR#1033, GPR#1048: Merge build systems in the root directory
432  (Sébastien Hinderer, review by Adrien Nader and Damien Doligez,
433   testing and regression fix by Andreas Hauptmann)
434
435### Internal/compiler-libs changes:
436
437- GPR#673: distinguish initialization of block fields from mutation in lambda.
438  (Frédéric Bour, review by Xavier Leroy, Stephen Dolan and Mark Shinwell)
439
440- GPR#744, GPR#781: fix duplicate self-reference in imported cmi_crcs
441  list in .cmti files + avoid rebuilding cmi_info record when creating
442  .cmti files
443  (Alain Frisch, report by Daniel Bünzli, review by Jérémie Dimino)
444
445- GPR#881: change `Outcometree.out_variant` to be more general.
446  `Ovar_name of out_ident * out_type list` becomes `Ovar_type of out_type`.
447  (Valentin Gatien-Baron, review by Leo White)
448
449- GPR#908: refactor PIC-handling in the s390x backend
450  (Gabriel Scherer, review by Xavier Leroy and Mark Shinwell)
451
452### Bug fixes
453
454- MPR#5115: protect all byterun/fail.c functions against
455  uninitialized caml_global_data (only changes the bytecode behavior)
456  (Gabriel Scherer, review by Xavier Leroy)
457
458- MPR#6136, GPR#967: Fix Closure so that overapplication evaluation order
459  matches the bytecode compiler and Flambda.
460  (Mark Shinwell, report by Jeremy Yallop, review by Frédéric Bour)
461
462- MPR#6550, GPR#1094: Allow creation of empty .cmxa files on macOS
463  (Mark Shinwell)
464
465- MPR#6594, GPR#955: Remove "Istore_symbol" specific operation on x86-64.
466  This is more robust and in particular avoids assembly failures on Win64.
467  (Mark Shinwell, review by Xavier Leroy, testing by David Allsopp and
468   Olivier Andrieu)
469
470- MPR#6903: Unix.execvpe doesn't change environment on Cygwin
471  (Xavier Leroy, report by Adrien Nader)
472
473- MPR#6987: Strange error message probably caused by
474  universal variable escape (with polymorphic variants)
475  (Jacques Garrigue, report by Mikhail Mandrykin and Leo White)
476
477- MPR#7216, GPR#949: don't require double parens in Functor((val x))
478  (Jacques Garrigue, review by Valentin Gatien-Baron)
479
480- MPR#7331: ocamldoc, avoid infinite loop in presence of self alias,
481  i.e. module rec M:sig end = M
482  (Florian Angeletti, review Gabriel Scherer)
483
484- MPR#7346, GPR#966: Fix evaluation order problem whereby expressions could
485  be incorrectly re-ordered when compiling with Flambda.  This also fixes one
486  example of evaluation order in the native code compiler not matching the
487  bytecode compiler (even when not using Flambda)
488  (Mark Shinwell, Leo White, code review by Pierre Chambart)
489
490- MPR#7348: Private row variables can escape their scope
491  (Jacques Garrigue, report by Leo White)
492
493- MPR#7407: Two not-quite-standard C idioms rejected by SUNWSPro compilers
494  (Xavier Leroy)
495
496- MPR#7421: Soundness bug with GADTs and lazy
497  (Jacques Garrigue, report by Leo White)
498
499- MPR#7424: Typechecker diverges on unboxed type declaration
500  (Jacques Garrigue, report by Stephen Dolan)
501
502- MPR#7426, GPR#965: Fix fatal error during object compilation (also
503  introduces new [Pfield_computed] and [Psetfield_computed] primitives)
504  (Mark Shinwell, report by Ulrich Singer)
505
506- MPR#7427, GPR#959: Don't delete let bodies in Cmmgen
507  (Mark Shinwell, report by Valentin Gatien-Baron)
508
509- MPR#7432: Linking modules compiled with -labels and -nolabels is not safe
510  (Jacques Garrigue, report by Jeremy Yallop)
511
512- MPR#7437: typing assert failure with nonrec priv
513  (Jacques Garrigue, report by Anil Madhavapeddy)
514
515- MPR#7438: warning +34 exposes #row with private types
516  (Alain Frisch, report by Anil Madhavapeddy)
517
518- MPR#7443, GPR#990: spurious unused open warning with local open in patterns
519  (Florian Angeletti, report by Gabriel Scherer)
520
521- MPR#7504: fix warning 8 with unconstrained records
522  (Florian Angeletti, report by John Whitington)
523
524- MPR#7456, GPR#1092: fix slow compilation on source files containing a lot
525  of similar debugging information location entries
526  (Mark Shinwell)
527
528- GPR#795: remove 256-character limitation on Sys.executable_name
529  (Xavier Leroy)
530
531- GPR#805, GPR#815, GPR#833: check for integer overflow in String.concat
532  (Jeremy Yallop,
533   review by Damien Doligez, Alain Frisch, Daniel Bünzli, Fabrice Le Fessant)
534
535- GPR#881: short-paths did not apply to some polymorphic variants
536  (Valentin Gatien-Baron, review by Leo White)
537
538- GPR#886: Fix Ctype.moregeneral's handling of row_name
539  (Leo White, review by Jacques Garrigue)
540
541- GPR#934: check for integer overflow in Bytes.extend
542  (Jeremy Yallop, review by Gabriel Scherer)
543
544- GPR#956: Keep possibly-effectful expressions when optimizing multiplication
545  by zero.
546  (Jeremy Yallop, review by Nicolás Ojeda Bär, Xavier Leroy and Mark Shinwell)
547
548- GPR#977: Catch Out_of_range in ocamldebug's "list" command
549  (Yunxing Dai)
550
551- GPR#983: Avoid removing effectful expressions in Closure, and
552  eliminate more non-effectful ones
553  (Alain Frisch, review by Mark Shinwell and Gabriel Scherer)
554
555- GPR#987: alloc_sockaddr: don't assume a null terminator. It is not inserted
556  on macOS by system calls that fill in a struct sockaddr (e.g. getsockname).
557  (Anton Bachin)
558
559- GPR#998: Do not delete unused closures in un_anf.ml.
560  (Leo White, review by Mark Shinwell and Pierre Chambart)
561
562- GPR#1019: Fix fatal error in Flambda mode "[functions] does not map set of
563  closures ID"
564  (Pierre Chambart, code review by Mark Shinwell and Leo White)
565
566- GPR#1075: Ensure that zero-sized float arrays have zero tags.
567  (Mark Shinwell, Leo White, review by Xavier Leroy)
568
569* GPR#1088: Gc.minor_words now returns accurate numbers.
570  (Stephen Dolan, review by Pierre Chambart and Xavier Leroy)
571
572OCaml 4.04.2 (23 Jun 2017):
573---------------------------
574
575### Security fix:
576
577- PR#7557: Local privilege escalation issue with ocaml binaries.
578  (Damien Doligez, report by Eric Milliken, review by Xavier Leroy)
579
580OCaml 4.04.1 (14 Apr 2017):
581---------------------------
582
583- PR#7501, GPR#1089: Consider arrays of length zero as constants
584  when using Flambda.
585  (Pierre Chambart, review by Mark Shinwell and Leo White)
586
587### Standard library:
588
589- PR#7403, GPR#894: fix a bug in Set.map as introduced in 4.04.0
590  (Gabriel Scherer, report by Thomas Leonard)
591
592### Tools:
593
594- PR#7411: ocamldoc, avoid nested <pre> tags in module description.
595  (Florian Angeletti, report by user 'kosik')
596
597- PR#7488: ocamldoc, wrong Latex output for variant types
598  with constructors without arguments.
599  (Florian Angeletti, report by Xavier Leroy)
600
601### Build system:
602
603- PR#7373, GPR#1023: New flexlink target in Makefile.nt to bootstrap the
604  flexlink binary only, rather than the flexlink binary and the FlexDLL C
605  objects.
606  (David Allsopp)
607
608### Bug fixes
609
610- PR#7369: Str.regexp raises "Invalid_argument: index out of bounds"
611  (Damien Doligez, report by John Whitington)
612
613- PR#7373, GPR#1023: Fix ocamlmklib with bootstrapped FlexDLL. Bootstrapped
614  FlexDLL objects are now installed to a subdirectory flexdll of the Standard
615  Library which allows the compilers to pick them up explicitly and also
616  ocamlmklib to include them without unnecessarily adding the entire Standard
617  Library.
618  (David Allsopp)
619
620- PR#7385, GPR#1057: fix incorrect timestamps returned by Unix.stat on Windows
621  when either TZ is set or system date is in DST.
622  (David Allsopp, report and initial fix by Nicolás Ojeda Bär, review and
623   superior implementation suggestion by Xavier Leroy)
624
625- PR#7405, GPR#903: s390x: Fix address of caml_raise_exn in native dynlink modules
626  (Richard Jones, review by Xavier Leroy)
627
628- PR#7417, GPR#930: ensure 16 byte stack alignment inside caml_allocN on x86-64
629  for ocaml build with WITH_FRAME_POINTERS defined
630  (Christoph Cullmann)
631
632- PR#7456, GPR#1092: fix slow compilation on source files containing a lot
633  of similar debugging information location entries
634  (Mark Shinwell)
635
636- PR#7457: a case of double free in the systhreads library (POSIX implementation)
637  (Xavier Leroy, report by Chet Murthy)
638
639- PR#7460, GPR#1011: catch uncaught exception when unknown files are passed
640  as argument (regression in 4.04.0)
641  (Bernhard Schommer, review by Florian Angeletti and Gabriel Scherer,
642   report by Stephen Dolan)
643
644- PR#7505: Memory cannot be released after calling
645    Bigarray.Genarray.change_layout.
646  (Damien Doligez and Xavier Leroy, report by Liang Wang)
647
648- PR#7511, GPR#1133: Unboxed type with unboxed argument should not be accepted
649  (Damien Doligez, review by Jeremy Yallop and Leo White)
650
651- GPR#912: Fix segfault in Unix.create_process on Windows caused by wrong header
652  configuration.
653  (David Allsopp)
654
655- GPR#980: add dynlink options to ocamlbytecomp.cmxa to allow ocamlopt.opt
656  to load plugins. See http://github.com/OCamlPro/ocamlc-plugins for examples.
657  (Fabrice Le Fessant, review by David Allsopp)
658
659- GPR#992: caml-types.el: Fix missing format argument, so that it can show kind
660  of call at point correctly.
661  (Chunhui He)
662
663- GPR#1043: Allow Windows CRLF line-endings in ocamlyacc on Unix and Cygwin.
664  (David Allsopp, review by Damien Doligez and Xavier Leroy)
665
666- GPR#1072: Fix segfault in Sys.runtime_parameters when exception backtraces
667  are enabled.
668  (Olivier Andrieu)
669
670OCaml 4.04.0 (4 Nov 2016):
671--------------------------
672
673(Changes that can break existing programs are marked with a "*")
674
675### Language features:
676
677- PR#7233: Support GADT equations on non-local abstract types
678  (Jacques Garrigue)
679
680- GPR#187, GPR#578: Local opening of modules in a pattern.
681  Syntax: "M.(p)", "M.[p]","M.[| p |]", "M.{p}"
682  (Florian Angeletti, Jacques Garrigue, review by Alain Frisch)
683
684- GPR#301: local exception declarations "let exception ... in"
685  (Alain Frisch)
686
687- GPR#508: Allow shortcut for extension on semicolons: ;%foo
688  (Jérémie Dimino)
689
690- GPR#606: optimized representation for immutable records with a single
691  field, and concrete types with a single constructor with a single argument.
692  This is triggered with a [@@unboxed] attribute on the type definition.
693  Currently mutually recursive datatypes are not well supported, this
694  limitation should be lifted in the future (see MPR#7364).
695  (Damien Doligez)
696
697### Compiler user-interface and warnings:
698
699* PR#6475, GPR#464: interpret all command-line options before compiling any
700  files, changes (improves) the semantics of repeated -o options or -o
701  combined with -c see the super-detailed commit message at
702  https://github.com/ocaml/ocaml/commit/da56cf6dfdc13c09905c2e07f1d4849c8346eec8
703  (whitequark)
704
705- PR#7139: clarify the wording of Warning 38
706  (Unused exception or extension constructor)
707  (Gabriel Scherer)
708
709* PR#7147, GPR#475: add colors when reporting errors generated by ppx rewriters.
710  Remove the `Location.errorf_prefixed` function which is no longer relevant
711  (Simon Cruanes, Jérémie Dimino)
712
713- PR#7169, GPR#501: clarify the wording of Warning 8
714  (Non-exhaustivity warning for pattern matching)
715  (Florian Angeletti, review and report by Gabriel Scherer)
716
717* GPR#591: Improve support for OCAMLPARAM: (i) do not use objects
718  files with -a, -pack, -shared; (ii) use "before" objects in the toplevel
719  (but not "after" objects); (iii) use -I dirs in the toplevel,
720  (iv) fix bug where -I dirs were ignored when using threads
721  (Marc Lasson, review by Damien Doligez and Alain Frisch)
722
723- GPR#648: New -plugin option for ocamlc and ocamlopt, to dynamically extend
724  the compilers at runtime.
725  (Fabrice Le Fessant)
726
727- GPR#684: Detect unused module declarations
728  (Alain Frisch)
729
730- GPR#706: Add a settable Env.Persistent_signature.load function so
731  that cmi files can be loaded from other sources. This can be used to
732  create self-contained toplevels.
733  (Jérémie Dimino)
734
735### Standard library:
736
737- PR#6279, GPR#553: implement Set.map
738  (Gabriel Scherer)
739
740- PR#6820, GPR#560: Add Obj.reachable_words to compute the
741  "transitive" heap size of a value
742  (Alain Frisch, review by Mark Shinwell and Damien Doligez)
743
744- GPR#473: Provide `Sys.backend_type` so that user can write backend-specific
745  code in some cases (for example,  code generator).
746  (Hongbo Zhang)
747
748- GPR#589: Add a non-allocating function to recover the number of
749  allocated minor words.
750  (Pierre Chambart, review by Damien Doligez and Gabriel Scherer)
751
752- GPR#626: String.split_on_char
753  (Alain Frisch)
754
755- GPR#669: Filename.extension and Filename.remove_extension
756  (Alain Frisch, request by Edgar Aroutiounian, review by Daniel Bünzli
757  and Damien Doligez)
758
759- GPR#674: support unknown Sys.os_type in Filename, defaulting to Unix
760  (Filename would previously fail at initialization time for
761   Sys.os_type values other than "Unix", "Win32" and "Cygwin";
762   mirage-os uses "xen")
763  (Anil Madhavapeddy)
764
765- GPR#772 %string_safe_set and %string_unsafe_set are deprecated aliases
766  for %bytes_safe_set and %bytes_unsafe_set.
767  (Hongbo Zhang and Damien Doligez)
768
769### Other libraries
770
771- MPR#4834, GPR#592: Add a Biggarray.Genarray.change_layout function
772  to switch bigarrays between C and fortran layouts.
773  (Guillaume Hennequin, review by Florian Angeletti)
774
775### Code generation and optimizations:
776
777- PR#4747, GPR#328: Optimize Hashtbl by using in-place updates of its
778  internal bucket lists.  All operations run in constant stack size
779  and are usually faster, except Hashtbl.copy which can be much
780  slower
781  (Alain Frisch)
782
783- PR#6217, GPR#538: Optimize performance of record update:
784  no more performance cliff when { foo with t1 = ..; t2 = ...; ... }
785  hits 6 updated fields
786  (Olivier Nicole, review by Thomas Braibant and Pierre Chambart)
787
788- PR#7023, GPR#336: Better unboxing strategy
789  (Alain Frisch, Pierre Chambart)
790
791- PR#7244, GPR#840: Ocamlopt + flambda requires a lot of memory
792  to compile large array literal expressions
793  (Pierre Chambart, review by Mark Shinwell)
794
795- PR#7291, GPR#780: Handle specialisation of recursive function that does
796  not always preserve the arguments
797  (Pierre Chambart, Mark Shinwell, report by Simon Cruanes)
798
799- PR#7328, GPR#702: Do not eliminate boxed int divisions by zero and
800  avoid checking twice if divisor is zero with flambda.
801  (Pierre Chambart, report by Jeremy Yallop)
802
803- GPR#427: Obj.is_block is now an inlined OCaml function instead of a
804  C external.  This should be faster.
805  (Demi Obenour)
806
807- GPR#580: Optimize immutable float records
808  (Pierre Chambart, review by Mark Shinwell)
809
810- GPR#602: Do not generate dummy code to force module linking
811  (Pierre Chambart, reviewed by Jacques Garrigue)
812
813- GPR#703: Optimize some constant string operations when the "-safe-string"
814  configure time option is enabled.
815  (Pierre Chambart)
816
817- GPR#707: Load cross module information during a meet
818  (Pierre Chambart, report by Leo White, review by Mark Shinwell)
819
820- GPR#709: Share a few more equal switch branches
821  (Pierre Chambart, review by Gabriel Scherer)
822
823- GPR#712: Small improvements to type-based optimizations for array
824  and lazy
825  (Alain Frisch, review by Pierre Chambart)
826
827- GPR#714: Prevent warning 59 from triggering on Lazy of constants
828  (Pierre Chambart, review by Leo White)
829
830- GPR#723 Sort emitted functions according to source location
831  (Pierre Chambart, review by Mark Shinwell)
832
833- Lack of type normalization lead to missing simple compilation for "lazy x"
834  (Alain Frisch)
835
836### Runtime system:
837
838- PR#7203, GPR#534: Add a new primitive caml_alloc_float_array to allocate an
839  array of floats
840  (Thomas Braibant)
841
842- PR#7210, GPR#562: Allows to register finalisation function that are
843  called only when a value will never be reachable anymore. The
844  drawbacks compared to the existing one is that the finalisation
845  function is not called with the value as argument. These finalisers
846  are registered with `GC.finalise_last`
847  (François Bobot reviewed by Damien Doligez and Leo White)
848
849- GPR#247: In previous OCaml versions, inlining caused stack frames to
850  disappear from stacktraces. This made debugging harder in presence of
851  optimizations, and flambda was going to make this worse. The debugging
852  information produced by the compiler now enables the reconstruction of the
853  original backtrace. Use `Printexc.get_raw_backtrace_next_slot` to traverse
854  the list of inlined stack frames.
855  (Frédéric Bour, review by Mark Shinwell and Xavier Leroy)
856
857- GPR#590: Do not perform compaction if the real overhead is less than expected
858  (Thomas Braibant)
859
860### Tools:
861
862- PR#7189: toplevel #show, follow chains of module aliases
863  (Gabriel Scherer, report by Daniel Bünzli, review by Thomas Refis)
864
865- PR#7248: have ocamldep interpret -open arguments in left-to-right order
866  (Gabriel Scherer, report by Anton Bachin)
867
868- PR#7272, GPR#798: ocamldoc, missing line breaks in type_*.html files
869  (Florian Angeletti)
870
871- PR#7290: ocamldoc, improved support for inline records
872  (Florian Angeletti)
873
874- PR#7323, GPR#750: ensure "ocamllex -ml" works with -safe-string
875  (Hongbo Zhang)
876
877- PR#7350, GPR#806: ocamldoc, add viewport metadata to generated html pages
878  (Florian Angeletti, request by Daniel Bünzli)
879
880- GPR#452: Make the output of ocamldep more stable
881  (Alain Frisch)
882
883- GPR#548: empty documentation comments
884  (Florian Angeletti)
885
886- GPR#575: Add the -no-version option to the toplevel
887  (Sébastien Hinderer)
888
889- GPR#598: Add a --strict option to ocamlyacc treat conflicts as errors
890  (this option is now used for the compiler's parser)
891  (Jeremy Yallop)
892
893- GPR#613: make ocamldoc use -open arguments
894  (Florian Angeletti)
895
896- GPR#718: ocamldoc, fix order of extensible variant constructors
897  (Florian Angeletti)
898
899### Debugging and profiling:
900
901- GPR#585: Spacetime, a new memory profiler (Mark Shinwell, Leo White)
902
903### Manual and documentation:
904
905- PR#7007, PR#7311: document the existence of OCAMLPARAM and
906  ocaml_compiler_internal_params
907  (Damien Doligez, reports by Wim Lewis and Gabriel Scherer)
908
909- PR#7243: warn users against using WinZip to unpack the source archive
910  (Damien Doligez, report by Shayne Fletcher)
911
912- PR#7245, GPR#565: clarification to the wording and documentation
913  of Warning 52 (fragile constant pattern)
914  (Gabriel Scherer, William, Adrien Nader, Jacques Garrigue)
915
916- #PR7265, GPR#769: Restore 4.02.3 behaviour of Unix.fstat, if the
917  file descriptor doesn't wrap a regular file (win32unix only)
918  (Andreas Hauptmann, review by David Allsopp)
919
920- PR#7288: flatten : Avoid confusion
921  (Damien Doligez, report by user 'tormen')
922
923- PR#7355: Gc.finalise and lazy values
924  (Jeremy Yallop)
925
926- GPR#842: Document that [Store_field] must not be used to populate
927  arrays of values declared using [CAMLlocalN] (Mark Shinwell)
928
929### Compiler distribution build system:
930
931- GPR#324: Compiler developers: Adding new primitives to the
932  standard runtime doesn't require anymore to run `make bootstrap`
933  (François Bobot)
934
935- GPR#384: Fix compilation using old Microsoft C Compilers not
936  supporting secure CRT functions (SDK Visual Studio 2005 compiler and
937  earlier) and standard 64-bit integer literals (Visual Studio .NET
938  2002 and earlier)
939  (David Allsopp)
940
941- GPR#507: More sharing between Unix and Windows makefiles
942  (whitequark, review by Alain Frisch)
943
944* GPR#512, GPR#587: Installed `ocamlc`, `ocamlopt`, and `ocamllex` are
945  now the native-code versions of the tools, if those versions were
946  built.
947  (Demi Obenour)
948
949- GPR#525: fix build on OpenIndiana
950  (Sergey Avseyev, review by Damien Doligez)
951
952- GPR#687: "./configure -safe-string" to get a system where
953  "-unsafe-string" is not allowed, thus giving stronger non-local
954  guarantees about immutability of strings
955  (Alain Frisch, review by Hezekiah M. Carty)
956
957### Bug fixes:
958
959* PR#6505: Missed Type-error leads to a segfault upon record access.
960  (Jacques Garrigue, extra report by Stephen Dolan)
961  Proper fix required a more restrictive approach to recursive types:
962  mutually recursive types are seen as abstract types (i.e. non-contractive)
963  when checking the well-foundedness of the recursion.
964
965* PR#6752: Nominal types and scope escaping.
966  Revert to strict scope for non-generalizable type variables, cf. Mantis.
967  Note that this is actually stricter than the behavior before 4.03,
968  cf. PR#7313, meaning that you may sometimes need to add type annotations
969  to explicitly instantiate non-generalizable type variables.
970  (Jacques Garrigue, following discussion with Jeremy Yallop,
971   Nicolas Ojeda Bar and Alain Frisch)
972
973- PR#7112: Aliased arguments ignored for equality of module types
974  (Jacques Garrigue, report by Leo White)
975
976- PR#7134: compiler forcing aliases it shouldn't while reporting type errors
977  (Jacques Garrigue, report and suggestion by sliquister)
978
979- PR#7153: document that Unix.SOCK_SEQPACKET is not really usable.
980
981- PR#7165, GPR#494: uncaught exception on invalid lexer directive
982  (Gabriel Scherer, report by KC Sivaramakrishnan using afl-fuzz)
983
984- PR#7257, GPR#583: revert a 4.03 change of behavior on (Unix.sleep 0.),
985  it now calls (nano)sleep for 0 seconds as in (< 4.03) versions.
986  (Hannes Mehnert, review by Damien Doligez)
987
988- PR#7260: GADT + subtyping compile time crash
989  (Jacques Garrigue, report by Nicolas Ojeda Bar)
990
991- PR#7269: Segfault from conjunctive constraints in GADT
992  (Jacques Garrigue, report by Stephen Dolan)
993
994- PR#7276: Support more than FD_SETSIZE sockets in Windows' emulation
995  of select
996  (David Scott, review by Alain Frisch)
997
998* PR#7278: Prevent private inline records from being mutated
999  (Alain Frisch, report by Pierre Chambart)
1000
1001- PR#7284: Bug in mcomp_fields leads to segfault
1002  (Jacques Garrigue, report by Leo White)
1003
1004- PR#7285: Relaxed value restriction broken with principal
1005  (Jacques Garrigue, report by Leo White)
1006
1007- PR#7297: -strict-sequence turns off Warning 21
1008  (Jacques Garrigue, report by Valentin Gatien-Baron)
1009
1010- PR#7299: remove access to OCaml heap inside blocking section in win32unix
1011  (David Allsopp, report by Andreas Hauptmann)
1012
1013- PR#7300: remove access to OCaml heap inside blocking in Unix.sleep on Windows
1014  (David Allsopp)
1015
1016- PR#7305: -principal causes loop in type checker when compiling
1017  (Jacques Garrigue, report by Anil Madhavapeddy, analysis by Leo White)
1018
1019- PR#7330: Missing exhaustivity check for extensible variant
1020  (Jacques Garrigue, report by Elarnon *)
1021
1022- PR#7374: Contractiveness check unsound with constraints
1023  (Jacques Garrigue, report by Leo White)
1024
1025- PR#7378: GADT constructors can be re-exposed with an incompatible type
1026  (Jacques Garrigue, report by Alain Frisch)
1027
1028- PR#7389: Unsoundness in GADT exhaustiveness with existential variables
1029  (Jacques Garrigue, report by Stephen Dolan)
1030
1031* GPR#533: Thread library: fixed [Thread.wait_signal] so that it
1032  converts back the signal number returned by [sigwait] to an
1033  OS-independent number
1034  (Jérémie Dimino)
1035
1036- GPR#600: (similar to GPR#555) ensure that register typing constraints are
1037  respected at N-way join points in the control flow graph
1038  (Mark Shinwell)
1039
1040- GPR#672: Fix float_of_hex parser to correctly reject some invalid forms
1041  (Bogdan Tătăroiu, review by Thomas Braibant and Alain Frisch)
1042
1043- GPR#700: Fix maximum weak bucket size
1044  (Nicolas Ojeda Bar, review by François Bobot)
1045
1046- GPR#708 Allow more module aliases in strengthening (Leo White)
1047
1048- GPR#713, PR#7301: Fix wrong code generation involving lazy values in Flambda
1049  mode
1050  (Mark Shinwell, review by Pierre Chambart and Alain Frisch)
1051
1052- GPR#721: Fix infinite loop in flambda due to [@@specialise] annotations
1053
1054- GPR#779: Building native runtime on Windows could fail when bootstrapping
1055  FlexDLL if there was also a system-installed flexlink
1056  (David Allsopp, report Michael Soegtrop)
1057
1058- GPR#805, GPR#815, GPR#833: check for integer overflow in String.concat
1059  (Jeremy Yallop,
1060   review by Damien Doligez, Alain Frisch, Daniel Bünzli, Fabrice Le Fessant)
1061
1062- GPR#810: check for integer overflow in Array.concat
1063  (Jeremy Yallop)
1064
1065- GPR#814: fix the Buffer.add_substring bounds check to handle overflow
1066  (Jeremy Yallop)
1067
1068- GPR#880: Fix [@@inline] with default parameters in flambda (Leo White)
1069
1070### Internal/compiler-libs changes:
1071
1072- PR#7200, GPR#539: Improve, fix, and add test for parsing/pprintast.ml
1073  (Runhang Li, David Sheets, Alain Frisch)
1074
1075- GPR#351: make driver/pparse.ml functions type-safe
1076  (Gabriel Scherer, Dmitrii Kosarev, review by Jérémie Dimino)
1077
1078- GPR#516: Improve Texp_record constructor representation, and
1079  propagate updated record type information
1080  (Pierre Chambart, review by Alain Frisch)
1081
1082- GPR#678: Graphics.close_graph crashes 64-bit Windows ports (re-implementation
1083  of PR#3963)
1084  (David Allsopp)
1085
1086- GPR#679: delay registration of docstring after the mapper is applied
1087  (Hugo Heuzard, review by Leo White)
1088
1089- GPR#872: don't attach (**/**) comments to any particular node
1090  (Thomas Refis, review by Leo White)
1091
1092OCaml 4.03.0 (25 Apr 2016):
1093---------------------------
1094
1095(Changes that can break existing programs are marked with a "*")
1096
1097### Language features:
1098
1099- PR#5528: inline records for constructor arguments
1100  (Alain Frisch)
1101
1102- PR#6220, PR#6403, PR#6437, PR#6801:
1103  Improved redundancy and exhaustiveness checks for GADTs.
1104  Namely, the redundancy checker now checks whether the uncovered pattern
1105  of the pattern is actually inhabited, exploding at most one wild card.
1106  This is also done for exhaustiveness when there is only one case.
1107  Additionally, one can now write unreachable cases, of the form
1108  "pat -> .", which are treated by the redundancy check.
1109  (Jacques Garrigue)
1110
1111- PR#6374: allow "_ t" as a short-hand for "(_, _, ..) t" for n-ary type
1112  constructors
1113  (Alain Frisch)
1114
1115- PR#6714: allow [@@ocaml.warning] on most structure and signature items:
1116  values, modules, module types
1117  (whitequark)
1118
1119- PR#6806: Syntax shortcut for putting a type annotation on a record field:
1120  { f1 : typ = e } is sugar for { f1 = (e : typ) }
1121  { f1 : typ } is sugar for { f1 = (f1 : typ) }
1122  (Valentin Gatien-Baron, review by Jérémie Dimino)
1123
1124- PR#6806: Allow type annotations before the "->" in "fun <args> -> <expr>"
1125  fun x y : (int * int) -> (x, y)
1126  (Valentin Gatien-Baron, review by Jérémie Dimino)
1127
1128- GPR#26: support for "(type a b)" as syntactic sugar for "(type a) (type b)"
1129  (Gabriel Scherer)
1130
1131- GPR#42: short functor type syntax: "S -> T" for "functor (_ : S) -> T"
1132  (Leo White)
1133
1134- GPR#88: allow field punning in object copying expressions:
1135  {< x; y; >} is sugar for {< x = x; y = y; >}
1136  (Jeremy Yallop)
1137
1138- GPR#112: octal escape sequences for char and string literals
1139  "Make it \o033[1mBOLD\o033[0m"
1140  (Rafaël Bocquet, request by John Whitington)
1141
1142- GPR#167: allow to annotate externals' arguments and result types so
1143  they can be unboxed or untagged: [@unboxed], [@untagged]. Supports
1144  untagging int and unboxing int32, int64, nativeint and float.
1145  (Jérémie Dimino, Mark Shinwell)
1146
1147- GPR#173: [@inline] and [@inlined] attributes (for function declarations
1148  and call sites respectively) to control inlining
1149  (Pierre Chambart, Mark Shinwell)
1150
1151- GPR#188: accept [@@immediate] attribute on type declarations to mark types
1152  that are represented at runtime by an integer
1153  (Will Crichton, reviewed by Leo White)
1154
1155* GPR#234: allow "[]" as a user-defined constructor. Demand parenthesis
1156  around "::" when using "::" as user-defined constructor:
1157  code using "| :: of ..." must change to "| (::) of ...".
1158  (Runhang Li, review by Damien Doligez)
1159
1160- GPR#240: replace special annotations on externals by attributes:
1161  * "float" is generalized to [@@unboxed]
1162  * "noalloc" becomes [@@noalloc]
1163  Deprecate "float" and "noalloc".
1164  (Jérémie Dimino)
1165
1166- GPR#254: @ocaml.warn_on_literal_pattern attribute on constructors to
1167  warn when the argument is matches against a constant pattern.  This
1168  attribute is applied on predefined exception constructors which
1169  carry purely informational (with no stability guarantee) messages.
1170  (Alain Frisch)
1171
1172- GPR#268: hexadecimal notation for floating-point literals: -0x1.ffffp+987
1173  In OCaml source code, FP literals can be written using the hexadecimal
1174  notation 0x<mantissa in hex>p<exponent> from ISO C99.
1175  (Xavier Leroy)
1176
1177- GPR#273: allow to get the extension slot of an extension constructor
1178  by writing [%extension_constructor <path>]
1179  (Jérémie Dimino)
1180
1181- GPR#282: change short-paths penalty heuristic to assign the same cost to
1182  idents containing double underscores as to idents starting with an underscore
1183  (Thomas Refis, Leo White)
1184
1185- PR#6681 GPR#326: signature items are now accepted as payloads for
1186  extension and attributes, using the syntax [%foo: SIG ] or [@foo: SIG ].
1187  Examples: "[%%client: val foo : int]" or "val%client foo : int".
1188  (Alain Frisch and Gabriel Radanne)
1189
1190* GPR#342: Allow shortcuts for extension and attributes on all keywords:
1191  module%foo, class[@foo], etc.
1192  The attribute in "let[@foo] .. in .." is now attached to the value binding,
1193  not to the expression.
1194  (Gabriel Radanne)
1195
1196### Compilers:
1197
1198* PR#4231, PR#5461: warning 31 is now fatal by default
1199  (Warning 31: A module is linked twice in the same executable.)
1200  This is an interim solution; double-linking of modules has dangerous
1201  semantics, eg. exception constructors end up with two distinct declarations.
1202  (Alain Frisch)
1203
1204- PR#4800: better compilation of tuple assignment
1205  (Gabriel Scherer and Alain Frisch)
1206
1207- PR#5995: keep -for-pack into account to name exceptions;
1208  -for-pack should now be used during bytecode compilation as well
1209  (Alain Frisch, report by Christophe Troestler)
1210
1211- PR#6400: better error message for '_' used as an expression
1212  (Alain Frisch, report by whitequark)
1213
1214- PR#6501: harden the native-code generator against certain uses of "%identity"
1215  (Xavier Leroy, report by Antoine Miné)
1216
1217- PR#6636: add --version option
1218  (whitequark)
1219
1220- PR#6679: fix pprintast printing of constraints in type declarations
1221  (Alain Frisch, report by Jun Furuse)
1222
1223- PR#6737: fix Typedtree attributes on (fun x -> body) expressions
1224  (Alain Frisch, report by Oleg Kiselyov)
1225
1226* PR#6865: remove special case for parsing "let _ = expr" in structures
1227  (Jérémie Dimino, Alain Frisch)
1228
1229* PR#6438, PR#7059, GPR#315: Pattern guard disables exhaustiveness check
1230  (function Some x when x = 0 -> ()) will now raise warning 8 (non-exhaustive)
1231  instead of warning 25 (all clauses are guarded). 25 isn't raised anymore.
1232  Projects that set warning 8 as an error may fail to compile (presumably
1233  this is the semantics they wanted).
1234  (Alain Frisch, request by Martin Jambon and John Whitington)
1235
1236- PR#6920: fix debug informations around uses of %apply or %revapply
1237  (Jérémie Dimino, report by Daniel Bünzli)
1238
1239- PR#6939: Segfault with improper use of let-rec
1240  (Alain Frisch)
1241
1242- PR#6943: native-code generator for POWER/PowerPC 64 bits, both in
1243  big-endian (ppc64) and little-endian (ppc64le) configuration.
1244  (Xavier Leroy, with inspiration from RedHat's unofficial ppc64 and ppc64le
1245  ports)
1246
1247- PR#6979: better code generation in x86-32 backend for copying floats to
1248  the stack
1249  (Marc Lasson, review by Xavier Leroy)
1250
1251- PR#7018: fix missing identifier renaming during inlining
1252  (Alain Frisch, review by Xavier Leroy)
1253
1254- PR#7022, GPR#259: unbox float and boxed ints earlier, avoid second pass
1255  (Alain Frisch)
1256
1257- PR#7026, GPR#288: remove write barrier for polymorphic variants without
1258  arguments
1259  (Simon Cruanes)
1260
1261- PR#7031: new warning 57, ambiguous guarded or-patterns
1262  (Luc Maranget, Gabriel Scherer, report by Martin Clochard and Claude Marché)
1263
1264- PR#7064, GPR#316: allowing to mark compilation units and sub-modules as
1265  deprecated
1266  (Alain Frisch)
1267
1268- PR#7067: fix performance regression (wrt. 4.01) in the native compiler
1269  for long nested structures
1270  (Alain Frisch, report by Daniel Bünzli, review by Jacques Garrigue)
1271
1272- PR#7097: fix strange syntax error message around illegal packaged module
1273  signature constraints
1274  (Alain Frisch, report by Jun Furuse)
1275
1276- PR#7118, PR#7120, GPR#408, GPR#476: Bug fixed in stack unwinding
1277  metadata generation. Was a cause of crashes in GUI programs on OS X.
1278  (Bart Jacobs, review by Mark Shinwell)
1279
1280- PR#7168: Exceeding stack limit in bytecode can lead to a crash.
1281  (Jacques-Henri Jourdan)
1282
1283- PR#7232: Strange Pprintast output with ppx_deriving
1284  (Damien Doligez, report by Anton Bachin)
1285
1286- GPR#17: some cmm optimizations of integer operations with constants
1287  (Stephen Dolan, review by Pierre Chambart)
1288
1289- GPR#89: improve type-specialization of unapplied primitives:
1290  unapplied annotations (compare : int -> _),
1291  type propagation (List.sort compare [1;2;3])
1292  and propagation from module signatures now lead to specialization
1293  (Frédéric Bour, review by Gabriel Scherer)
1294
1295- GPR#107: Prevent more unnecessary float boxing, especially in `if` and `match`
1296  (Vladimir Brankov, review by Alain Frisch)
1297
1298- GPR#109: new (lazy) unboxing strategy for float and int references
1299  (Vladimir Brankov, review by Alain Frisch)
1300
1301- GPR#115: More precise typing of values at the C-- and Mach level.
1302  (Xavier Leroy, review by Pierre Chambart)
1303
1304- GPR#132: Flambda: new intermediate language and "middle-end" optimizers
1305  (Pierre Chambart, Mark Shinwell, Leo White)
1306
1307- GPR#212, PR#7226, GPR#542: emit column position in gas assembly `.loc`
1308  (Frédéric Bour, Anton Bachin)
1309
1310- GPR#207: Colors in compiler messages (warnings, errors)
1311  configure with -color {auto|always|never} or TERM=dumb
1312  (Simon Cruanes, review by Gabriel Scherer)
1313
1314- GPR#258: more precise information on PowerPC instruction sizes
1315  (Pierre Chambart, Xavier Leroy)
1316
1317- GPR#263: improve code generation for if-equivalents of (&&) and (||)
1318  (Pierre Chambart)
1319
1320- GPR#270: Make [transl_exception_constructor] generate [Immutable] blocks
1321  (Mark Shinwell)
1322
1323- GPR#271: Fix incorrect mutability flag when records are built using "with"
1324  (Mark Shinwell)
1325
1326- GPR#275: native-code generator for IBM z System running Linux.
1327  In memoriam Gene Amdahl, 1922-2015.
1328  (Bill O'Farrell, Tristan Amini, Xavier Leroy)
1329
1330- GPR#282: relax short-paths safety check in presence of module aliases, take
1331  penalty into account while building the printing map.
1332  (Thomas Refis, Leo White)
1333
1334- GPR#306: Instrument the compiler to debug performance regressions
1335  (Pierre Chambart)
1336
1337- GPR#319: add warning 58 for missing cmx files, and
1338  extend -opaque option to mli files: a missing .cmx does not warn
1339  if the corresponding .cmi is compiled -opaque.
1340  (Leo White)
1341
1342- GPR#388: OCAML_FLEXLINK environment variable allows overriding flexlink
1343  command (David Allsopp)
1344
1345- GPR#392: put all parsetree invariants in a new module Ast_invariants
1346  (Jérémie Dimino)
1347
1348- GPR#407: don't display the name of compiled .c files when calling the
1349  Microsoft C Compiler (same as the assembler).
1350  (David Allsopp)
1351
1352- GPR#431: permit constant float arrays to be eligible for pattern match
1353  branch merging
1354  (Pierre Chambart)
1355
1356- GPR#455: provide more debugging information to Js_of_ocaml
1357  (Jérôme Vouillon)
1358
1359- GPR#514, GPR#554: Added several command-line flags to explicitly enable
1360  settings that are currently the default:
1361  `-alias-deps`, `-app-funct`, `-no-keep-docs`, `-no-keep-locs`,
1362  `-no-principal`, `-no-rectypes`, `-no-strict-formats`
1363  (Demi Obenour)
1364
1365- GPR#545: use reraise to preserve backtrace on
1366  `match .. with exception e -> raise e`
1367  (Nicolas Ojeda Bar, review by Gabriel Scherer)
1368
1369### Runtime system:
1370
1371* GPR#596: make string/bytes distinguishable in the underlying
1372  compiler implementation; caml_fill_string and caml_create_string are
1373  deprecated and will be removed in the future, please use
1374  caml_fill_bytes and caml_create_bytes for migration
1375  (Hongbo Zhang, review by Damien Doligez, Alain Frisch, and Hugo Heuzard)
1376
1377- PR#3612, PR#92: allow allocating custom block with finalizers
1378  in the minor heap.
1379  (Pierre Chambart)
1380
1381* PR#6517: use ISO C99 types {,u}int{32,64}_t in preference to our homegrown
1382  types {,u}int{32,64}.
1383  C stubs may have to be updated as {,u}int{32,64}_t are not defined anymore.
1384  (Xavier Leroy)
1385
1386- PR#6760: closures evaluated in the toplevel can now be marshalled
1387  (whitequark, review by Jacques-Henri Jourdan)
1388
1389- PR#6902, GPR#210: emit a runtime warning on stderr
1390  when finalizing an I/O channel which is still open:
1391    "channel opened on file '...' dies without being closed"
1392  this is controlled by OCAMLRUNPARAM=W=1 or with Sys.enable_runtime_warnings.
1393  The behavior of affected program is not changed,
1394  but they should still be fixed.
1395  (Alain Frisch, review by Damien Doligez)
1396
1397- Signal handling: for read-and-clear, use GCC/Clang atomic builtins
1398  if available.
1399  (Xavier Leroy)
1400
1401- PR#6910, GPR#224: marshaling (output_value, input_value, et al)
1402  now support marshaled data bigger than 4 Gb.
1403  (Xavier Leroy)
1404
1405* GPR#226: select higher levels of optimization for GCC >= 3.4 and Clang
1406  when compiling the run-time system and C stub code.
1407  "-std=gnu99 -O2 -fno-strict-aliasing -fwrapv" is used by default.
1408  This also affects default flags for user stubs compiled with "ocamlc -c foo.c"
1409  and may uncover bugs in them.
1410  (Xavier Leroy)
1411
1412- GPR#262: Multiple GC roots per compilation unit
1413  (Pierre Chambart, Mark Shinwell, review by Damien Doligez)
1414
1415* GPR#297: Several changes to improve the worst-case GC pause time.
1416  Changes Gc.control and Gc.major_slice and adds functions to the Gc module.
1417  (Damien Doligez, with help from François Bobot, Thomas Braibant, Leo White)
1418
1419- GPR#325: Add v=0x400 flag to OCAMLRUNPARAM to display GC stats on exit
1420  (Louis Gesbert, review by Alain Frisch)
1421
1422### Standard library:
1423
1424- PR#1460, GPR#230: Array.map2, Array.iter2
1425  (John Christopher McAlpine)
1426
1427- PR#5197, GPR#63: Arg: allow flags such as --flag=arg as well as --flag arg
1428  (Richard Jones)
1429
1430- PR#6017, PR#7034, GPR#267: More efficient ifprintf implementation
1431  (Jeremy Yallop, review by Gabriel Scherer)
1432
1433- PR#6296: Some documentation on the floating-point representations
1434    recognized by Pervasives.float_of_string
1435  (Xavier Leroy)
1436
1437- PR#6316: Scanf.scanf failure on %u formats when reading big integers
1438  (Xavier Leroy, Benoît Vaugon)
1439
1440- PR#6321: guarantee that "hypot infinity nan = infinity"
1441  (for conformance with ISO C99)
1442  (Xavier Leroy)
1443
1444- PR#6390, GPR#36: expose Sys.{int_size,max_wosize} for js_of_ocaml portability
1445  (Hugo Heuzard)
1446
1447- PR#6449: Add Map.union
1448  (Alain Frisch)
1449
1450* PR#6494: Add 'equal' functions in modules
1451  Bytes, Char, Digest, Int32, Int64, Nativeint, and String
1452  Users defining their own modules with signature 'module type of Int32'
1453  have to extend their implementation.
1454  (Romain Calascibetta)
1455
1456* PR#6524, GPR#79: Filename: Optional ?perms argument to open_temp_file
1457  May break partial applications of the function (fix by passing ?perms:None)
1458  (Daniel Bünzli, review by Jacques-Pascal Deplaix)
1459
1460* PR#6525, GPR#80: Add Uchar module to the standard library
1461  May introduce module name conflicts with existing projects.
1462  (Daniel Bünzli, review by Yoriyuki Yamagata and Damien Doligez)
1463
1464- PR#6577: improve performance of %L, %l, %n, %S, %C format specifiers
1465  (Alain Frisch)
1466
1467- PR#6585: fix memory leak in win32unix/createprocess.c
1468  (Alain Frisch, report by user 'aha')
1469
1470- PR#6645, GPR#174: Guarantee that Set.add, Set.remove, Set.filter
1471  return the original set if no change is required
1472  (Alain Frisch, Mohamed Iguernlala)
1473
1474- PR#6649, GPR#222: accept (int_of_string "+3")
1475  (John Christopher McAlpine)
1476
1477- PR#6694, PR#6695, GPR#124: deprecate functions using ISO-8859-1 character set
1478  in Char, Bytes, String and provide alternatives *_acii using US-ASCII.
1479  Affected functions:
1480    {Char,String,Bytes}.{uppercase,lowercase},
1481    {String,Bytes}.{capitalize,uncaptialize}
1482  (whitequark, review by Damien Doligez)
1483
1484- GPR#22: Add the Ephemeron module that implements ephemerons and weak
1485  hash table
1486  (François Bobot, review by Damien Doligez, Daniel Bünzli,
1487  Alain Frisch, Pierre Chambart)
1488
1489- GPR#164: more efficient (branchless) implementation of Pervasives.compare
1490  specialized at type 'float'.
1491  (Vladimir Brankov)
1492
1493- GPR#175: Guarantee that Map.add, Map.remove, Map.filter
1494  return the original map if no change is required.
1495  (Mohamed Iguernlala)
1496
1497- GPR#201: generalize types of Printf.{ifprintf,ikfprintf}
1498  (Maxence Guesdon)
1499
1500- GPR#216: add the missing POSIX.1-2001 signals in Sys
1501  (Guillaume Bury)
1502
1503- GPR#239: remove type-unsafe code from Stream
1504  (Pierre Chambart, review by Gabriel Scherer and Jeremy Yallop)
1505
1506- GPR#250: Check for negative start element in Array.sub
1507  (Jeremy Yallop)
1508
1509- GPR#265: new implementation of Queue avoiding Obj.magic
1510  (Jérémie Dimino)
1511
1512- GPR#268, GPR#303: '%h' and '%H' modifiers for printf and scanf to
1513  support floating-point numbers in hexadecimal notation
1514  (Xavier Leroy, Benoît Vaugon)
1515
1516- GPR#272: Switch classify_float to [@@unboxed]
1517  (Alain Frisch)
1518
1519- Improve speed of classify_float by not going through fpclassify()
1520  (Alain Frisch, Xavier Leroy)
1521
1522- GPR#277: Switch the following externals to [@@unboxed]:
1523  * {Nativeint,Int32,Int64}.{of,to}_float
1524  * Int{32,64}.float_of_bits
1525  * Int{32,64}.bits_of_float
1526  (Jérémie Dimino)
1527
1528- GPR#281: Switch the following externals to [@@unboxed]:
1529  * Sys.time (and [@@noalloc])
1530  * Pervasives.ldexp (and [@@noalloc])
1531  * Pervasives.compare for float, nativeint, int32, int64.
1532  (François Bobot)
1533
1534- PR#3622, GPR#195: add function Stack.fold
1535  (Simon Cruanes)
1536
1537- GPR#329: Add exists, for_all,  mem and memq functions in Array
1538  (Bernhard Schommer)
1539
1540- GPR#337: Add [Hashtbl.filter_map_inplace]
1541  (Alain Frisch)
1542
1543- GPR#356: Add [Format.kasprintf]
1544  (Jérémie Dimino, Mark Shinwell)
1545
1546### Type system:
1547
1548- PR#5545: Type annotations on methods cannot control the choice of abbreviation
1549  (Jacques Garrigue)
1550
1551* PR#6465: allow incremental weakening of module aliases.
1552  This is done by adding equations to submodules when expanding aliases.
1553  In theory this may be incompatible is some corner cases defining a module
1554  type through inference, but no breakage known on published code.
1555  (Jacques Garrigue)
1556
1557- PR#6593: Functor application in tests/basic-modules fails after commit 15405
1558  (Jacques Garrigue)
1559
1560### Toplevel and debugger:
1561
1562- PR#6113: Add descriptions to directives, and display them via #help
1563  (Nick Giannarakis, Berke Durak, Francis Southern and Gabriel Scherer)
1564
1565- PR#6396: Warnings-as-errors not properly flushed in the toplevel
1566  (Alain Frisch)
1567
1568- PR#6401: use proper error reporting for toplevel environment initialization:
1569  no more Env.Error(_) at start time
1570  (Gabriel Scherer, Alain Frisch)
1571
1572- PR#6468: toplevel now supports backtraces if invoked with OCAMLRUNPARAM=b
1573  (whitequark and Jake Donham,
1574   review by Gabriel Scherer and Jacques-Henri Jourdan)
1575
1576- PR#6906: wrong error location for unmatched paren with #use in toplevel
1577  (Damien Doligez, report by Kenichi Asai)
1578
1579- PR#6935, GPR#298: crash in debugger when load_printer is given a directory
1580  (Junsong Li, review by Gabriel Scherer)
1581
1582- PR#7081: report preprocessor warnings in the toplevel
1583  (Valentin Gatien-Baron, review by Jérémie Dimino)
1584
1585- PR#7098: Loss of ppx context in toplevel after an exception
1586  (Alain Frisch, report by whitequark)
1587
1588- PR#7101: The toplevel does not close in_channel for libraries specified on
1589  its command line
1590  (Alain Frisch)
1591
1592- PR#7119: the toplevel does not respect [@@@warning]
1593  (Alain Frisch, report by Gabriel Radanne)
1594
1595### Other libraries:
1596
1597* Unix library: channels created by Unix.in_channel_of_descr or
1598  Unix.out_channel_of_descr no longer support text mode under Windows.
1599  Calling [set_binary_mode_{in,out} chan false] on these channels
1600  now causes an error.
1601  (Xavier Leroy)
1602
1603- PR#4023 and GPR#68: add Unix.sleepf (sleep with sub-second resolution)
1604  (Evgenii Lepikhin and Xavier Leroy)
1605
1606* Protect Unix.sleep against interruptions by handled signals.
1607  Before, a handled signal could cause Unix.sleep to return early.
1608  Now, the sleep is restarted until the given time is elapsed.
1609  (Xavier Leroy)
1610
1611* PR#6120, GPR#462: implement Unix.symlink and Unix.readlink on
1612  Windows. Unix.symlink has a new optional argument to_dir (ignored on
1613  non-native Windows platforms). stat functions reimplemented to avoid
1614  buggy Microsoft CRT implementations (native Windows only)
1615  (David Allsopp, review by Daniel Bünzli)
1616
1617- PR#6263: add kind_size_in_bytes and size_in_bytes functions
1618  to Bigarray module.
1619  (Runhang Li, review by Mark Shinwell)
1620
1621- PR#6289: Unix.utimes uses the current time only if both arguments
1622    are exactly 0.0.  Also, use sub-second resolution if available.
1623  (Xavier Leroy, report by Christophe Troestler)
1624
1625- PR#6896: serious reimplementation of Big_int.float_of_big_int and
1626  Ratio.float_of_ratio, ensuring that the result is correctly rounded.
1627  (Xavier Leroy)
1628
1629- PR#6989: in Str library, make sure that all \(...\) groups are binding
1630    and can be consulted with Str.matched_group.  There used to be
1631    a limitation to 32 binding groups.
1632  (Xavier Leroy)
1633
1634- PR#7013: spurious wake-up in the Event module
1635  (Xavier Leroy)
1636
1637- PR#7024: in documentation of Str regular expressions, clarify what
1638    "end of line" means for "^" and "$" regexps.
1639  (Xavier Leroy, question by Fredrik Lindgren)
1640
1641- PR#7209: do not run at_exit handlers in [Unix.create_process] and
1642  similar functions when the [exec] call fails in the child process
1643  (Jérémie Dimino)
1644
1645### OCamldep:
1646
1647- GPR#286: add support for module aliases
1648  (Jacques Garrigue)
1649
1650### Manual:
1651
1652- GPR#302: The OCaml reference manual is now included in the manual/
1653  subdirectory of the main OCaml source repository. Contributions to
1654  the manual are warmly welcome.
1655  (François Bobot, review by Florian Angeletti)
1656
1657- PR#6601: replace strcpy with caml_strdup in sample code
1658  (Christopher Zimmermann)
1659
1660- PR#6676: ongoing simplification of the "Language Extensions" section
1661  (Alain Frisch, John Whitington)
1662
1663- PR#6898: Update win32 support documentation of the Unix library
1664  (Damien Doligez, report by Daniel Bünzli)
1665
1666- PR#7092, GPR#379: Add missing documentation for new 4.03 features
1667  (Florian Angeletti)
1668
1669- PR#7094, GPR#468, GPR#551: add new section 8.5 to document warnings
1670  The general idea is to document warnings that may require explanations.
1671  Currently documented warnings are:
1672  - 52: Fragile constant pattern.
1673  - 57: Ambiguous or-pattern variables under guard
1674  (Florian Angeletti and Gabriel Scherer)
1675
1676- PR#7109, GPR#380: Fix bigarray documentation layout
1677  (Florian Angeletti, Leo White)
1678
1679### Bug fixes:
1680
1681- PR#3612: memory leak in bigarray read from file
1682  (Pierre Chambart, report by Gary Huber)
1683
1684* PR#4166, PR#6956: force linking when calling external C primitives
1685  (Jacques Garrigue, reports by Markus Mottl and Christophe Troestler)
1686
1687* PR#4466, PR#5325: under Windows, concurrent read and write operations
1688    on the same socket could block unexpectedly.  Fixed by keeping sockets
1689    in asynchronous mode rather than creating them in synchronous mode.
1690  (Xavier Leroy)
1691
1692* PR#4539: change exception string raised when comparing functional values
1693  May break programs matching on the string argument of Invalid_argument.
1694  Matching on the string argument of Invalid_argument or Failure is a
1695  programming mistake: these strings may change in future versions.
1696  (Nicolas Braud-Santoni, report by Eric Cooper)
1697
1698- PR#4832: Filling bigarrays may block out runtime
1699  (Markus Mottl)
1700
1701- PR#5663: program rejected due to nongeneralizable type variable that
1702    appears nowhere
1703  (Jacques Garrigue, report by Stephen Weeks)
1704
1705- PR#5780: report more informative type names in GADTs error messages
1706  (Jacques Garrigue, report by Sebastien Furic)
1707
1708- PR#5887: move the byterun/*.h headers to byterun/caml/*.h to avoid header
1709    name clashes
1710  (Jérôme Vouillon and Adrien Nader and whitequark)
1711
1712* PR#6081: ocaml now adds script's directory to search path, not current
1713    directory
1714  (Thomas Leonard and Damien Doligez)
1715
1716- PR#6108, PR#6802: fail cleanly if dynlink.cma or ocamltoplevel.cma
1717    are loaded inside the toplevel loop.
1718  (Xavier Leroy)
1719
1720- PR#6171: Confusing error message when a type escapes its scope.
1721  (Jacques Garrigue and Leo White, report by John Whitington)
1722
1723- PR#6340: Incorrect handling of \r when processing "Windows" source files
1724  (Damien Doligez, report by David Allsopp)
1725
1726- PR#6342: Incorrect error message when type constraints differ
1727  (Alain Frisch, report by Philippe Wang)
1728
1729* PR#6521: {Bytes,Char,String}.escaped were locale-dependent
1730  we now escape all non-ASCII-printable instead of a locale-dependent subset.
1731  (Damien Doligez, report by Jun Furuse)
1732
1733- PR#6526: ocamllex should not warn on unescaped newline inside comments
1734  (Damien Doligez, report by user 'dhekir')
1735
1736- PR#6341: ocamldoc -colorize-code adds spurious <br> tags to <pre> blocks
1737  (Maxence Guesdon, report by Damien Doligez)
1738
1739- PR#6560: Wrong failure message for {Int32,Int64,NativeInt}.of_string
1740  It reported (Failure "int_of_string"), now "Int32.of_string" etc.
1741  (Maxime Dénès and Gabriel Scherer)
1742
1743- PR#6648: show_module should indicate its elision
1744  (Jacques Garrigue, report by Leo White)
1745
1746- PR#6650: Cty_constr not handled correctly by Subst
1747  (Jacques Garrigue, report by Leo White)
1748
1749- PR#6651: Failing component lookup
1750  (Jacques Garrigue, report by Leo White)
1751
1752* PR#6664: Crash when finalising lazy values of the wrong type.
1753  (Damien Doligez)
1754
1755- PR#6672: Unused variance specification allowed in with constraint
1756  (Jacques Garrigue, report by Leo White)
1757
1758- PR#6677: Allow to disable warning 39 (useless "rec") with [@ocaml.warning]
1759  applied to the first value binding of the would-be "rec" declaration
1760  (Alain Frisch, report by Jun Furuse)
1761
1762- PR#6744: Univars can escape through polymorphic variants (partial fix)
1763  (Jacques Garrigue, report by Leo White)
1764
1765- PR#6752: Extensible variant types and scope escaping
1766  A side-effect of the fix is that (ocamlc -i) sometimes reports
1767  (type-sound) invalid signature, with a type used before its declaration.
1768  (Jacques Garrigue, report by Maxence Guesdon)
1769
1770- PR#6762: improve warning 45 in presence of re-exported type definitions
1771  (Warning 45: open statement shadows the constructor)
1772  (Alain Frisch, report by Olivier Andrieu)
1773
1774- PR#6776: Failure to kill the "tick" thread, segfault when exiting the runtime
1775  (Damien Doligez, report by Thomas Braibant)
1776
1777- PR#6780: Poor error message for wrong -farch and -ffpu options (ocamlopt, ARM)
1778  (Xavier Leroy, report by whitequark)
1779
1780- PR#6805: Duplicated expression in case of hole in a non-failing switch.
1781  (Luc Maranget)
1782
1783* PR#6808: the parsing of OCAMLRUNPARAM is too lax
1784  (Damien Doligez)
1785
1786- PR#6874: Inefficient code generated for module function arguments
1787  (Jacques Garrigue, report by Markus Mottl)
1788
1789- PR#6888: The list command of ocamldebug uses the wrong file
1790  (Damien Doligez, report by Pierre-Marie Pédrot)
1791
1792- PR#6897: Bad error message for some pattern matching on extensible variants
1793  (Alain Frisch, report by Gabriel Radanne)
1794
1795- PR#6899: Optional parameters and non generalizable type variables
1796  (Thomas Refis and Leo White)
1797
1798- PR#6907: Stack overflow printing error in class declaration
1799  (Jacques Garrigue, report by Ivan Gotovchits)
1800
1801- PR#6931: Incorrect error message on type error inside record construction
1802  (Damien Doligez, report by Leo White)
1803
1804- PR#6938: fix regression on "%047.27{l,L,n}{d,i,x,X,o,u}"
1805  (Benoît Vaugon, report by Arduino Cascella)
1806
1807- PR#6944: let module X = Path in … is not typed as a module alias
1808  (Jacques Garrigue, report by Frédéric Bour)
1809
1810- PR#6945 and GPR#227: protect Sys and Unix functions against string
1811    arguments containing the null character '\000'
1812  (Simon Cruanes and Xavier Leroy, report by Daniel Bünzli)
1813
1814- PR#6946: Uncaught exception with wrong type for "%ignore"
1815  (Jacques Garrigue, report by Leo White)
1816
1817- PR#6954: Infinite loop in type checker with module aliases
1818  (Jacques Garrigue, report by Markus Mottl)
1819
1820- PR#6972, GPR#276: 4.02.3 regression on documentation comments in .cmt files
1821  (Leo White, report by Olivier Andrieu)
1822
1823- PR#6977: String literals in comments interpret escape sequences
1824  (Damien Doligez, report by Daniel Bünzli and David Sheets)
1825
1826- PR#6980: Assert failure from polymorphic variants and existentials
1827  (Jacques Garrigue, report by Leo White)
1828
1829- PR#6981: Ctype.Unify(_) with associated functor arg refering to previous one
1830  (Jacques Garrigue, report by Nicholas Labich)
1831
1832- PR#6982: unexpected type error when packing a module alias
1833  (Jacques Garrigue, report by Valentin Gatien-Baron)
1834
1835- PR#6985: `module type of struct include Bar end exposes
1836           %s#row when Bar contains private row types
1837  (Jacques Garrigue, report by Nicholas Labich)
1838
1839- PR#6992: Segfault from bug in GADT/module typing
1840  (Jacques Garrigue, report by Stephen Dolan)
1841
1842- PR#6993: Segfault from recursive modules violating exhaustiveness assumptions
1843  (Jacques Garrigue, report by Stephen Dolan)
1844
1845- PR#6998: Typer fails reading unnecessary cmis with -no-alias-deps and -w -49
1846  (Leo White, report by Valentin Gatien-Baron)
1847
1848- PR#7003: String.sub may cause segmentation fault on sizes above 2^31
1849  (Damien Doligez, report by Radek Micek)
1850
1851- PR#7008: Fatal error in ocamlc with empty compilation unit name
1852  (Damien Doligez, report by Cesar Kunz)
1853
1854- PR#7012: Variable name forgotten when it starts with a capital letter
1855  (Jacques Garrigue, Gabriel Scherer,
1856   report by Thomas Leonard and Florian Angeletti)
1857
1858- PR#7016: fix Stack overflow in GADT typing
1859  Note: Equi-recursive types are considered when checking GADT pattern
1860  exhaustiveness, even when -rectypes is not used.
1861  (Jacques Garrigue, report by Mikhail Mandrykin)
1862
1863- PR#7030: libasmrun_shared.so fails to build on SPARC Solaris
1864  (report and fix by Patrick Star)
1865
1866- PR#7036: Module alias is not taken into account when checking module
1867  type compatibility (in a class type)
1868  (Jacques Garrigue)
1869
1870- PR#7037: more reproducible builds, don't put temp file names into objects
1871  (Xavier Leroy)
1872
1873- PR#7038: out of memory condition in caml_io_mutex_lock
1874  (Xavier Leroy, report by Marc Lasson)
1875
1876- PR#7039: Unix.getsockname returns garbage for unnamed PF_UNIX sockets
1877  (Xavier Leroy)
1878
1879- PR#7042 and GPR#295: CSE optimization confuses the FP literals +0.0 and -0.0
1880  (Xavier Leroy)
1881
1882- PR#7075: Fix repetitions in ocamldoc generated documentation
1883  (Florian Angeletti)
1884
1885- PR#7082: Object type in recursive module's `with` annotation
1886  (Jacques Garrigue and Alain Frisch, report by Nicholas Labich)
1887
1888- PR#7096: ocamldoc uses an incorrect subscript/superscript style
1889  (Gabriel Scherer, report by user 'pierpa')
1890
1891- PR#7108: ocamldoc, have -html preserve custom/extended html generators
1892  (Armaël Guéneau)
1893
1894- PR#7111: reject empty let bindings instead of printing incorrect syntax
1895  (Jérémie Dimino)
1896
1897* PR#7113: -safe-string can break GADT compatibility check
1898  bytes and string are now considered compatible even with -safe-string,
1899  which may break exhaustivity for code assuming they were disjoint
1900  (Jacques Garrigue, report by Jeremy Yallop)
1901
1902- PR#7115: shadowing in a branch of a GADT match breaks unused variable warning
1903  (Alain Frisch, report by Valentin Gatien-Baron)
1904
1905- PR#7133, GPR#450: generate local jump labels on OS X
1906  (Bart Jacobs)
1907
1908- PR#7135: only warn about ground coercions in -principal mode
1909  (Jacques Garrigue, report by Jeremy Yallop)
1910
1911* PR#7152: Typing equality involving non-generalizable type variable
1912  A side-effect of the fix is that, for deeply nested non generalizable
1913  type variables, having an interface file may no longer be sufficient,
1914  and you may have to add a local type annotation (cf PR#7313)
1915  (Jacques Garrigue, report by François Bobot)
1916
1917- PR#7160: Type synonym definitions can weaken gadt constructor types
1918  (Jacques Garrigue, report by Mikhail Mandrykin)
1919
1920- PR#7181: Misleading error message with GADTs and polymorphic variants
1921  (Jacques Garrigue, report by Pierre Chambart)
1922
1923- PR#7182: Assertion failure with recursive modules and externals
1924  (Jacques Garrigue, report by Jeremy Yallop)
1925
1926- PR#7196: "let open" is not correctly pretty-printed to the left of a ';'
1927  (Gabriel Scherer, report by Christophe Raffalli)
1928
1929- PR#7214: Assertion failure in Env.add_gadt_instances
1930  (Jacques Garrigue, report by Stephen Dolan)
1931
1932- PR#7220: fix a memory leak when using both threads and exception backtraces
1933  (Gabriel Scherer, review by François Bobot, report by Rob Hoes)
1934
1935- PR#7222: Escaped existential type
1936  (Jacques Garrigue, report by Florian Angeletti)
1937
1938- PR#7230: Scrutinee discarded in match with only refutation cases
1939  (Jacques Garrigue, report by Jeremy Yallop)
1940
1941- PR#7234: Compatibility check wrong for abstract type constructors
1942  (Jacques Garrigue, report by Stephen Dolan)
1943
1944- PR#7324: OCaml 4.03.0 type checker dies with an assert failure when
1945  given some cyclic recusive module expression
1946  (Jacques Garrigue, report by jmcarthur)
1947
1948- PR#7368: Manual major GC fails to compact the heap
1949  (Krzysztof Pszeniczny)
1950
1951- GPR#205: Clear caml_backtrace_last_exn before registering as root
1952  (report and fix by Frédéric Bour)
1953
1954- GPR#220: minor -dsource error on recursive modules
1955  (Hongbo Zhang)
1956
1957- GPR#228: fix a dangling internal pointer in (bytecode )debug_info
1958  (Gabriel Scherer and Mark Shinwell and Xavier Leroy)
1959
1960- GPR#233: Make CamlinternalMod.init_mod robust to optimization
1961  (Pierre Chambart, Mark Shinwell)
1962
1963- GPR#249: fix a few hardcoded ar commands
1964  (Daniel Bünzli)
1965
1966- GPR#251: fix cross-compilation with ocamldoc enabled
1967  (whitequark)
1968
1969- GPR#280: Fix stdlib dependencies for .p.cmx
1970  (Pierre Chambart, Mark Shinwell)
1971
1972- GPR#283: Fix memory leaks in intern.c when OOM is raised
1973  (Marc Lasson, review by Alain Frisch)
1974
1975- GPR#22: Fix the cleaning of weak pointers. In very rare cases
1976  accessing a value during the cleaning of the weak pointers could
1977  result in the value being removed from one weak arrays and kept in
1978  another one. That breaks the property that a value is removed from a
1979  weak pointer only when it is dead and garbage collected.
1980  (François Bobot, review by Damien Doligez)
1981
1982- GPR#313: Prevent quadratic cases in CSE
1983  (Pierre Chambart, review by Xavier Leroy)
1984
1985- PR#6795, PR#6996: Make ocamldep report errors passed in
1986  [%ocaml.error] extension points
1987  (Jérémie Dimino)
1988
1989- GPR#355: make ocamlnat build again
1990  (Jérémie Dimino, Thomas Refis)
1991
1992- GPR#405: fix compilation under Visual Studio 2015
1993  (David Allsopp)
1994
1995- GPR#441: better type error location in presence of type constraints
1996  (Thomas Refis, report by Arseniy Alekseyev)
1997
1998- GPR#477: reallow docstrings inside object types, and inside polymorphic
1999  variant and arrow types
2000  (Thomas Refis)
2001
2002### Features wishes:
2003
2004- PR#4518, GPR#29: change location format for reporting errors in ocamldoc
2005  (Sergei Lebedev)
2006
2007- PR#4714: List.cons
2008
2009- PR#5418 (comments) : generate dependencies with $(CC) instead of gcc
2010  (Damien Doligez, report by Michael Grünewald)
2011
2012- PR#6167: OCAMLPARAM support for disabling PIC generation ("pic=0")
2013  (Gabor Pali)
2014
2015- PR#6367, GPR#25: introduce Asttypes.arg_label to encode labelled arguments
2016  (Frédéric Bour and Jacques Garrigue)
2017
2018- PR#6452, GPR#140: add internal suport for custom printing formats
2019  (Jérémie Dimino)
2020
2021- PR#6611: remove the option wrapper on optional arguments in the syntax tree
2022  (Alain Frisch, review by Damien Doligez, request by whitequark)
2023
2024- PR#6635: support M.[], M.(), M.{< >} and M.[| |]
2025  (Jeremy Yallop, review by Gabriel Radanne)
2026
2027- PR#6691: install .cmt[i] files for stdlib and compiler-libs
2028  (David Sheets, request by Gabriel Radanne)
2029
2030- PR#6722: compatibility with x32 architecture (x86-64 in ILP32 mode).
2031  ocamlopt is not supported, but bytecode compiles cleanly.
2032  (Adam Borowski and Xavier Leroy)
2033
2034- PR#6742: remove duplicate virtual_flag information from Tstr_class
2035  (Gabriel Radanne and Jacques Garrigue)
2036
2037- PR#6719: improve Buffer.add_channel when not enough input is available
2038  (Simon Cruanes)
2039
2040* PR#6816: reject integer and float literals directly followed by an identifier.
2041  This was prevously read as two separate tokens.
2042  [let abc = 1 in (+) 123abc] was accepted and is now rejected.
2043  (Hugo Heuzard)
2044
2045- PR#6876: improve warning 6 by listing the omitted labels.
2046  (Warning 6: Label omitted in function application)
2047  (Eyyüb Sari)
2048
2049- PR#6924: tiny optim to avoid some spilling of floats in x87
2050  (Alain Frisch)
2051
2052- GPR#111: `(f [@taillcall]) x y` warns if `f x y` is not a tail-call
2053  (Simon Cruanes)
2054
2055- GPR#118: ocamldep -allow-approx: fallback to a lexer-based approximation
2056  (Frédéric Bour)
2057
2058- GPR#137: add untypeast.ml (in open recursion style) to compiler-libs
2059  (Gabriel Radanne)
2060
2061- GPR#142: add a CAMLdrop macro for undoing CAMLparam*/CAMLlocal*
2062  (Thomas Braibant and Damien Doligez)
2063
2064- GPR#145: speeedup bigarray access by optimizing Cmmgen.bigarray_indexing
2065  (Vladimir Brankov, review by Gabriel Scherer)
2066
2067- GPR#147: [type 'a result = Ok of 'a | Error of 'b] in Pervasives
2068  (Yaron Minsky)
2069
2070- GPR#156, GPR#279: optimize caml_frame_descriptors realloc (dynlink speedup)
2071  (Pierre Chambart, Alain Frisch,
2072   review by François Bobot, Xavier Leroy and Damien Doligez)
2073
2074- GPR#165, GPR#221: fix windows compilation warnings
2075  (Bernhard Schommer, Gabriel Scherer, report by Alain Frisch)
2076
2077* GPR#170: Parse arbitrary precision integers.
2078  Accept a single [A-Za-z] as modifier for integers (generalizing 'l','L','n')
2079  and floats.
2080  May cause breakage (ie. ppx preprocessor) because of changes in the parsetree.
2081  This changes PR#6816 a little bit by reading the literal [123a] as a single
2082  token that can later be rewritten by a ppx preprocessor.
2083  (Hugo Heuzard)
2084
2085- GPR#189: Added .dylib and .so as extensions for ocamlmklib
2086  (Edgar Aroutiounian, whitequark)
2087
2088- GPR#191: Making gc.h and some part of memory.h public
2089  (Thomas Refis)
2090
2091- GPR#196: Make [Thread.id] and [Thread.self] [noalloc]
2092  (Clark Gaebel)
2093
2094- GPR#237: a CONTRIBUTING document
2095  (François Bobot, Gabriel Scherer, review by Xavier Leroy)
2096
2097- GPR#245: remove a few remaining French comments
2098  (Florian Angeletti)
2099
2100- GPR#252: improve build instructions in MSVC Windows README
2101  (Philip Daian)
2102
2103- GPR#308: add experimental support for NetBSD/arm (verified on RaspberryPi)
2104  (Rich Neswold)
2105
2106- GPR#335: Type error messages specifies if a type is abstract
2107  because no corresponding cmi could be found.
2108  (Hugo Heuzard)
2109
2110- GPR#365: prevent printing just a single type variable on one side
2111  of a type error clash.
2112  (Hugo Heuzard)
2113
2114- GPR#383: configure: define _ALL_SOURCE for build on AIX7.1
2115  (tkob)
2116
2117- GPR#401: automatically retry failed test directories in the testsuite
2118  (David Allsopp)
2119
2120- GPR#451: an optional 'parallel' target in testsuite/Makefile using the
2121  GNU parallel tool to run tests in parallel.
2122  (Gabriel Scherer)
2123
2124- GPR#555: ensure that register typing constraints are respected at
2125  join points in the control flow graph
2126  (Mark Shinwell, debugging & test case by Arseniy Alekseyev and Leo White,
2127    code review by Xavier Leroy)
2128
2129### Build system:
2130
2131- GPR#388: FlexDLL added as a Git submodule and bootstrappable with the compiler
2132  (David Allsopp)
2133
2134OCaml 4.02.3 (27 Jul 2015):
2135---------------------------
2136
2137Bug fixes:
2138- PR#6908: Top-level custom printing for GADTs: interface change in 4.02.2
2139  (Grégoire Henry, report by Jeremy Yallop)
2140- PR#6919: corrupted final_table
2141  (ygrek)
2142- PR#6926: Regression: ocamldoc lost unattached comment
2143  (Damien Doligez, report by François Bobot)
2144- PR#6930: Aliased result type of GADT constructor results in assertion failure
2145  (Jacques Garrigue)
2146
2147Feature wishes:
2148- PR#6691: install .cmt[i] files for stdlib and compiler-libs
2149  (David Sheets, request by Gabriel Radanne)
2150- GPR#37: New primitive: caml_alloc_dummy_function
2151  (Hugo Heuzard)
2152
2153OCaml 4.02.2 (17 Jun 2015):
2154---------------------------
2155
2156(Changes that can break existing programs are marked with a "*")
2157
2158Language features:
2159- PR#6583: add a new class of binary operators with the same syntactic
2160  precedence as method calls; these operators start with # followed
2161  by a non-empty sequence of operator symbols (for instance #+, #!?).
2162  It is also possible to use '#' as part of these extra symbols
2163  (for instance ##, or #+#); this is rejected by the type-checker,
2164  but can be used e.g. by ppx rewriters.
2165  (Alain Frisch, request by Gabriel Radanne)
2166* PR#6016: add a "nonrec" keyword for type declarations
2167  (Jérémie Dimino)
2168* PR#6612, GPR#152: change the precedence of attributes in type declarations
2169  (Jérémie Dimino)
2170
2171Compilers:
2172- PR#6600: make -short-paths faster by building the printing map
2173  incrementally
2174  (Jacques Garrigue)
2175- PR#6642: replace $CAMLORIGIN in -ccopt with the path to cma or cmxa
2176  (whitequark, Gabriel Scherer, review by Damien Doligez)
2177- PR#6797: new option -output-complete-obj
2178  to output an object file with included runtime and autolink libraries
2179  (whitequark)
2180- PR#6845: -no-check-prims to tell ocamlc not to check primitives in runtime
2181  (Alain Frisch)
2182- GPR#149: Attach documentation comments to parse tree
2183  (Leo White)
2184- GPR#159: Better locations for structure/signature items
2185  (Leo White)
2186
2187Toplevel and debugger:
2188- PR#5958: generalized polymorphic #install_printer
2189  (Pierre Chambart and Grégoire Henry)
2190
2191OCamlbuild:
2192- PR#6237: explicit "infer" tag to control or disable menhir --infer
2193  (Hugo Heuzard)
2194- PR#6625: pass -linkpkg to files built with -output-obj.
2195  (whitequark)
2196- PR#6702: explicit "linkpkg" and "dontlink(foo)" flags
2197  (whitequark, Gabriel Scherer)
2198- PR#6712: Ignore common VCS directories
2199  (whitequark)
2200- PR#6720: pass -g to C compilers when tag 'debug' is set
2201  (whitequark, Gabriel Scherer)
2202- PR#6733: add .byte.so and .native.so targets to pass
2203  -output-obj -cclib -shared.
2204  (whitequark)
2205- PR#6733: "runtime_variant(X)" to pass -runtime-variant X option.
2206  (whitequark)
2207- PR#6774: new menhir-specific flags "only_tokens" and "external_tokens(Foo)"
2208  (François Pottier)
2209
2210Libraries:
2211- PR#6285: Add support for nanosecond precision in Unix.stat()
2212  (Jérémie Dimino, report by user 'gfxmonk')
2213- PR#6781: Add higher baud rates to Unix termios
2214  (Damien Doligez, report by Berke Durak)
2215- PR#6834: Add Obj.{first,last}_non_constant_constructor_tag
2216  (Mark Shinwell, request by Gabriel Scherer)
2217
2218Runtime:
2219- PR#6078: Release the runtime system when calling caml_dlopen
2220  (Jérémie Dimino)
2221- PR#6675: GC hooks
2222  (Damien Doligez and Roshan James)
2223
2224Build system:
2225- PR#5418 (comments) : generate dependencies with $(CC) instead of gcc
2226  (Damien Doligez and Michael Grünewald)
2227- PR#6266: Cross compilation for iOs, Android etc
2228  (whitequark, review by Damien Doligez and Mark Shinwell)
2229
2230Installation procedure:
2231- Update instructions for x86-64 PIC mode and POWER architecture builds
2232  (Mark Shinwell)
2233
2234Bug fixes:
2235- PR#5271: Location.prerr_warning is hard-coded to use Format.err_formatter
2236  (Damien Doligez, report by Rolf Rolles)
2237- PR#5395: OCamlbuild mishandles relative symlinks and include paths
2238  (Damien Doligez, report by Didier Le Botlan)
2239- PR#5822: wrong value of Options.ext_dll on windows
2240  (Damien Doligez and Daniel Weil)
2241- PR#5836, PR#6684: printing lazy values in ocamldebug may segfault
2242  (Gabriel Scherer, request by the Coq team)
2243- PR#5887: move the byterun/*.h headers to byterun/caml/*.h to avoid
2244  header name clashes
2245  (Jérôme Vouillon and Adrien Nader and whitequark)
2246- PR#6281: Graphics window does not acknowledge second click (double click)
2247  (Kyle Headley)
2248- PR#6490: incorrect backtraces in gdb on AArch64.  Also fixes incorrect
2249  backtraces on 32-bit ARM.
2250  (Mark Shinwell)
2251- PR#6573: extern "C" for systhreads/threads.h
2252  (Mickaël Delahaye)
2253- PR#6575: Array.init evaluates callback although it should not do so
2254  (Alain Frisch, report by Gerd Stolpmann)
2255- PR#6607: The manual doesn't mention 0x200 flag for OCAMLRUNPARAM=v
2256  (Alain Frisch)
2257- PR#6616: allow meaningful use of -use-runtime without -custom.
2258  (whitequark)
2259- PR#6617: allow android build with pthreads support (since SDK r10c)
2260  (whitequark)
2261- PR#6626: ocamlbuild on cygwin cannot find ocamlfind
2262  (Gergely Szilvasy)
2263- PR#6628: Configure script rejects legitimate arguments
2264  (Michael Grünewald, Damien Doligez)
2265- PR#6630: Failure of tests/prim-bigstring/{big,}string.ml on big-endian
2266  architectures
2267  (Pierre Chambart, testing by Mark Shinwell)
2268- PR#6640: ocamlbuild: wrong "unused tag" warning on "precious"
2269  (report by user 'william')
2270- PR#6652: ocamlbuild -clean does not print a newline after output
2271  (Damien Doligez, report by Andi McClure)
2272- PR#6658: cross-compiler: version check not working on OS X
2273  (Gerd Stolpmann)
2274- PR#6665: Failure of tests/asmcomp on sparc
2275  (Stéphane Glondu)
2276- PR#6667: wrong implementation of %bswap16 on ARM64
2277  (Xavier Leroy)
2278- PR#6669: fix 4.02 regression in toplevel printing of lazy values
2279  (Leo White, review by Gabriel Scherer)
2280- PR#6671: Windows: environment variable 'TZ' affects Unix.gettimeofday
2281  (Mickaël Delahaye and Damien Doligez)
2282- PR#6680: Missing parentheses in warning about polymorphic variant value
2283  (Jacques Garrigue and Gabriel Scherer, report by Philippe Veber)
2284- PR#6686: Bug in [subst_boxed_number]
2285  (Jérémie Dimino, Mark Shinwell)
2286- PR#6690: Uncaught exception (Not_found) with (wrong) wildcard or unification
2287  type variable in place of a local abstract type
2288  (Jacques Garrigue, report by Mikhail Mandrykin)
2289- PR#6693 (part two): Incorrect relocation types in x86-64 runtime system
2290  (whitequark, review by Jacques-Henri Jourdan, Xavier Leroy and Mark Shinwell)
2291- PR#6717: Pprintast does not print let-pattern attributes
2292  (Gabriel Scherer, report by whitequark)
2293- PR#6727: Printf.sprintf "%F" misbehavior
2294  (Benoît Vaugon, report by Vassili Karpov)
2295- PR#6747: ocamlobjinfo: missing symbol caml_plugin_header due to underscore
2296  (Damien Doligez, Maverick Woo)
2297- PR#6749: ocamlopt returns n for (n mod 1) instead of 0
2298  (Mark Shinwell and Jérémie Dimino)
2299- PR#6753: Num.quo_num and Num.mod_num incorrect for some negative arguments
2300  (Xavier Leroy)
2301- PR#6758: Ocamldoc "analyse_module: parsetree and typedtree don't match"
2302  (Damien Doligez, report by user 'maro')
2303- PR#6759: big_int_of_string incorrectly parses some hexa literals
2304  (Damien Doligez, report by Pierre-yves Strub)
2305- PR#6763: #show with -short-paths doesn't select shortest type paths
2306  (Jacques Garrigue, report by David Sheets)
2307- PR#6768: Typechecker overflow the stack on cyclic type
2308  (Jacques Garrigue, report by user 'darktenaibre')
2309- PR#6770: (duplicate of PR#6686)
2310- PR#6772: asmrun/signals_asm.c doesn't compile on NetBSD/i386
2311  (Kenji Tokudome)
2312- PR#6775: Digest.file leaks file descriptor on error
2313  (Valentin Gatien-Baron)
2314- PR#6779: Cross-compilers cannot link bytecode using custom primitives
2315  (Damien Doligez, request by whitequark)
2316- PR#6787: Soundness bug with polymorphic variants
2317  (Jacques Garrigue, with help from Leo White and Grégoire Henry,
2318   report by Michael O'Connor)
2319- PR#6790: otherlibs should be built with -g
2320  (Damien Doligez, report by whitequark)
2321- PR#6791: "%s@[", "%s@{" regression in Scanf
2322  (Benoît Vaugon)
2323- PR#6793: ocamlbuild passes nonsensical "-ocamlc ..." commands to menhir
2324  (Gabriel Scherer, report by Damien Doligez)
2325- PR#6799: include guards missing for unixsupport.h and other files
2326  (Andreas Hauptmann)
2327- PR#6810: Improve documentation of Bigarray.Genarray.map_file
2328  (Mark Shinwell and Daniel Bünzli)
2329- PR#6812: -short-paths and -no-alias-deps can create inconsistent assumptions
2330  (Jacques Garrigue, report by Valentin Gatien-Baron)
2331- PR#6817: GADT exhaustiveness breakage with modules
2332  (Leo White, report by Pierre Chambart)
2333- PR#6824: fix buffer sharing on partial application of Format.asprintf
2334  (Gabriel Scherer, report by Alain Frisch)
2335- PR#6831: Build breaks for -aspp gcc on solaris-like OSs
2336  (John Tibble)
2337- PR#6836: Assertion failure using -short-paths
2338  (Jacques Garrigue, report by David Sheets)
2339- PR#6837: Build profiling libraries on FreeBSD and NetBSD x86-64
2340  (Mark Shinwell, report by Michael Grünewald)
2341- PR#6841: Changing compilation unit name with -o breaks ocamldebug
2342  (Jacques Garrigue, report by Jordan Walke)
2343- PR#6842: export Typemod.modtype_of_package
2344- PR#6843: record weak dependencies even when the .cmi is missing
2345  (Leo White, Gabriel Scherer)
2346- PR#6849: Inverted pattern unification error
2347  (Jacques Garrigue, report by Leo White)
2348- PR#6857: __MODULE__ doesn't give the current module with -o
2349  (Jacques Garrigue, report by Valentin Gatien-Baron)
2350- PR#6862: Exhaustiveness check wrong for class constructor arguments
2351  (Jacques Garrigue)
2352- PR#6869: Improve comment on [Hashtbl.hash_param]
2353  (Mark Shinwell, report by Jun Furuse)
2354- PR#6870: Unsoundness when -rectypes fails to detect non-contractive type
2355  (Jacques Garrigue, report by Stephen Dolan)
2356- PR#6872: Type-directed propagation fails to disambiguate variants
2357  that are also exception constructors
2358  (Jacques Garrigue, report by Romain Beauxis)
2359- PR#6878: AArch64 backend generates invalid asm: conditional branch
2360  out of range (Mark Shinwell, report by Richard Jones, testing by Richard
2361  Jones and Xavier Leroy, code review by Xavier Leroy and Thomas Refis)
2362- PR#6879: Wrong optimization of 1 mod n
2363  (Mark Shinwell, report by Jean-Christophe Filliâtre)
2364- PR#6884: The __CYGWIN32__ #define should be replaced with __CYGWIN__
2365  (Adrien Nader)
2366- PR#6886: -no-alias-deps allows to build self-referential compilation units
2367  (Jacques Garrigue, report by Valentin Gatien-Baron)
2368- PR#6889: ast_mapper fails to rewrite class attributes
2369  (Sébastien Briais)
2370- PR#6893: ocamlbuild:  "tag not used" warning when using (p)dep
2371  (Gabriel Scherer, report by Christiano Haesbaert)
2372- GPR#143: fix getsockopt behaviour for boolean socket options
2373  (Anil Madhavapeddy and Andrew Ray)
2374- GPR#190: typo in pervasives
2375  (Guillaume Bury)
2376- Misplaced assertion in major_gc.c for no-naked-pointers mode
2377  (Stephen Dolan, Mark Shinwell)
2378
2379Feature wishes:
2380- PR#6452, GPR#140: add internal suport for custom printing formats
2381  (Jérémie Dimino)
2382- PR#6641: add -g, -ocamlcflags, -ocamloptflags options to ocamlmklib
2383  (whitequark)
2384- PR#6693: also build libasmrun_shared.so and lib{asm,caml}run_pic.a
2385  (whitequark, review by Mark Shinwell)
2386- PR#6842: export Typemod.modtype_of_package
2387  (Jacques Garrigue, request by Jun Furuse)
2388- GPR#139: more versatile specification of locations of .annot
2389  (Christophe Troestler, review by Damien Doligez)
2390- GPR#171: allow custom warning printers / catchers
2391  (Benjamin Canou, review by Damien Doligez)
2392- GPR#191: Making gc.h and some part of memory.h public
2393  (Thomas Refis)
2394
2395OCaml 4.02.1 (14 Oct 2014):
2396---------------------------
2397
2398(Changes that can break existing programs are marked with a "*")
2399
2400Standard library:
2401* Add optional argument ?limit to Arg.align.
2402
2403Bug Fixes:
2404- PR#4099: Bug in Makefile.nt: won't stop on error
2405  (George Necula)
2406- PR#6181: Improve MSVC build
2407  (Chen Gang)
2408- PR#6207: Configure doesn't detect features correctly on Haiku
2409  (Jessica Hamilton)
2410- PR#6466: Non-exhaustive matching warning message for open types is confusing
2411  (whitequark)
2412- PR#6529: fix quadratic-time algorithm in Consistbl.extract.
2413  (Xavier Leroy, Alain Frisch, relase-worthy report by Jacques-Pascal Deplaix)
2414- PR#6530: Add stack overflow handling for native code (OpenBSD i386 and amd64)
2415  (Cristopher Zimmermann)
2416- PR#6533: broken semantics of %(%) when substituted by a box
2417  (Benoît Vaugon, report by Boris Yakobowski)
2418- PR#6534: legacy support for %.10s
2419  (Benoît Vaugon, Gabriel Scherer, report by Nick Chapman)
2420- PR#6536: better documentation of flag # in format strings
2421  (Damien Doligez, report by Nick Chapman)
2422- PR#6544: Bytes and CamlinternalFormat missing from threads stdlib.cma
2423  (Christopher Zimmermann)
2424- PR#6546: -dsource omits parens for `List ((`String "A")::[]) in patterns
2425  (Gabriel Scherer, report by whitequark)
2426- PR#6547: __MODULE__ aborts the compiler if the module name cannot be inferred
2427  (Jacques Garrigue, report by Kaustuv Chaudhuri)
2428- PR#6549: Debug section is sometimes not readable when using -pack
2429  (Hugo Heuzard, review by Gabriel Scherer)
2430- PR#6553: Missing command line options for ocamldoc
2431  (Maxence Guesdon)
2432- PR#6554: fix race condition when retrieving backtraces
2433  (Jérémie Dimino, Mark Shinwell).
2434- PR#6557: String.sub throws Invalid_argument("Bytes.sub")
2435  (Damien Doligez, report by Oliver Bandel)
2436- PR#6562: Fix ocamldebug module source lookup
2437  (Leo White)
2438- PR#6563: Inclusion of packs failing to run module initializers
2439  (Jacques Garrigue, report by Mark Shinwell)
2440- PR#6564: infinite loop in Mtype.remove_aliases
2441  (Jacques Garrigue, report by Mark Shinwell)
2442- PR#6565: compilation fails with Env.Error(_)
2443  (Jacques Garrigue and Mark Shinwell)
2444- PR#6566: -short-paths and signature inclusion errors
2445  (Jacques Garrigue, report by Mark Shinwell)
2446- PR#6572: Fatal error with recursive modules
2447  (Jacques Garrigue, report by Quentin Stievenart)
2448- PR#6575: Array.init evaluates callback although it should not do so
2449  (Alain Frisch, report by Gerd Stolpmann)
2450- PR#6578: Recursive module containing alias causes Segmentation fault
2451  (Jacques Garrigue)
2452- PR#6581: Some bugs in generative functors
2453  (Jacques Garrigue, report by Mark Shinwell)
2454- PR#6584: ocamldep support for "-open M"
2455  (Gabriel Scherer, review by Damien Doligez, report by Hezekiah M. Carty)
2456- PR#6588: Code generation errors for ARM
2457  (Mark Shinwell, Xavier Leroy)
2458- PR#6590: Improve Windows (MSVC and mingw) build
2459  (Chen Gang)
2460- PR#6599: ocamlbuild: add -bin-annot when using -pack
2461  (Christopher Zimmermann)
2462- PR#6602: Fatal error when tracing a function with abstract type
2463  (Jacques Garrigue, report by Hugo Herbelin)
2464- ocamlbuild: add an -ocamlmklib option to change the ocamlmklib command
2465  (Jérôme Vouillon)
2466
2467OCaml 4.02.0 (29 Aug 2014):
2468---------------------------
2469
2470(Changes that can break existing programs are marked with a "*")
2471
2472Language features:
2473- Attributes and extension nodes
2474  (Alain Frisch)
2475- Generative functors (PR#5905)
2476  (Jacques Garrigue)
2477* Module aliases
2478  (Jacques Garrigue)
2479* Alternative syntax for string literals {id|...|id} (can break comments)
2480  (Alain Frisch)
2481- Separation between read-only strings (type string) and read-write byte
2482  sequences (type bytes). Activated by command-line option -safe-string.
2483  (Damien Doligez)
2484- PR#6318: Exception cases in pattern matching
2485  (Jeremy Yallop, backend by Alain Frisch)
2486- PR#5584: Extensible open datatypes
2487  (Leo White)
2488
2489Build system for the OCaml distribution:
2490- Use -bin-annot when building.
2491- Use GNU make instead of portable makefiles.
2492- Updated build instructions for 32-bit Mac OS X on Intel hardware.
2493
2494Shedding weight:
2495* Removed Camlp4 from the distribution, now available as third-party software.
2496* Removed Labltk from the distribution, now available as a third-party library.
2497
2498Type system:
2499* PR#6235: Keep typing of pattern cases independent in principal mode
2500  (i.e. information from previous cases is no longer used when typing
2501  patterns; cf. 'PR#6235' in testsuite/test/typing-warnings/records.ml)
2502  (Jacques Garrigue)
2503- Allow opening a first-class module or applying a generative functor
2504  in the body of a generative functor. Allow it also in the body of
2505  an applicative functor if no types are created
2506  (Jacques Garrigue, suggestion by Leo White)
2507* Module aliases are now typed in a specific way, which remembers their
2508  identity. Compiled interfaces become smaller, but may depend on the
2509  original modules. This also changes the signature inferred by
2510  "module type of".
2511  (Jacques Garrigue, feedback from Leo White, Mark Shinwell and Nick Chapman)
2512- PR#6331: Slight change in the criterion to distinguish private
2513  abbreviations and private row types: create a private abbreviation for
2514  closed objects and fixed polymorphic variants.
2515  (Jacques Garrigue)
2516* PR#6333: Compare first class module types structurally rather than
2517  nominally. Value subtyping allows module subtyping as long as the internal
2518  representation is unchanged.
2519  (Jacques Garrigue)
2520
2521Compilers:
2522- More aggressive constant propagation, including float and
2523  int32/int64/nativeint arithmetic.  Constant propagation for floats
2524  can be turned off with option -no-float-const-prop, for codes that
2525  change FP rounding modes at run-time.
2526  (Xavier Leroy)
2527- New back-end optimization pass: common subexpression elimination (CSE).
2528  (Reuses results of previous computations instead of recomputing them.)
2529  (Xavier Leroy)
2530- New back-end optimization pass: dead code elimination.
2531  (Removes arithmetic and load instructions whose results are unused.)
2532  (Xavier Leroy)
2533- PR#6269: Optimization of sequences of string patterns
2534  (Benoît Vaugon and Luc Maranget)
2535- Experimental native code generator for AArch64 (ARM 64 bits)
2536  (Xavier Leroy)
2537- PR#6042: Optimization of integer division and modulus by constant divisors
2538  (Xavier Leroy and Phil Denys)
2539- Add "-open" command line flag for opening a single module before typing
2540  (Leo White, Mark Shinwell and Nick Chapman)
2541* "-o" now sets module name to the output file name up to the first "."
2542  (it also applies when "-o" is not given, i.e. the module name is then
2543   the input file name up to the first ".")
2544  (Leo White, Mark Shinwell and Nick Chapman)
2545* PR#5779: better sharing of structured constants
2546  (Alain Frisch)
2547- PR#5817: new flag to keep locations in cmi files
2548  (Alain Frisch)
2549- PR#5854: issue warning 3 when referring to a value marked with
2550  the [@@ocaml.deprecated] attribute
2551  (Alain Frisch, suggestion by Pierre-Marie Pédrot)
2552- PR#6017: a new format implementation based on GADTs
2553  (Benoît Vaugon and Gabriel Scherer)
2554* PR#6203: Constant exception constructors no longer allocate
2555  (Alain Frisch)
2556- PR#6260: avoid unnecessary boxing in let
2557  (Vladimir Brankov)
2558- PR#6345: Better compilation of optional arguments with default values
2559  (Alain Frisch, review by Jacques Garrigue)
2560- PR#6389: ocamlopt -opaque option for incremental native compilation
2561  (Pierre Chambart, Gabriel Scherer)
2562
2563Toplevel interactive system:
2564- PR#5377: New "#show_*" directives
2565  (ygrek, Jacques Garrigue and Alain Frisch)
2566
2567Runtime system:
2568- New configure option "-no-naked-pointers" to improve performance by
2569  avoiding page table tests during block darkening and the marking phase
2570  of the major GC.  In this mode, all out-of-heap pointers must point at
2571  things that look like OCaml values: in particular they must have a valid
2572  header.  The colour of said headers should be black.
2573  (Mark Shinwell, reviews by Damien Doligez and Xavier Leroy)
2574- Fixed bug in native code version of [caml_raise_with_string] that could
2575  potentially lead to heap corruption.
2576  (Mark Shinwell)
2577* Blocks initialized by [CAMLlocal*] and [caml_alloc] are now filled with
2578  [Val_unit] rather than zero.
2579  (Mark Shinwell)
2580- Fixed a major performance problem on large heaps (~1GB) by making heap
2581  increments proportional to heap size by default
2582  (Damien Doligez)
2583- PR#4765: Structural equality treats exception specifically
2584  (Alain Frisch)
2585- PR#5009: efficient comparison/indexing of exceptions
2586  (Alain Frisch, request by Markus Mottl)
2587- PR#6075: avoid using unsafe C library functions (strcpy, strcat, sprintf)
2588  (Xavier Leroy, reports from user 'jfc' and Anil Madhavapeddy)
2589- An ISO C99-compliant C compiler and standard library is now assumed.
2590  (Plus special exceptions for MSVC.)  In particular, emulation code for
2591  64-bit integer arithmetic was removed, the C compiler must support a
2592  64-bit integer type.
2593  (Xavier Leroy)
2594
2595Standard library:
2596* Add new modules Bytes and BytesLabels for mutable byte sequences.
2597  (Damien Doligez)
2598- PR#4986: add List.sort_uniq and Set.of_list
2599  (Alain Frisch)
2600- PR#5935: a faster version of "raise" which does not maintain the backtrace
2601  (Alain Frisch)
2602- PR#6146: support "Unix.kill pid Sys.sigkill" under Windows
2603  (Romain Bardou and Alain Frisch)
2604- PR#6148: speed improvement for Buffer
2605  (John Whitington)
2606- PR#6180: efficient creation of uninitialized float arrays
2607  (Alain Frisch, request by Markus Mottl)
2608- PR#6355: Improve documentation regarding finalisers and multithreading
2609  (Daniel Bünzli, Mark Shinwell)
2610- Trigger warning 3 for all values marked as deprecated in the documentation.
2611  (Damien Doligez)
2612
2613OCamldoc:
2614- PR#6257: handle full doc comments for variant constructors and
2615  record fields
2616  (Maxence Guesdon, request by ygrek)
2617- PR#6274: allow doc comments on object types
2618  (Thomas Refis)
2619- PR#6310: fix ocamldoc's subscript/superscript CSS font size
2620  (Anil Madhavapeddy)
2621- PR#6425: fix generation of man pages
2622  (Maxence Guesdon, report by Anil Madhavapeddy)
2623
2624Bug fixes:
2625- PR#2719: wrong scheduling of bound checks within a
2626  try...with Invalid_argument -> _ ...  (Xavier Leroy)
2627- PR#4719: Sys.executable_name wrong if executable name contains dots (Windows)
2628  (Alain Frisch, report by Bart Jacobs)
2629- PR#5406 ocamlbuild: "tag 'package' does not expect a parameter"
2630  (Gabriel Scherer)
2631- PR#5598, PR#6165: Alterations to handling of \013 in source files
2632  breaking other tools
2633  (David Allsopp and Damien Doligez)
2634- PR#5820: Fix camlp4 lexer roll back problem
2635  (Hongbo Zhang)
2636- PR#5946: CAMLprim taking (void) as argument
2637  (Benoît Vaugon)
2638- PR#6038: on x86-32, enforce 16-byte stack alignment for compatibility
2639  with recent GCC and Clang.  Win32/MSVC keeps 4-byte stack alignment.
2640  (Xavier Leroy)
2641- PR#6062: Fix a 4.01 camlp4 DELETE_RULE regression caused by commit 13047
2642  (Hongbo Zhang, report by Christophe Troestler)
2643- PR#6173: Typing error message is worse than before
2644  (Jacques Garrigue and John Whitington)
2645- PR#6174: OCaml compiler loops on an example using GADTs (-rectypes case)
2646  (Jacques Garrigue and Grégoire Henry, report by Chantal Keller)
2647- PR#6175: open! was not suppored by camlp4
2648  (Hongbo Zhang)
2649- PR#6184: ocamlbuild: `ocamlfind ocamldep` does not support -predicate
2650  (Jacques-Pascal Deplaix)
2651- PR#6194: Incorrect unused warning with first-class modules in patterns
2652  (Jacques Garrigue, report by Markus Mottl and Leo White)
2653- PR#6211: in toplevel interactive use, bad interaction between uncaught
2654  exceptions and multiple bindings of the form "let x = a let y = b;;".
2655  (Xavier Leroy)
2656- PR#6216: inlining of GADT matches generates invalid assembly
2657  (Xavier Leroy and Alain Frisch, report by Mark Shinwell)
2658- PR#6232: Don't use [mktemp] on platforms where [mkstemp] is available
2659  (Stéphane Glondu, Mark Shinwell)
2660- PR#6233: out-of-bounds exceptions lose their locations on ARM, PowerPC
2661  (Jacques-Henri Jourdan and Xavier Leroy,
2662   report and testing by Stéphane Glondu)
2663- PR#6235: Issue with type information flowing through a variant pattern
2664  (Jacques Garrigue, report by Hongbo Zhang)
2665- PR#6239: sometimes wrong stack alignment when raising exceptions
2666           in -g mode with backtraces active
2667  (Xavier Leroy, report by Yaron Minsky)
2668- PR#6240: Fail to expand module type abbreviation during substyping
2669  (Jacques Garrigue, report by Leo White)
2670- PR#6241: Assumed inequality between paths involving functor arguments
2671  (Jacques Garrigue, report by Jeremy Yallop)
2672- PR#6243: Make "ocamlopt -g" more resistant to ill-formed locations
2673  (Xavier Leroy, report by Pierre-Marie Pédrot)
2674- PR#6262: equality of first-class modules take module aliases into account
2675  (Alain Frisch and Leo White)
2676- PR#6268: -DMODEL_$(MODEL) not passed when building asmrun/arm.p.o
2677  (Peter Michael Green)
2678- PR#6273: fix Sys.file_exists on large files (Win32)
2679  (Christoph Bauer)
2680- PR#6275: Soundness bug related to type constraints
2681  (Jacques Garrigue, report by Leo White)
2682- PR#6293: Assert_failure with invalid package type
2683  (Jacques Garrigue, report by Elnatan Reisner)
2684- PR#6300: ocamlbuild -use-ocamlfind conflicts with -ocamlc
2685  (Gabriel Scherer)
2686- PR#6302: bytecode debug information re-read from filesystem every time
2687  (Jacques-Henri Jourdan)
2688- PR#6307: Behavior of 'module type of' w.r.t. module aliases
2689  (Jacques Garrigue, report by Alain Frisch)
2690- PR#6332: Unix.open_process fails to pass empty arguments under Windows
2691  (Damien Doligez, report Virgile Prevosto)
2692- PR#6346: Build failure with latest version of xcode on OSX
2693  (Jérémie Dimino)
2694- PR#6348: Unification failure for GADT when original definition is hidden
2695  (Leo White and Jacques Garrigue, report by Jeremy Yallop)
2696- PR#6352: Automatic removal of optional arguments and sequencing
2697  (Jacques Garrigue and Alain Frisch)
2698- PR#6361: Hashtbl.hash not terminating on some lazy values w/ recursive types
2699  (Xavier Leroy, report by Leo White)
2700- PR#6383: Exception Not_found when using object type in absent module
2701  (Jacques Garrigue, report by Sébastien Briais)
2702- PR#6384: Uncaught Not_found exception with a hidden .cmi file
2703  (Leo White)
2704- PR#6385: wrong allocation of large closures by the bytecode interpreter
2705  (Xavier Leroy, report by Stephen Dolan)
2706- PR#6394: Assertion failed in Typecore.expand_path
2707  (Alain Frisch and Jacques Garrigue)
2708- PR#6405: unsound interaction of -rectypes and GADTs
2709  (Jacques Garrigue, report by Gabriel Scherer and Benoît Vaugon)
2710- PR#6408: Optional arguments given as ~?arg instead of ?arg in message
2711  (Michael O'Connor)
2712- PR#6411: missing libgcc_s_sjlj-1.dll in mingw (add -static-libgcc)
2713  (Jun Furuse and Alain Frisch, Jonathan Protzenko and Adrien Nader)
2714- PR#6436: Typos in @deprecated text in stdlib/arrayLabels.mli
2715  (John Whitington)
2716- PR#6439: Don't use the deprecated [getpagesize] function
2717  (John Whitington, Mark Shinwell)
2718- PR#6441: undetected tail-call in some mutually-recursive functions
2719  (many arguments, and mutual block mixes functions and non-functions)
2720  (Stefan Holdermans, review by Xavier Leroy)
2721- PR#6443: ocaml segfault when List.fold_left is traced then executed
2722  (Jacques Garrigue, report by user 'Reventlov')
2723- PR#6451: some bugs in untypeast.ml
2724  (Jun Furuse, review by Alain Frisch)
2725- PR#6460: runtime assertion failure with large [| e1;...eN |]
2726  float array expressions
2727  (Leo White)
2728- PR#6463: -dtypedtree fails on class fields
2729  (Leo White)
2730- PR#6469: invalid -dsource printing of "external _pipe = ...", "Pervasives.(!)"
2731  (Gabriel Scherer and Damien Doligez, user 'ngunn')
2732- PR#6482: ocamlbuild fails when _tags file in unhygienic directory
2733  (Gabriel Scherer)
2734- PR#6502: ocamlbuild spurious warning on "use_menhir" tag
2735  (Xavier Leroy)
2736- PR#6505: Missed Type-error leads to a segfault upon record access
2737  (Jacques Garrigue, Jeremy Yallop, report by Christoph Höger)
2738- PR#6507: crash on AArch64 resulting from incorrect setting of
2739  [caml_bottom_of_stack].  (Richard Jones, Mark Shinwell)
2740- PR#6509: add -linkall flag to ocamlcommon.cma
2741  (Frédéric Bour)
2742- PR#6513: Fatal error Ctype.Unify(_) in functor type
2743- PR#6523: failure upon character bigarray access, and unnecessary change
2744  in comparison ordering (Jeremy Yallop, Mark Shinwell)
2745- bound-checking bug in caml_string_{get,set}{16,32,64}
2746  (Pierre Chambart and Gabriel Scherer, report by Nicolas Trangez)
2747- sometimes wrong stack alignment at out-of-bounds array access
2748  (Gabriel Scherer and Xavier Leroy, report by Pierre Chambart)
2749
2750Features wishes:
2751- PR#4243: make the Makefiles parallelizable
2752  (Grégoire Henry and Damien Doligez)
2753- PR#4323: have "of_string" in Num and Big_int work with binary and
2754           hex representations
2755  (Zoe Paraskevopoulou, review by Gabriel Scherer)
2756- PR#4771: Clarify documentation of Dynlink.allow_only
2757  (Damien Doligez, report by David Allsopp)
2758- PR#4855: 'camlp4 -I +dir' accepted, dir is relative to 'camlp4 -where'
2759  (Jun Furuse and Hongbo Zhang, report by Dmitry Grebeniuk)
2760- PR#5201: ocamlbuild: add --norc to the bash invocation to help performances
2761  (Daniel Weil)
2762- PR#5650: Camlp4FoldGenerator doesn't handle well "abstract" types
2763  (Hongbo Zhang)
2764- PR#5808: allow simple patterns, not just identifiers, in "let p : t = ..."
2765  (Alain Frisch)
2766- PR#5851: warn when -r is disabled because no _tags file is present
2767  (Gabriel Scherer)
2768- PR#5899: a programmer-friendly access to backtrace information
2769  (Jacques-Henri Jourdan and Gabriel Scherer)
2770- PR#6000 comment 9644: add a warning for non-principal coercions to format
2771  (Jacques Garrigue, report by Damien Doligez)
2772- PR#6054: add support for M.[ foo ], M.[| foo |] etc.
2773  (Kaustuv Chaudhuri)
2774- PR#6064: GADT representation for Bigarray.kind + CAML_BA_CHAR runtime kind
2775  (Jeremy Yallop, review by Gabriel Scherer)
2776- PR#6071: Add a -noinit option to the toplevel
2777  (David Sheets)
2778- PR#6087: ocamlbuild, improve _tags parsing of escaped newlines
2779  (Gabriel Scherer, request by Daniel Bünzli)
2780- PR#6109: Typos in ocamlbuild error messages
2781  (Gabriel Kerneis)
2782- PR#6116: more efficient implementation of Digest.to_hex
2783  (ygrek)
2784- PR#6142: add cmt file support to ocamlobjinfo
2785  (Anil Madhavapeddy)
2786- PR#6166: document -ocamldoc option of ocamlbuild
2787  (Xavier Clerc)
2788- PR#6182: better message for virtual objects and class types
2789  (Leo White, Stephen Dolan)
2790- PR#6183: enhanced documentation for 'Unix.shutdown_connection'
2791  (Anil Madhavapeddy, report by Jun Furuse)
2792- PR#6187: ocamlbuild: warn when using -plugin-tag(s) without myocamlbuild.ml
2793  (Jacques-Pascal Deplaix)
2794- PR#6246: allow wildcard _ as for-loop index
2795  (Alain Frisch, request by ygrek)
2796- PR#6267: more information printed by "bt" command of ocamldebug
2797  (Josh Watzman)
2798- PR#6270: remove need for -I directives to ocamldebug in common case
2799  (Josh Watzman, review by Xavier Clerc and Alain Frisch)
2800- PR#6311: Improve signature mismatch error messages
2801  (Alain Frisch, suggestion by Daniel Bünzli)
2802- PR#6358: obey DESTDIR in install targets
2803  (Gabriel Scherer, request by François Berenger)
2804- PR#6388, PR#6424: more parsetree correctness checks for -ppx users
2805  (Alain Frisch, request by whitequark and Jun Furuse)
2806- PR#6406: Expose OCaml version in C headers
2807  (whitequark and Romain Calascibetta)
2808- PR#6446: improve "unused declaration" warnings wrt. name shadowing
2809  (Alain Frisch)
2810- PR#6495: ocamlbuild tags 'safe_string', 'unsafe_string'
2811  (Anil Madhavapeddy)
2812- PR#6497: pass context information to -ppx preprocessors
2813  (whitequark, Alain Frisch)
2814- ocamllex: user-definable refill action
2815  (Frédéric Bour, review by Gabriel Scherer and Luc Maranget)
2816- shorten syntax for functor signatures: "functor (M1:S1) (M2:S2) .. -> .."
2817  (Thomas Gazagnaire and Jeremy Yallop, review by Gabriel Scherer)
2818- make ocamldebug -I auto-detection work with ocamlbuild
2819  (Josh Watzman)
2820
2821OCaml 4.01.0 (12 Sep 2013):
2822---------------------------
2823
2824(Changes that can break existing programs are marked with a "*")
2825
2826Other libraries:
2827- Labltk: updated to Tcl/Tk 8.6.
2828
2829Type system:
2830- PR#5759: use well-disciplined type information propagation to
2831  disambiguate label and constructor names
2832  (Jacques Garrigue, Alain Frisch and Leo White)
2833* Propagate type information towards pattern-matching, even in the presence of
2834  polymorphic variants (discarding only information about possibly-present
2835  constructors). As a result, matching against absent constructors is no longer
2836  allowed for exact and fixed polymorphic variant types.
2837  (Jacques Garrigue)
2838* PR#6035: Reject multiple declarations of the same method or instance variable
2839  in an object
2840  (Alain Frisch)
2841
2842Compilers:
2843- PR#5861: raise an error when multiple private keywords are used in type
2844  declarations
2845  (Hongbo Zhang)
2846- PR#5634: parsetree rewriter (-ppx flag)
2847  (Alain Frisch)
2848- ocamldep now supports -absname
2849  (Alain Frisch)
2850- PR#5768: On "unbound identifier" errors, use spell-checking to suggest names
2851  present in the environment
2852  (Gabriel Scherer)
2853- ocamlc has a new option -dsource to visualize the parsetree
2854  (Alain Frisch, Hongbo Zhang)
2855- tools/eqparsetree compares two parsetree ignoring location
2856  (Hongbo Zhang)
2857- ocamlopt now uses clang as assembler on OS X if available, which enables
2858  CFI support for OS X.
2859  (Benedikt Meurer)
2860- Added a new -short-paths option, which attempts to use the shortest
2861  representation for type constructors inside types, taking open modules
2862  into account. This can make types much more readable if your code
2863  uses lots of functors.
2864  (Jacques Garrigue)
2865- PR#5986: added flag -compat-32 to ocamlc, ensuring that the generated
2866  bytecode executable can be loaded on 32-bit hosts.
2867  (Xavier Leroy)
2868- PR#5980: warning on open statements which shadow an existing
2869  identifier (if it is actually used in the scope of the open); new
2870  open! syntax to silence it locally
2871  (Alain Frisch, thanks to a report of Daniel Bünzli)
2872* warning 3 is extended to warn about other deprecated features:
2873  - ISO-latin1 characters in identifiers
2874  - uses of the (&) and (or) operators instead of (&&) and (||)
2875  (Damien Doligez)
2876- Experimental OCAMLPARAM for ocamlc and ocamlopt
2877  (Fabrice Le Fessant)
2878- PR#5571: incorrect ordinal number in error message
2879  (Alain Frisch, report by John Carr)
2880- PR#6073: add signature to Tstr_include
2881  (patch by Leo White)
2882
2883Standard library:
2884- PR#5899: expose a way to inspect the current call stack,
2885  Printexc.get_callstack
2886  (Gabriel Scherer, Jacques-Henri Jourdan, Alain Frisch)
2887- PR#5986: new flag Marshal.Compat_32 for the serialization functions
2888  (Marshal.to_*), forcing the output to be readable on 32-bit hosts.
2889  (Xavier Leroy)
2890- infix application operators |> and @@ in Pervasives
2891  (Fabrice Le Fessant)
2892- PR#6176: new Format.asprintf function with a %a formatter
2893  compatible with Format.fprintf (unlike Format.sprintf)
2894  (Pierre Weis)
2895
2896Other libraries:
2897- PR#5568: add O_CLOEXEC flag to Unix.openfile, so that the returned
2898  file descriptor is created in close-on-exec mode
2899  (Xavier Leroy)
2900
2901Runtime system:
2902* PR#6019: more efficient implementation of caml_modify() and caml_initialize().
2903  The new implementations are less lenient than the old ones: now,
2904  the destination pointer of caml_modify() must point within the minor or
2905  major heaps, and the destination pointer of caml_initialize() must
2906  point within the major heap.
2907  (Xavier Leroy, from an experiment by Brian Nigito, with feedback
2908  from Yaron Minsky and Gerd Stolpmann)
2909
2910Internals:
2911- Moved debugger/envaux.ml to typing/envaux.ml to publish env_of_only_summary
2912  as part of compilerlibs, to be used on bin-annot files.
2913  (Fabrice Le Fessant)
2914- The test suite can now be run without installing OCaml first.
2915  (Damien Doligez)
2916
2917Bug fixes:
2918- PR#3236: Document the fact that queues are not thread-safe
2919  (Damien Doligez)
2920- PR#3468: (part 1) Sys_error documentation
2921  (Damien Doligez)
2922- PR#3679: Warning display problems
2923  (Fabrice Le Fessant)
2924- PR#3963: Graphics.wait_next_event in Win32 hangs if window closed
2925  (Damien Doligez)
2926- PR#4079: Queue.copy is now tail-recursive
2927  (patch by Christophe Papazian)
2928- PR#4138: Documentation for Unix.mkdir
2929  (Damien Doligez)
2930- PR#4469: emacs mode: caml-set-compile-command is annoying with ocamlbuild
2931  (Daniel Bünzli)
2932- PR#4485: Graphics: Keyboard events incorrectly delivered in native code
2933  (Damien Doligez, report by Sharvil Nanavati)
2934- PR#4502: ocamlbuild now reliably excludes the build-dir from hygiene check
2935  (Gabriel Scherer, report by Romain Bardou)
2936- PR#4762: ?? is not used at all, but registered as a lexer token
2937  (Alain Frisch)
2938- PR#4788: wrong error message when executable file is not found for backtrace
2939  (Damien Doligez, report by Claudio Sacerdoti Coen)
2940- PR#4812: otherlibs/unix: add extern int code_of_unix_error (value error);
2941  (Goswin von Berdelow)
2942- PR#4887: input_char after close_in crashes ocaml (msvc runtime)
2943  (Alain Frisch and Christoph Bauer, report by ygrek)
2944- PR#4994: ocaml-mode doesn't work with xemacs21
2945  (Damien Doligez, report by Stéphane Glondu)
2946- PR#5098: creating module values may lead to memory leaks
2947  (Alain Frisch, report by Milan Stanojević)
2948- PR#5102: ocamlbuild fails when using an unbound variable in rule dependency
2949  (Xavier Clerc, report by Daniel Bünzli)
2950* PR#5119: camlp4 now raises a specific exception when 'DELETE_RULE' fails,
2951  rather than raising 'Not_found'
2952  (ygrek)
2953- PR#5121: %( %) in Format module seems to be broken
2954  (Pierre Weis, first patch by Valentin Gatien-Baron, report by Khoo Yit Phang)
2955- PR#5178: document in INSTALL how to build a 32-bit version under Linux x86-64
2956  (Benjamin Monate)
2957- PR#5212: Improve ocamlbuild error messages of _tags parser
2958  (ygrek)
2959- PR#5240: register exception printers for Unix.Unix_error and Dynlink.Error
2960  (Jérémie Dimino)
2961- PR#5300: ocamlbuild: verbose parameter should implicitly set classic display
2962  (Xavier Clerc, report by Robert Jakob)
2963- PR#5327: (Windows) Unix.select blocks if same socket listed in first and
2964  third arguments
2965  (David Allsopp, displaying impressive MSDN skills)
2966- PR#5343: ocaml -rectypes is unsound wrt module subtyping (was still unsound)
2967  (Jacques Garrigue)
2968- PR#5350: missing return code checks in the runtime system
2969  (Xavier Leroy)
2970- PR#5468: ocamlbuild should preserve order of parametric tags
2971  (Wojciech Meyer, report by Dario Texeira)
2972- PR#5551: Avoid repeated lookups for missing cmi files
2973  (Alain Frisch)
2974- PR#5552: unrecognized gcc option -no-cpp-precomp
2975  (Damien Doligez, report by Markus Mottl)
2976* PR#5580: missed opportunities for constant propagation
2977  (Xavier Leroy and John Carr)
2978- PR#5611: avoid clashes betwen .cmo files and output files during linking
2979  (Wojciech Meyer)
2980- PR#5662: typo in md5.c
2981  (Olivier Andrieu)
2982- PR#5673: type equality in a polymorphic field
2983  (Jacques Garrigue, report by Jean-Louis Giavitto)
2984- PR#5674: Methods call are 2 times slower with 4.00 than with 3.12
2985  (Jacques Garrigue, Gabriel Scherer, report by Jean-Louis Giavitto)
2986- PR#5694: Exception raised by type checker
2987  (Jacques Garrigue, report by Markus Mottl)
2988- PR#5695: remove warnings on sparc code emitter
2989  (Fabrice Le Fessant)
2990- PR#5697: better location for warnings on statement expressions
2991  (Dan Bensen)
2992- PR#5698: remove harcoded limit of 200000 labels in emitaux.ml
2993  (Fabrice Le Fessant, report by Marcin Sawicki)
2994- PR#5702: bytecomp/bytelibrarian lib_sharedobjs was defined but never used
2995  (Hongbo Zhang, Fabrice Le Fessant)
2996- PR#5708: catch Failure"int_of_string" in ocamldebug
2997  (Fabrice Le Fessant, report by user 'schommer')
2998- PR#5712: (9) new option -bin-annot is not documented
2999  (Damien Doligez, report by Hendrik Tews)
3000- PR#5731: instruction scheduling forgot to account for destroyed registers
3001  (Xavier Leroy, Benedikt Meurer, reported by Jeffrey Scofield)
3002- PR#5734: improved Win32 implementation of Unix.gettimeofday
3003  (David Allsopp)
3004- PR#5735: %apply and %revapply not first class citizens
3005  (Fabrice Le Fessant, reported by Jun Furuse)
3006- PR#5738: first class module patterns not handled by ocamldep
3007  (Fabrice Le Fessant, Jacques Garrigue, reported by Hongbo Zhang)
3008- PR#5739: Printf.printf "%F" (-.nan) returns -nan
3009  (Xavier Leroy, David Allsopp, reported by Samuel Mimram)
3010- PR#5741: make pprintast.ml in compiler_libs
3011  (Alain Frisch, Hongbo Zhang)
3012- PR#5747: 'unused open' warning not given when compiling with -annot
3013  (Alain Frisch, reported by Valentin Gatien-Baron)
3014- PR#5752: missing dependencies at byte-code link with mlpack
3015  (Wojciech Meyer, Nicholas Lucaroni)
3016- PR#5763: ocamlbuild does not give correct flags when running menhir
3017  (Gabriel Scherer, reported by Philippe Veber)
3018- PR#5765: ocamllex doesn't preserve line directives
3019  (Damien Doligez, reported by Martin Jambon)
3020- PR#5770: Syntax error messages involving unclosed parens are sometimes
3021  incorrect
3022  (Michel Mauny)
3023- PR#5772: problem with marshaling of mutually-recursive functions
3024  (Jacques-Henri Jourdan, reported by Cédric Pasteur)
3025- PR#5775: several bug fixes for tools/pprintast.ml
3026  (Hongbo Zhang)
3027- PR#5784: -dclambda option is ignored
3028  (Pierre Chambart)
3029- PR#5785: misbehaviour with abstracted structural type used as GADT index
3030  (Jacques Garrigue, report by Jeremy Yallop)
3031- PR#5787: Bad behavior of 'Unused ...' warnings in the toplevel
3032  (Alain Frisch)
3033- PR#5793: integer marshalling is inconsistent between architectures
3034  (Xavier Clerc, report by Pierre-Marie Pédrot)
3035- PR#5798: add ARM VFPv2 support for Raspbian (ocamlopt)
3036  (Jeffrey Scofield and Anil Madhavapeddy, patch review by Benedikt Meurer)
3037- PR#5802: Avoiding "let" as a value name
3038  (Jacques Garrigue, report by Tiphaine Turpin)
3039- PR#5805: Assert failure with warning 34 on pre-processed file
3040  (Alain Frisch, report by Tiphaine Turpin)
3041- PR#5806: ensure that backtrace tests are always run (testsuite)
3042  (Xavier Clerc, report by user 'michi')
3043- PR#5809: Generating .cmt files takes a long time, in case of type error
3044  (Alain Frisch)
3045- PR#5810: error in switch printing when using -dclambda
3046  (Pierre Chambart)
3047- PR#5811: Untypeast produces singleton tuples for constructor patterns
3048  with only one argument
3049  (Tiphaine Turpin)
3050- PR#5813: GC not called when unmarshaling repeatedly in a tight loop (ocamlopt)
3051  (Xavier Leroy, report by David Waern)
3052- PR#5814: read_cmt -annot does not report internal references
3053  (Alain Frisch)
3054- PR#5815: Multiple exceptions in signatures gives an error
3055  (Leo White)
3056- PR#5816: read_cmt -annot does not work for partial .cmt files
3057  (Alain Frisch)
3058- PR#5819: segfault when using [with] on large recursive record (ocamlopt)
3059  (Xavier Leroy, Damien Doligez)
3060- PR#5821: Wrong record field is reported as duplicate
3061  (Alain Frisch, report by Martin Jambon)
3062- PR#5824: Generate more efficient code for immediate right shifts.
3063  (Pierre Chambart, review by Xavier Leroy)
3064- PR#5825: Add a toplevel primitive to use source file wrapped with the
3065  coresponding module
3066  (Grégoire Henry, Wojciech Meyer, caml-list discussion)
3067- PR#5833: README.win32 can leave the wrong flexlink in the path
3068  (Damien Doligez, report by William Smith)
3069- PR#5835: nonoptional labeled arguments can be passed with '?'
3070  (Jacques Garrigue, report by Elnatan Reisner)
3071- PR#5840: improved documentation for 'Unix.lseek'
3072  (Xavier Clerc, report by Matej Košík)
3073- PR#5848: Assertion failure in type checker
3074  (Jacques Garrigue, Alain Frisch, report by David Waern)
3075- PR#5858: Assert failure during typing of class
3076  (Jacques Garrigue, report by Julien Signoles)
3077- PR#5865: assert failure when reporting undefined field label
3078  (Jacques Garrigue, report by Anil Madhavapeddy)
3079- PR#5872: Performance: Buffer.add_char is not inlined
3080  (Gerd Stolpmann, Damien Doligez)
3081- PR#5876: Uncaught exception with a typing error
3082  (Alain Frisch, Gabriel Scherer, report by Julien Moutinho)
3083- PR#5877: multiple "open" can become expensive in memory
3084  (Fabrice Le Fessant and Alain Frisch)
3085- PR#5880: 'Genlex.make_lexer' documention mentions the wrong exception
3086  (Xavier Clerc, report by Virgile Prevosto)
3087- PR#5885: Incorrect rule for compiling C stubs when shared libraries are not
3088  supported.
3089  (Jérôme Vouillon)
3090- PR#5891: ocamlbuild: support rectypes tag for mlpack
3091  (Khoo Yit Phang)
3092- PR#5892: GADT exhaustiveness check is broken
3093  (Jacques Garrigue and Leo White)
3094- PR#5906: GADT exhaustiveness check is still broken
3095  (Jacques Garrigue, report by Sébastien Briais)
3096- PR#5907: Undetected cycle during typecheck causes exceptions
3097  (Jacques Garrigue, report by Pascal Zimmer)
3098- PR#5910: Fix code generation bug for "mod 1" on ARM.
3099  (Benedikt Meurer, report by user 'jteg68')
3100- PR#5911: Signature substitutions fail in submodules
3101  (Jacques Garrigue, report by Markus Mottl)
3102- PR#5912: add configure option -no-cfi (for OSX 10.6.x with XCode 4.0.2)
3103  (Damien Doligez against XCode versions, report by Thomas Gazagnaire)
3104- PR#5914: Functor breaks with an equivalent argument signature
3105  (Jacques Garrigue, report by Markus Mottl and Grégoire Henry)
3106- PR#5920, PR#5957: linking failure for big bytecodes on 32bit architectures
3107  (Benoît Vaugon and Chet Murthy, report by Jun Furuse and Sebastien Mondet)
3108- PR#5928: Missing space between words in manual page for ocamlmktop
3109  (Damien Doligez, report by Matej Košík)
3110- PR#5930: ocamldep leaks temporary preprocessing files
3111  (Gabriel Scherer, report by Valentin Gatien-Baron)
3112- PR#5933: Linking is slow when there are functions with large arities
3113  (Valentin Gatien-Baron, review by Gabriel Scherer)
3114- PR#5934: integer shift by negative amount (in otherlibs/num)
3115  (Xavier Leroy, report by John Regehr)
3116- PR#5944: Bad typing performances of big variant type declaration
3117  (Benoît Vaugon)
3118- PR#5945: Mix-up of Minor_heap_min and Minor_heap_max units
3119  (Benoît Vaugon)
3120- PR#5948: GADT with polymorphic variants bug
3121  (Jacques Garrigue, report by Leo White)
3122- PR#5953: Unix.system does not handle EINTR
3123  (Jérémie Dimino)
3124- PR#5965: disallow auto-reference to a recursive module in its definition
3125  (Alain Frisch, report by Arthur Windler via Gabriel Scherer)
3126- PR#5973: Format module incorrectly parses format string
3127  (Pierre Weis, report by Frédéric Bour)
3128- PR#5974: better documentation for Str.regexp
3129  (Damien Doligez, report by william)
3130- PR#5976: crash after recovering from two stack overflows (ocamlopt on MacOS X)
3131  (Xavier Leroy, report by Pierre Boutillier)
3132- PR#5977: Build failure on raspberry pi: "input_value: integer too large"
3133  (Alain Frisch, report by Sylvain Le Gall)
3134- PR#5981: Incompatibility check assumes abstracted types are injective
3135  (Jacques Garrigue, report by Jeremy Yallop)
3136- PR#5982: caml_leave_blocking section and errno corruption
3137  (Jérémie Dimino)
3138- PR#5985: Unexpected interaction between variance and GADTs
3139  (Jacques Garrigue, Jeremy Yallop and Leo White and Gabriel Scherer)
3140- PR#5988: missing from the documentation: -impl is a valid flag for ocamlopt
3141  (Damien Doligez, report by Vincent Bernardoff)
3142- PR#5989: Assumed inequalities involving private rows
3143  (Jacques Garrigue, report by Jeremy Yallop)
3144- PR#5992: Crash when pattern-matching lazy values modifies the scrutinee
3145  (Luc Maranget, Leo White)
3146- PR#5993: Variance of private type abbreviations not checked for modules
3147  (Jacques Garrigue)
3148- PR#5997: Non-compatibility assumed for concrete types with same constructor
3149  (Jacques Garrigue, report by Gabriel Scherer)
3150- PR#6004: Type information does not flow to "inherit" parameters
3151  (Jacques Garrigue, report by Alain Frisch)
3152- PR#6005: Type unsoundness with recursive modules
3153  (Jacques Garrigue, report by Jérémie Dimino and Josh Berdine)
3154- PR#6010: Big_int.extract_big_int gives wrong results on negative arguments
3155  (Xavier Leroy, report by Drake Wilson via Stéphane Glondu)
3156- PR#6024: Format syntax for printing @ is incompatible with 3.12.1
3157  (Damien Doligez, report by Boris Yakobowski)
3158- PR#6001: Reduce the memory used by compiling Camlp4
3159  (Hongbo Zhang and Gabriel Scherer, report by Henri Gouraud)
3160- PR#6031: Camomile problem with -with-frame-pointers
3161  (Fabrice Le Fessant, report by Anil Madhavapeddy)
3162- PR#6032: better Random.self_init under Windows
3163  (Alain Frisch, Xavier Leroy)
3164- PR#6033: Matching.inline_lazy_force needs eta-expansion (command-line flags)
3165  (Pierre Chambart, Xavier Leroy and Luc Maranget,
3166   regression report by Gabriel Scherer)
3167- PR#6046: testsuite picks up the wrong ocamlrun dlls
3168  (Anil Madhavapeddy)
3169- PR#6056: Using 'match' prevents generalization of values
3170  (Jacques Garrigue, report by Elnatan Reisner)
3171- PR#6058: 'ocamlbuild -use-ocamlfind -tag thread -package threads t.cma' fails
3172  (Gabriel Scherer, report by Hezekiah M. Carty)
3173- PR#6069: ocamldoc: lexing: empty token
3174  (Maxence Guesdon, Grégoire Henry, report by ygrek)
3175- PR#6072: configure does not handle FreeBSD current (i.e. 10) correctly
3176  (Damien Doligez, report by Prashanth Mundkur)
3177- PR#6074: Wrong error message for failing Condition.broadcast
3178  (Markus Mottl)
3179- PR#6084: Define caml_modify and caml_initialize as weak symbols to help
3180  with Netmulticore
3181  (Xavier Leroy, Gerd Stolpmann)
3182- PR#6090: Module constraint + private type seems broken in ocaml 4.01.0
3183  (Jacques Garrigue, report by Jacques-Pascal Deplaix)
3184- PR#6109: Typos in ocamlbuild error messages
3185  (Gabriel Kerneis)
3186- PR#6123: Assert failure when self escapes its class
3187  (Jacques Garrigue, report by whitequark)
3188- PR#6158: Fatal error using GADTs
3189  (Jacques Garrigue, report by Jeremy Yallop)
3190- PR#6163: Assert_failure using polymorphic variants in GADTs
3191  (Jacques Garrigue, report by Leo White)
3192- PR#6164: segmentation fault on Num.power_num of 0/1
3193  (Fabrice Le Fessant, report by Johannes Kanig)
3194- PR#6210: Camlp4 location error
3195  (Hongbo Zhang, report by Jun Furuse)
3196
3197Feature wishes:
3198- PR#5181: Merge common floating point constants in ocamlopt
3199  (Benedikt Meurer)
3200- PR#5243: improve the ocamlbuild API documentation in signatures.mli
3201  (Christophe Troestler)
3202- PR#5546: moving a function into an internal module slows down its use
3203  (Alain Frisch, report by Fabrice Le Fessant)
3204- PR#5597: add instruction trace option 't' to OCAMLRUNPARAM
3205  (Anil Madhavapeddy, Wojciech Meyer)
3206- PR#5676: IPv6 support under Windows
3207  (Jérôme Vouillon, review by Jonathan Protzenko)
3208- PR#5721: configure -with-frame-pointers for Linux perf profiling
3209  (Fabrice Le Fessant, test by Jérémie Dimino)
3210- PR#5722: toplevel: print full module path only for first record field
3211  (Jacques Garrigue, report by ygrek)
3212- PR#5762: Add primitives for fast access to bigarray dimensions
3213  (Pierre Chambart)
3214- PR#5769: Allow propagation of Sys.big_endian in native code
3215  (Pierre Chambart, stealth commit by Fabrice Le Fessant)
3216- PR#5771: Add primitives for reading 2, 4, 8 bytes in strings and bigarrays
3217  (Pierre Chambart)
3218- PR#5774: Add bswap primitives for amd64 and arm
3219  (Pierre Chambart, test by Alain Frisch)
3220- PR#5795: Generate sqrtsd opcode instead of external call to sqrt on amd64
3221  (Pierre Chambart)
3222- PR#5827: provide a dynamic command line parsing mechanism
3223  (Hongbo Zhang)
3224- PR#5832: patch to improve "wrong file naming" error messages
3225  (William Smith)
3226- PR#5864: Add a find operation to Set
3227  (François Berenger)
3228- PR#5886: Small changes to compile for Android
3229  (Jérôme Vouillon, review by Benedikt Meurer)
3230- PR#5902: -ppx based pre-processor executables accept arguments
3231  (Alain Frisch, report by Wojciech Meyer)
3232- PR#5986: Protect against marshaling 64-bit integers in bytecode
3233  (Xavier Leroy, report by Alain Frisch)
3234- PR#6049: support for OpenBSD/macppc platform
3235  (Anil Madhavapeddy, review by Benedikt Meurer)
3236- PR#6059: add -output-obj rules for ocamlbuild
3237  (Anil Madhavapeddy)
3238- PR#6060: ocamlbuild tags 'principal', 'strict_sequence' and 'short_paths'
3239  (Anil Madhavapeddy)
3240- ocamlbuild tag 'no_alias_deps'
3241  (Daniel Bünzli)
3242
3243Tools:
3244- OCamlbuild now features a bin_annot tag to generate .cmt files.
3245  (Jonathan Protzenko)
3246- OCamlbuild now features a strict_sequence tag to trigger the
3247  strict-sequence option.
3248  (Jonathan Protzenko)
3249- OCamlbuild now picks the non-core tools like ocamlfind and menhir from PATH
3250  (Wojciech Meyer)
3251- PR#5884: Misc minor fixes and cleanup for emacs mode
3252  (Stefan Monnier)
3253- PR#6030: Improve performance of -annot
3254  (Guillaume Melquiond, Alain Frisch)
3255
3256
3257OCaml 4.00.1 (5 Oct 2012):
3258--------------------------
3259
3260Bug fixes:
3261- PR#4019: better documentation of Str.matched_string
3262- PR#5111: ocamldoc, heading tags inside spans tags is illegal in html
3263- PR#5278: better error message when typing "make"
3264- PR#5468: ocamlbuild should preserve order of parametric tags
3265- PR#5563: harden Unix.select against file descriptors above FD_SETSIZE
3266- PR#5690: "ocamldoc ... -text README" raises exception
3267- PR#5700: crash with native-code stack backtraces under MacOS 10.8 x86-64
3268- PR#5707: AMD64 code generator: do not use r10 and r11 for parameter passing,
3269  as these registers can be destroyed by the dynamic loader
3270- PR#5712: some documentation problems
3271- PR#5715: configuring with -no-shared-libs breaks under cygwin
3272- PR#5718: false positive on 'unused constructor' warning
3273- PR#5719: ocamlyacc generates code that is not warning 33-compliant
3274- PR#5725: ocamldoc output of preformatted code
3275- PR#5727: emacs caml-mode indents shebang line in toplevel scripts
3276- PR#5729: tools/untypeast.ml creates unary Pexp_tuple
3277- PR#5731: instruction scheduling forgot to account for destroyed registers
3278- PR#5735: %apply and %revapply not first class citizens
3279- PR#5738: first class module patterns not handled by ocamldep
3280- PR#5742: missing bound checks in Array.sub
3281- PR#5744: ocamldoc error on "val virtual"
3282- PR#5757: GC compaction bug (crash)
3283- PR#5758: Compiler bug when matching on floats
3284- PR#5761: Incorrect bigarray custom block size
3285
3286
3287OCaml 4.00.0 (26 Jul 2012):
3288---------------------------
3289
3290(Changes that can break existing programs are marked with a "*")
3291
3292- The official name of the language is now OCaml.
3293
3294Language features:
3295- Added Generalized Algebraic Data Types (GADTs) to the language.
3296  See chapter "Language extensions" of the reference manual for documentation.
3297- It is now possible to omit type annotations when packing and unpacking
3298  first-class modules. The type-checker attempts to infer it from the context.
3299  Using the -principal option guarantees forward compatibility.
3300- New (module M) and (module M : S) syntax in patterns, for immediate
3301  unpacking of a first-class module.
3302
3303Compilers:
3304- Revised simplification of let-alias (PR#5205, PR#5288)
3305- Better reporting of compiler version mismatch in .cmi files
3306* Warning 28 is now enabled by default.
3307- New option -absname to use absolute paths in error messages
3308- Optimize away compile-time beta-redexes, e.g. (fun x y -> e) a b.
3309- Added option -bin-annot to dump the AST with type annotations.
3310- Added lots of new warnings about unused variables, opens, fields,
3311  constructors, etc.
3312* New meaning for warning 7: it is now triggered when a method is overridden
3313  with the "method" keyword.  Use "method!" to avoid the warning.
3314
3315Native-code compiler:
3316- Optimized handling of partially-applied functions (PR#5287)
3317- Small improvements in code generated for array bounds checks (PR#5345,
3318  PR#5360).
3319* New ARM backend (PR#5433):
3320    . Supports both Linux/EABI (armel) and Linux/EABI+VFPv3 (armhf).
3321    . Added support for the Thumb-2 instruction set with average code size
3322      savings of 28%.
3323    . Added support for position-independent code, natdynlink, profiling and
3324      exception backtraces.
3325- Generation of CFI information, and filename/line number debugging (with -g)
3326  annotations, enabling in particular precise stack backtraces with
3327  the gdb debugger. Currently supported for x86 32-bits and 64-bits only.
3328  (PR#5487)
3329- New tool: ocamloptp, the equivalent of ocamlcp for the native-code compiler.
3330
3331OCamldoc:
3332- PR#5645: ocamldoc doesn't handle module/type substitution in signatures
3333- PR#5544: improve HTML output (less formatting in html code)
3334- PR#5522: allow refering to record fields and variant constructors
3335- fix PR#5419 (error message in french)
3336- fix PR#5535 (no cross ref to class after dump+load)
3337* Use first class modules for custom generators, to be able to
3338  load various plugins incrementally adding features to the current
3339  generator
3340* PR#5507: Use Location.t structures for locations.
3341- fix: do not keep code when not told to keep code.
3342
3343Standard library:
3344- Added float functions "hypot" and "copysign" (PR#3806, PR#4752, PR#5246)
3345* Arg: options with empty doc strings are no longer included in the usage string
3346  (PR#5437)
3347- Array: faster implementations of "blit", "copy", "sub", "append" and "concat"
3348  (PR#2395, PR#2787, PR#4591)
3349* Hashtbl:
3350    . Statistically-better generic hash function based on Murmur 3 (PR#5225)
3351    . Fixed behavior of generic hash function w.r.t. -0.0 and NaN (PR#5222)
3352    . Added optional "random" parameter to Hashtbl.create to randomize
3353      collision patterns and improve security (PR#5572, CVE-2012-0839)
3354    . Added "randomize" function and "R" parameter to OCAMLRUNPARAM
3355      to turn randomization on by default (PR#5572, CVE-2012-0839)
3356    . Added new functorial interface "MakeSeeded" to support randomization
3357      with user-provided seeded hash functions.
3358    . Install new header <caml/hash.h> for C code.
3359- Filename: on-demand (lazy) initialization of the PRNG used by "temp_file".
3360- Marshal: marshalling of function values (flag Marshal.Closures) now
3361  also works for functions that come from dynamically-loaded modules (PR#5215)
3362- Random:
3363     . More random initialization (Random.self_init()), using /dev/urandom
3364       when available (e.g. Linux, FreeBSD, MacOS X, Solaris)
3365     * Faster implementation of Random.float (changes the generated sequences)
3366- Format strings for formatted input/output revised to correct PR#5380
3367    . Consistently treat %@ as a plain @ character
3368    . Consistently treat %% as a plain % character
3369- Scanf: width and precision for floating point numbers are now handled
3370- Scanf: new function "unescaped" (PR#3888)
3371- Set and Map: more efficient implementation of "filter" and "partition"
3372- String: new function "map" (PR#3888)
3373
3374Installation procedure:
3375- Compiler internals are now installed in `ocamlc -where`/compiler-libs.
3376  The files available there include the .cmi interfaces for all compiler
3377  modules, plus the following libraries:
3378      ocamlcommon.cma/.cmxa     modules common to ocamlc, ocamlopt, ocaml
3379      ocamlbytecomp.cma/.cmxa   modules for ocamlc and ocaml
3380      ocamloptcomp.cma/.cmxa    modules specific to ocamlopt
3381      ocamltoplevel.cma         modules specific to ocaml
3382   (PR#1804, PR#4653, frequently-asked feature).
3383* Some .cmi for toplevel internals that used to be installed in
3384  `ocamlc -where` are now to be found in  `ocamlc -where`/compiler-libs.
3385  Add "-I +compiler-libs" where needed.
3386* toplevellib.cma is no longer installed because subsumed by
3387  ocamlcommon.cma ocamlbytecomp.cma ocamltoplevel.cma
3388- Added a configuration option (-with-debug-runtime) to compile and install
3389  a debug version of the runtime system, and a compiler option
3390  (-runtime-variant) to select the debug runtime.
3391
3392Bug Fixes:
3393
3394- PR#1643: functions of the Lazy module whose named started with 'lazy_' have
3395  been deprecated, and new ones without the prefix added
3396- PR#3571: in Bigarrays, call msync() before unmapping to commit changes
3397- PR#4292: various documentation problems
3398- PR#4511, PR#4838: local modules remove polymorphism
3399* PR#4549: Filename.dirname is not handling multiple / on Unix
3400- PR#4688: (Windows) special floating-point values aren't converted to strings
3401  correctly
3402- PR#4697: Unix.putenv leaks memory on failure
3403- PR#4705: camlp4 does not allow to define types with `True or `False
3404- PR#4746: wrong detection of stack overflows in native code under Linux
3405- PR#4869: rare collisions between assembly labels for code and data
3406- PR#4880: "assert" constructs now show up in the exception stack backtrace
3407- PR#4892: Array.set could raise "out of bounds" before evaluating 3rd arg
3408- PR#4937: camlp4 incorrectly handles optional arguments if 'option' is
3409  redefined
3410- PR#5024: camlp4r now handles underscores in irrefutable pattern matching of
3411  records
3412- PR#5064, PR#5485: try to ensure that 4K words of stack are available
3413  before calling into C functions, raising a Stack_overflow exception
3414  otherwise.  This reduces (but does not eliminate) the risk of
3415  segmentation faults due to stack overflow in C code
3416- PR#5073: wrong location for 'Unbound record field label' error
3417- PR#5084: sub-sub-module building fails for native code compilation
3418- PR#5120: fix the output function of Camlp4.Debug.formatter
3419- PR#5131: compilation of custom runtime with g++ generates lots of warnings
3420- PR#5137: caml-types-explore does not work
3421- PR#5159: better documentation of type Lexing.position
3422- PR#5171: Map.join does more comparisons than needed
3423- PR#5176: emacs mode: stack overflow in regexp matcher
3424- PR#5179: port OCaml to mingw-w64
3425- PR#5211: updated Genlex documentation to state that camlp4 is mandatory for
3426  'parser' keyword and associated notation
3427- PR#5214: ocamlfind plugin invokes 'cut' utility
3428- PR#5218: use $(MAKE) instead of "make" in Makefiles
3429- PR#5224: confusing error message in non-regular type definition
3430- PR#5231: camlp4: fix parsing of <:str_item< type t = $x$ >>
3431- PR#5233: finaliser on weak array gives dangling pointers (crash)
3432- PR#5238, PR#5277: Sys_error when getting error location
3433- PR#5261, PR#5497: Ocaml source-code examples are not "copy-paste-able"
3434* PR#5279: executable name is not initialized properly in caml_startup_code
3435- PR#5290: added hash functions for channels, nats, mutexes, conditions
3436- PR#5291: undetected loop in class initialization
3437- PR#5295: OS threads: problem with caml_c_thread_unregister()
3438- PR#5301: camlp4r and exception equal to another one with parameters
3439- PR#5305: prevent ocamlbuild from complaining about links to _build/
3440- PR#5306: comparing to Thread.self() raises exception at runtime
3441- PR#5309: Queue.add is not thread/signal safe
3442- PR#5310: Ratio.create_ratio/create_normalized_ratio have misleading names
3443- PR#5311: better message for warning 23
3444* PR#5312: command-line arguments @reponsefile auto-expansion feature
3445  removed from the Windows OCaml runtime, to avoid conflicts with "-w @..."
3446- PR#5313: ocamlopt -g misses optimizations
3447- PR#5214: ocamlfind plugin invokes 'cut' utility
3448- PR#5316: objinfo now shows ccopts/ccobjs/force_link when applicable
3449- PR#5318: segfault on stack overflow when reading marshaled data
3450- PR#5319: %r11 clobbered by Lswitch in Windows AMD64 native-code compilation
3451- PR#5322: type abbreviations expanding to a universal type variable
3452- PR#5328: under Windows, Unix.select leaves sockets in non-blocking mode
3453- PR#5330: thread tag with '.top' and '.inferred.mli' targets
3454- PR#5331: ocamlmktop is not always a shell script
3455- PR#5335: Unix.environment segfaults after a call to clearenv
3456- PR#5338: sanitize.sh has windows style end-of-lines (mingw)
3457- PR#5344: some predefined exceptions need special printing
3458- PR#5349: Hashtbl.replace uses new key instead of reusing old key
3459- PR#5356: ocamlbuild handling of 'predicates' for ocamlfind
3460- PR#5364: wrong compilation of "((val m : SIG1) : SIG2)"
3461- PR#5370: ocamldep omits filename in syntax error message
3462- PR#5374: camlp4 creates wrong location for type definitions
3463- PR#5380: strange sscanf input segfault
3464- PR#5382: EOPNOTSUPP and ENOTSUPP different on exotic platforms
3465- PR#5383: build failure in Win32/MSVC
3466- PR#5387: camlp4: str_item and other syntactic elements with Nils are
3467  not very usable
3468- PR#5389: compaction sometimes leaves a very large heap
3469- PR#5393: fails to build from source on GNU/kFreeBSD because of -R link option
3470- PR#5394: documentation for -dtypes is missing in manpage
3471- PR#5397: Filename.temp_dir_name should be mutable
3472- PR#5410: fix printing of class application with Camlp4
3473- PR#5416: (Windows) Unix.(set|clear)_close_on_exec now preserves blocking mode
3474- PR#5435: ocamlbuild does not find .opt executables on Windows
3475- PR#5436: update object ids on unmarshaling
3476- PR#5442: camlp4: quotation issue with strings
3477- PR#5453: configure doesn't find X11 under Ubuntu/MultiarchSpec
3478- PR#5461: Double linking of bytecode modules
3479- PR#5463: Bigarray.*.map_file fail if empty array is requested
3480- PR#5465: increase stack size of ocamlopt.opt for windows
3481- PR#5469: private record type generated by functor loses abbreviation
3482- PR#5475: Wrapper script for interpreted LablTk wrongly handles command line
3483  parameters
3484- PR#5476: bug in native code compilation of let rec on float arrays
3485- PR#5477: use pkg-config to configure graphics on linux
3486- PR#5481: update camlp4 magic numbers
3487- PR#5482: remove bashism in test suite scripts
3488- PR#5495: camlp4o dies on infix definition (or)
3489- PR#5498: Unification with an empty object only checks the absence of
3490  the first method
3491- PR#5503: error when ocamlbuild is passed an absolute path as build directory
3492- PR#5509: misclassification of statically-allocated empty array that
3493  falls exactly at beginning of an otherwise unused data page.
3494- PR#5510: ocamldep has duplicate -ml{,i}-synonym options
3495- PR#5511: in Bigarray.reshape, unwarranted limitation on new array dimensions.
3496- PR#5513: Int64.div causes floating point exception (ocamlopt, x86)
3497- PR#5516: in Bigarray C stubs, use C99 flexible array types if possible
3498- PR#5518: segfault with lazy empty array
3499- PR#5531: Allow ocamlbuild to add ocamldoc flags through -docflag
3500  and -docflags switches
3501- PR#5538: combining -i and -annot in ocamlc
3502- PR#5543: in Bigarray.map_file, try to avoid using lseek() when growing file
3503- PR#5648: (probably fixed) test failures in tests/lib-threads
3504- PR#5551: repeated calls to find_in_path degrade performance
3505- PR#5552: Mac OS X: unrecognized gcc option "-no-cpp-precomp"
3506- PR#5555: add Hashtbl.reset to resize the bucket table to its initial size
3507- PR#5560: incompatible type for tuple pattern with -principal
3508- PR#5575: Random states are not marshallable across architectures
3509- PR#5579: camlp4: when a plugin is loaded in the toplevel,
3510  Token.Filter.define_filter has no effect before the first syntax error
3511- PR#5585: typo: "explicitely"
3512- PR#5587: documentation: "allows to" is not correct English
3513- PR#5593: remove C file when -output-obj fails
3514- PR#5597: register names for instrtrace primitives in embedded bytecode
3515- PR#5598: add backslash-space support in strings in ocamllex
3516- PR#5603: wrong .file debug info generated by ocamlopt -g
3517- PR#5604: fix permissions of files created by ocamlbuild itself
3518- PR#5610: new unmarshaler (from PR#5318) fails to freshen object identifiers
3519- PR#5614: add missing -linkall flag when compiling ocamldoc.opt
3520- PR#5616: move ocamlbuild documentation to the reference manual
3521- PR#5619: Uncaught CType.Unify exception in the compiler
3522- PR#5620: invalid printing of type manifest (camlp4 revised syntax)
3523- PR#5637: invalid printing of anonymous type parameters (camlp4 revised syntax)
3524- PR#5643: issues with .cfi and .loc directives generated by ocamlopt -g
3525- PR#5644: Stream.count broken when used with Sapp or Slazy nodes
3526- PR#5647: Cannot use install_printer in debugger
3527- PR#5651: printer for abstract data type (camlp4 revised syntax)
3528- PR#5654: self pattern variable location tweak
3529- PR#5655: ocamlbuild doesn't pass cflags when building C stubs
3530- PR#5657: wrong error location for abbreviated record fields
3531- PR#5659: ocamlmklib -L option breaks with MSVC
3532- PR#5661: fixes for the test suite
3533- PR#5668: Camlp4 produces invalid syntax for "let _ = ..."
3534- PR#5671: initialization of compare_ext field in caml_final_custom_operations()
3535- PR#5677: do not use "value" as identifier (genprintval.ml)
3536- PR#5687: dynlink broken when used from "output-obj" main program (bytecode)
3537- problem with printing of string literals in camlp4 (reported on caml-list)
3538- emacs mode: colorization of comments and strings now works correctly
3539- problem with forall and method (reported on caml-list on 2011-07-26)
3540- crash when using OCAMLRUNPARAM=a=X with invalid X (reported in private)
3541
3542Feature wishes:
3543- PR#352: new option "-stdin" to make ocaml read stdin as a script
3544- PR#1164: better error message when mixing -a and .cmxa
3545- PR#1284: documentation: remove restriction on mixed streams
3546- PR#1496: allow configuring LIBDIR, BINDIR, and MANDIR relative to $(PREFIX)
3547- PR#1835: add Digest.from_hex
3548- PR#1898: toplevel: add option to suppress continuation prompts
3549- PR#4278: configure: option to disable "graph" library
3550- PR#4444: new String.trim function, removing leading and trailing whistespace
3551- PR#4549: make Filename.dirname/basename POSIX compliant
3552- PR#4830: add option -v to expunge.ml
3553- PR#4898: new Sys.big_endian boolean for machine endianness
3554- PR#4963, PR#5467: no extern "C" into ocaml C-stub headers
3555- PR#5199: tests are run only for bytecode if either native support is missing,
3556  or a non-empty value is set to "BYTECODE_ONLY" Makefile variable
3557- PR#5215: marshalling of dynlinked closure
3558- PR#5236: new '%revapply' primitive with the semantics 'revapply x f = f x',
3559    and '%apply' with semantics 'apply f x = f x'.
3560- PR#5255: natdynlink detection on powerpc, hurd, sparc
3561- PR#5295: OS threads: problem with caml_c_thread_unregister()
3562- PR#5297: compiler now checks existence of builtin primitives
3563- PR#5329: (Windows) more efficient Unix.select if all fd's are sockets
3564- PR#5357: warning for useless open statements
3565- PR#5358: first class modules don't allow "with type" declarations for types
3566  in sub-modules
3567- PR#5385: configure: emit a warning when MACOSX_DEPLOYMENT_TARGET is set
3568- PR#5396: ocamldep: add options -sort, -all, and -one-line
3569- PR#5397: Filename.temp_dir_name should be mutable
3570- PR#5403: give better error message when emacs is not found in PATH
3571- PR#5411: new directive for the toplevel: #load_rec
3572- PR#5420: Unix.openfile share mode (Windows)
3573- PR#5421: Unix: do not leak fds in various open_proc* functions
3574- PR#5434: implement Unix.times in win32unix (partially)
3575- PR#5438: new warnings for unused declarations
3576- PR#5439: upgrade config.guess and config.sub
3577- PR#5445 and others: better printing of types with user-provided names
3578- PR#5454: Digest.compare is missing and md5 doc update
3579- PR#5455: .emacs instructions, add lines to recognize ocaml scripts
3580- PR#5456: pa_macro: replace __LOCATION__ after macro expansion; add LOCATION_OF
3581- PR#5461: bytecode: emit warning when linking two modules with the same name
3582- PR#5478: ocamlopt assumes ar command exists
3583- PR#5479: Num.num_of_string may raise an exception, not reflected in the
3584  documentation.
3585- PR#5501: increase IO_BUFFER_SIZE to 64KiB
3586- PR#5532: improve error message when bytecode file is wrong
3587- PR#5555: add function Hashtbl.reset to resize the bucket table to
3588  its initial size.
3589- PR#5586: increase UNIX_BUFFER_SIZE to 64KiB
3590- PR#5597: register names for instrtrace primitives in embedded bytecode
3591- PR#5599: Add warn() tag in ocamlbuild to control -w compiler switch
3592- PR#5628: add #remove_directory and Topdirs.remove_directory to remove
3593  a directory from the load path
3594- PR#5636: in system threads library, issue with linking of pthread_atfork
3595- PR#5666: C includes don't provide a revision number
3596- ocamldebug: ability to inspect values that contain code pointers
3597- ocamldebug: new 'environment' directive to set environment variables
3598  for debuggee
3599- configure: add -no-camlp4 option
3600
3601Shedding weight:
3602* Removed the obsolete native-code generators for Alpha, HPPA, IA64 and MIPS.
3603* The "DBM" library (interface with Unix DBM key-value stores) is no
3604  longer part of this distribution.  It now lives its own life at
3605  https://forge.ocamlcore.org/projects/camldbm/
3606* The "OCamlWin" toplevel user interface for MS Windows is no longer
3607  part of this distribution.  It now lives its own life at
3608  https://forge.ocamlcore.org/projects/ocamltopwin/
3609
3610Other changes:
3611- Copy VERSION file to library directory when installing.
3612
3613
3614OCaml 3.12.1 (4 Jul 2011):
3615--------------------------
3616
3617Bug fixes:
3618- PR#4345, PR#4767: problems with camlp4 printing of float values
3619- PR#4380: ocamlbuild should not use tput on windows
3620- PR#4487, PR#5164: multiple 'module type of' are incompatible
3621- PR#4552: ocamlbuild does not create symlinks when using '.itarget' file
3622- PR#4673, PR#5144: camlp4 fails on object copy syntax
3623- PR#4702: system threads: cleanup tick thread at exit
3624- PR#4732: camlp4 rejects polymorphic variants using keywords from macros
3625- PR#4778: Win32/MSVC port: rare syntax error in generated MASM assembly file
3626- PR#4794, PR#4959: call annotations not generated by ocamlopt
3627- PR#4820: revised syntax pretty printer crashes with 'Stack_overflow'
3628- PR#4928: wrong printing of classes and class types by camlp4
3629- PR#4939: camlp4 rejects patterns of the '?x:_' form
3630- PR#4967: ocamlbuild passes wrong switches to ocamldep through menhir
3631- PR#4972: mkcamlp4 does not include 'dynlink.cma'
3632- PR#5039: ocamlbuild should use '-linkpkg' only when linking programs
3633- PR#5066: ocamldoc: add -charset option used in html generator
3634- PR#5069: fcntl() in caml_sys_open may block, do it within blocking section
3635- PR#5071, PR#5129, PR#5134: inconsistencies between camlp4 and camlp4* binaries
3636- PR#5080, PR#5104: regression in type constructor handling by camlp4
3637- PR#5090: bad interaction between toplevel and camlp4
3638- PR#5095: ocamlbuild ignores some tags when building bytecode objects
3639- PR#5100: ocamlbuild always rebuilds a 'cmxs' file
3640- PR#5103: build and install objinfo when building with ocamlbuild
3641- PR#5109: crash when a parser calls a lexer that calls another parser
3642- PR#5110: invalid module name when using optional argument
3643- PR#5115: bytecode executables produced by msvc64 port crash on 32-bit versions
3644- PR#5117: bigarray: wrong function name without HAS_MMAP; missing include
3645- PR#5118: Camlp4o and integer literals
3646- PR#5122: camlp4 rejects lowercase identifiers for module types
3647- PR#5123: shift_right_big_int returns a wrong zero
3648- PR#5124: substitution inside a signature leads to odd printing
3649- PR#5128: typo in 'Camlp4ListComprehension' syntax extension
3650- PR#5136: obsolete function used in emacs mode
3651- PR#5145: ocamldoc: missing html escapes
3652- PR#5146: problem with spaces in multi-line string constants
3653- PR#5149: (partial) various documentation problems
3654- PR#5156: rare compiler crash with objects
3655- PR#5165: ocamlbuild does not pass '-thread' option to ocamlfind
3656- PR#5167: camlp4r loops when printing package type
3657- PR#5172: camlp4 support for 'module type of' construct
3658- PR#5175: in bigarray accesses, make sure bigarray expr is evaluated only once
3659- PR#5177: Gc.compact implies Gc.full_major
3660- PR#5182: use bytecode version of ocamldoc to generate man pages
3661- PR#5184: under Windows, alignment issue with bigarrays mapped from files
3662- PR#5188: double-free corruption in bytecode system threads
3663- PR#5192: mismatch between words and bytes in interpreting max_young_wosize
3664- PR#5202: error in documentation of atan2
3665- PR#5209: natdynlink incorrectly detected on BSD systems
3666- PR#5213: ocamlbuild should pass '-rectypes' to ocamldoc when needed
3667- PR#5217: ocamlfind plugin should add '-linkpkg' for toplevel
3668- PR#5228: document the exceptions raised by functions in 'Filename'
3669- PR#5229: typo in build script ('TAG_LINE' vs 'TAGLINE')
3670- PR#5230: error in documentation of Scanf.Scanning.open_in
3671- PR#5234: option -shared reverses order of -cclib options
3672- PR#5237: incorrect .size directives generated for x86-32 and x86-64
3673- PR#5244: String.compare uses polymorphic compare_val (regression of PR#4194)
3674- PR#5248: regression introduced while fixing PR#5118
3675- PR#5252: typo in docs
3676- PR#5258: win32unix: unix fd leak under windows
3677- PR#5269: (tentative fix) Wrong ext_ref entries in .annot files
3678- PR#5272: caml.el doesn't recognize downto as a keyword
3679- PR#5276: issue with ocamlc -pack and recursively-packed modules
3680- PR#5280: alignment constraints incorrectly autodetected on MIPS 32
3681- PR#5281: typo in error message
3682- PR#5308: unused variables not detected in "include (struct .. end)"
3683- camlp4 revised syntax printing bug in the toplevel (reported on caml-list)
3684- configure: do not define _WIN32 under cygwin
3685- Hardened generic comparison in the case where two custom blocks
3686  are compared and have different sets of custom operations.
3687- Hardened comparison between bigarrays in the case where the two
3688  bigarrays have different kinds.
3689- Fixed wrong autodetection of expm1() and log1p().
3690- don't add .exe suffix when installing the ocamlmktop shell script
3691- ocamldoc: minor fixes related to the display of ocamldoc options
3692- fixed bug with huge values in OCAMLRUNPARAM
3693- mismatch between declaration and definition of caml_major_collection_slice
3694
3695Feature wishes:
3696- PR#4992: added '-ml-synonym' and '-mli-synonym' options to ocamldep
3697- PR#5065: added '-ocamldoc' option to ocamlbuild
3698- PR#5139: added possibility to add options to ocamlbuild
3699- PR#5158: added access to current camlp4 parsers and printers
3700- PR#5180: improved instruction selection for float operations on amd64
3701- stdlib: added a 'usage_string' function to Arg
3702- allow with constraints to add a type equation to a datatype definition
3703- ocamldoc: allow to merge '@before' tags like other ones
3704- ocamlbuild: allow dependency on file "_oasis"
3705
3706Other changes:
3707- Changed default minor heap size from 32k to 256k words.
3708- Added new operation 'compare_ext' to custom blocks, called when
3709  comparing a custom block value with an unboxed integer.
3710
3711
3712Objective Caml 3.12.0 (2 Aug 2010):
3713-----------------------------------
3714
3715(Changes that can break existing programs are marked with a "*"  )
3716
3717Language features:
3718- Shorthand notation for records: in expressions and patterns,
3719    { lbl } stands for { lbl = lbl } and { M.lbl } for { M.lbl = lbl }
3720- Record patterns of the form { lbl = pat; _ } to mark that not all
3721  labels are listed, purposefully.  (See new warning below.)
3722- Explicit naming of a generic type; in an expression
3723  "fun ... (type t) ... -> e", the type t is considered abstract in its
3724  scope (the arguments that follow it and the body of the function),
3725  and then replaced by a fresh type variable. In particular, the type
3726  t can be used in contexts where a type variable is not allowed
3727  (e.g. for defining an exception in a local module).
3728- Explicit polymorphic types and polymorphic recursion. In let
3729  definitions, one can write an explicit polymorphic type just
3730  immediately the function name; the polymorphism will be enforced,
3731  and recursive calls may use the polymorphism.
3732  The syntax is the same as for polymorphic methods:
3733    "let [rec] <ident> : 'a1 ... 'an. <typexp> = ..."
3734- First-class packages modules.
3735  New kind of type expression, for packaged modules: (module PT).
3736  New kind of expression, to pack a module as a first-class value:
3737    (module MODEXPR : PT).
3738  New kind of module expression, to unpack a first-class value as a module:
3739    (val EXPR : PT).
3740  PT is a package type of the form "S" or
3741  "S with type t1 = ... and ... and type tn = ..." (S refers to a module type).
3742- Local opening of modules in a subexpression.
3743  Syntax: "let open M in e", or "M.(e)"
3744- In class definitions, method and instance variable override can now
3745  be made explicit, by writing "method!", "val!" or "inherit!" in place of
3746  "method", "val" and "inherit". It is an error to override an
3747  undefined member (or to use overriding inheritance when nothing get
3748  overridden). Additionally, these constructs disactivate respectively
3749  warnings 7 (method override, code 'M') and 13 (instance variable
3750  override, code 'V'). Note that, by default, warning 7 is inactive
3751  and warning 13 is active.
3752- "Destructive" substitution in signatures.
3753  By writing "<signature> with type t := <typeconstr>" and
3754  "<signature> with module M := <module-path>" one replaces "t" and "M"
3755  inside the signature, removing their respective fields. Among other
3756  uses, this allows to merge two signatures containing identically
3757  named fields.
3758* While fixing PR#4824, also corrected a gaping hole in the type checker,
3759  which allowed instantiating separately object parameters and instance
3760  variables in an interface. This hole was here since the beginning of
3761  ocaml, and as a result many programs using object inheritance in a non
3762  trivial way will need to be corrected. You can look at lablgtk2 for an
3763  example.
3764
3765Compilers and toplevel:
3766- Warnings are now numbered and can be switched on and off individually.
3767  The old system with letters referring to sets of warnings is still
3768  supported.
3769- New warnings:
3770  + 9 (code 'R') to signal record patterns without "; _" where
3771    some labels of the record type are not listed in the pattern.
3772  + 28 when giving a wildcard argument to a constant constructor in
3773    a pattern-matching.
3774  + 29 when an end-of-line appears unescaped in a string constant.
3775  + 30 when the same constructor or record field is defined twice in
3776    mutually-recursive type definitions.
3777* The semantics of warning 7 (code 'M', method override) have changed
3778  (it now detects all overrides, not just repeated definitions inside
3779  the same class body), and it is now inactive by default.
3780- Better error report in case of unbound qualified identifier: if the module
3781  is unbound this error is reported in the first place.
3782- Added option '-strict-sequence' to force left hand part of sequence to have
3783  type unit.
3784- Added option '-no-app-funct' to turn applicative functors off.
3785  This option can help working around mysterious type incompatibilities
3786  caused by the incomplete comparison of applicative paths F(X).t.
3787
3788Native-code compiler:
3789- AMD64: shorter and slightly more efficient code generated for
3790  float comparisons.
3791
3792Standard library:
3793- Format: new function ikfprintf analoguous to ifprintf with a continuation
3794  argument.
3795* PR#4210, #4245: stricter range checking in string->integer conversion
3796  functions (int_of_string, Int32.of_string, Int64.of_string,
3797  Nativeint.of_string).  The decimal string corresponding to
3798  max_int + 1 is no longer accepted.
3799- Scanf: to prevent confusion when mixing Scanf scanning functions and direct
3800  low level input, value Scanf.stdin has been added.
3801* Random: changed the algorithm to produce better randomness.  Now passes the
3802  DieHard tests.
3803- Map: implement functions from Set that make sense for Map.
3804
3805Other libraries:
3806* Str: letters that constitute a word now include digits 0-9 and
3807  underscore _.  This changes the interpretation of '\b' (word boundary)
3808  in regexps, but is more consistent with other regexp libraries. (PR#4874).
3809
3810Ocamlbuild:
3811- Add support for native dynlink.
3812
3813New tool:
3814- ocamlobjinfo: displays various information, esp. dependencies, for
3815  compiled OCaml files (.cmi, .cmo, .cma, .cmx, .cmxa, .cmxs, and bytecode
3816  executables).  Extends and makes more official the old objinfo tool
3817  that was installed by some OCaml packages.
3818
3819All tools:
3820- PR#4857: add a -vnum option to display the version number and nothing else
3821
3822Bug Fixes:
3823- PR#4012: Map.map and Map.mapi do not conform to specification
3824- PR#4478: better error messages for type definition mismatches
3825- PR#4683: labltk script uses fixed path on windows
3826- PR#4742: finalisation function raising an exception blocks other finalisations
3827- PR#4775: compiler crash on crazy types (temporary fix)
3828- PR#4824: narrowing the type of class parameters with a module specification
3829- PR#4862: relaxed value restriction and records
3830- PR#4884: optional arguments do not work when Some is redefined
3831- PR#4964: parenthesized names for infix functions in annot files
3832- PR#4970: better error message for instance variables
3833- PR#4975: spelling mistakes
3834- PR#4988: contravariance lost with ocamlc -i
3835- PR#5004: problem in Buffer.add_channel with very large lengths.
3836- PR#5008: on AMD64/MSVC port, rare float corruption during GC.
3837- PR#5018: wrong exception raised by Dynlink.loadfile.
3838- PR#5057: fatal typing error with local module + functor + polymorphic variant
3839- Wrong type for Obj.add_offset.
3840- Small problem with representation of Int32, Int64, and Nativeint constants.
3841- Use RTLD_LOCAL for native dynlink in private mode.
3842
3843Objective Caml 3.11.2 (20 Jan 2010):
3844------------------------------------
3845
3846Bug fixes:
3847- PR#4151: better documentation for min and max w.r.t. NaN
3848- PR#4421: ocamlbuild uses wrong compiler for C files
3849- PR#4710, PR#4720: ocamlbuild does not use properly configuration information
3850- PR#4750: under some Windows installations, high start-up times for Unix lib
3851- PR#4777: problem with scanf and CRLF
3852- PR#4783: ocamlmklib problem under Windows
3853- PR#4810: BSD problem with socket addresses, e.g. in Unix.getnameinfo
3854- PR#4813: issue with parsing of float literals by the GNU assembler
3855- PR#4816: problem with modules and private types
3856- PR#4818: missed opportunity for type-based optimization of bigarray accesses
3857- PR#4821: check for duplicate method names in classes
3858- PR#4823: build problem on Mac OS X
3859- PR#4836: spurious errors raised by Unix.single_write under Windows
3860- PR#4841, PR#4860, PR#4930: problem with ocamlopt -output-obj under Mac OS X
3861- PR#4847: C compiler error with ocamlc -output-obj under Win64
3862- PR#4856: ocamlbuild uses ocamlrun to execute a native plugin
3863- PR#4867, PR#4760: ocamlopt -shared fails on Mac OS X 64bit
3864- PR#4873: ocamlbuild ignores "thread" tag when building a custom toplevel
3865- PR#4890: ocamlbuild tries to use native plugin on bytecode-only arch
3866- PR#4896: ocamlbuild should always pass -I to tools for external libraries
3867- PR#4900: small bug triggering automatic compaction even if max_overhead = 1M
3868- PR#4902: bug in %.0F printf format
3869- PR#4910: problem with format concatenation
3870- PR#4922: ocamlbuild recompiles too many files
3871- PR#4923: missing \xff for scanf %S
3872- PR#4933: functors not handling private types correctly
3873- PR#4940: problem with end-of-line in DOS text mode, tentative fix
3874- PR#4953: problem compiling bytecode interpreter on ARM in Thumb mode.
3875- PR#4955: compiler crash when typing recursive type expression with constraint
3876- Module Printf: the simple conversion %F (without width indication) was not
3877           treated properly.
3878- Makefile: problem with cygwin, flexdll, and symbolic links
3879- Various build problems with ocamlbuild under Windows with msvc
3880
3881Feature wishes:
3882- PR#9: (tentative implementation) make ocamldebug use #linenum annotations
3883- PR#123, PR#4477: custom exception printers
3884- PR#3456: Obj.double_field and Obj.set_double_field functions
3885- PR#4003: destination directory can be given to Filename.[open_]temp_file
3886- PR#4647: Buffer.blit function
3887- PR#4685: access to Filename.dir_sep
3888- PR#4703: support for debugging embedded applications
3889- PR#4723: "clear_rules" function to empty the set of ocamlbuild rules
3890- PR#4921: configure option to help cross-compilers
3891
3892Objective Caml 3.11.1 (12 Jun 2009):
3893------------------------------------
3894
3895Bug fixes:
3896- PR#4095: ocamldebug: strange behaviour of control-C
3897- PR#4403: ocamldebug: improved handling of packed modules
3898- PR#4650: Str.regexp_case_fold mis-handling complemented character sets [^a]
3899- PR#4660: Scanf.format_from_string: handling of double quote
3900- PR#4666: Unix.exec* failure in multithread programs under MacOS X and FreeBSD
3901- PR#4667: debugger out of sync with dynlink changes
3902- PR#4678: random "out of memory" error with systhreads
3903- PR#4690: issue with dynamic loading under MacOS 10.5
3904- PR#4692: wrong error message with options -i and -pack passed to ocamlc
3905- PR#4699: in otherlibs/dbm, fixed construction of dlldbm.so.
3906- PR#4704: error in caml_modify_generational_global_root()
3907- PR#4708: (ocamldoc) improved printing of infix identifiers such as "lor".
3908- PR#4722: typo in configure script
3909- PR#4729: documented the fact that PF_INET6 is not available on all platforms
3910- PR#4730: incorrect typing involving abbreviation "type 'a t = 'a"
3911- PR#4731: incorrect quoting of arguments passed to the assembler on x86-64
3912- PR#4735: Unix.LargeFile.fstat cannot report size over 32bits on Win32
3913- PR#4740: guard against possible processor error in
3914           {Int32,Int64,Nativeint}.{div,rem}
3915- PR#4745: type inference wrongly produced non-generalizable type variables.
3916- PR#4749: better pipe size for win32unix
3917- PR#4756: printf: no error reported for wrong format '%_s'
3918- PR#4758: scanf: handling of \<newline> by format '%S'
3919- PR#4766: incorrect simplification of some type abbreviations.
3920- PR#4768: printf: %F does not respect width and precision specifications
3921- PR#4769: Format.bprintf fails to flush
3922- PR#4775: fatal error Ctype.Unify during module type-checking (temporary fix)
3923- PR#4776: bad interaction between exceptions and classes
3924- PR#4780: labltk build problem under Windows.
3925- PR#4790: under Windows, map ERROR_NO_DATA Win32 error to EPIPE Unix error.
3926- PR#4792: bug in Big_int.big_int_of_int64 on 32-bit platforms.
3927- PR#4796: ocamlyacc: missing NUL termination of string
3928- PR#4804: bug in Big_int.int64_of_big_int on 32-bit platforms.
3929- PR#4805: improving compatibility with the clang C compiler
3930- PR#4809: issue with Unix.create_process under Win32
3931- PR#4814: ocamlbrowser: crash when editing comments
3932- PR#4816: module abbreviations remove 'private' type restrictions
3933- PR#4817: Object type gives error "Unbound type parameter .."
3934- Module Parsing: improved computation of locations when an ocamlyacc rule
3935                  starts with an empty nonterminal
3936- Type-checker: fixed wrong variance computation for private types
3937- x86-32 code generator, MSVC port: wrong "fld" instruction generated.
3938- ocamlbuild: incorrectly using the compile-time value of $OCAMLLIB
3939- Makefile problem when configured with -no-shared-libs
3940- ocamldoc: use dynamic loading in native code
3941
3942Other changes:
3943- Improved wording of various error messages
3944  (contributed by Jonathan Davies, Citrix).
3945- Support for 64-bit mode in Solaris/x86 (PR#4670).
3946
3947
3948Objective Caml 3.11.0 (03 Dec 2008):
3949------------------------------------
3950
3951(Changes that can break existing programs are marked with a "*"  )
3952
3953Language features:
3954- Addition of lazy patterns: "lazy <pat>" matches suspensions whose values,
3955  after forcing, match the pattern <pat>.
3956- Introduction of private abbreviation types "type t = private <type-expr>",
3957  for abstracting the actual manifest type in type abbreviations.
3958- Subtyping is now allowed between a private abbreviation and its definition,
3959  and between a polymorphic method and its monomorphic instance.
3960
3961Compilers:
3962- The file name for a compilation unit should correspond to a valid
3963  identifier (Otherwise dynamic linking and other things can fail, and
3964  a warning is emitted.)
3965* Revised -output-obj: the output name must now be provided; its
3966  extension must be one of .o/.obj, .so/.dll, or .c for the
3967  bytecode compiler. The compilers can now produce a shared library
3968  (with all the needed -ccopts/-ccobjs options) directly.
3969- -dtypes renamed to -annot, records (in .annot files) which function calls
3970  are tail calls.
3971- All compiler error messages now include a file name and location, for
3972  better interaction with Emacs' compilation mode.
3973- Optimized compilation of "lazy e" when the argument "e" is
3974  already evaluated.
3975- Optimized compilation of equality tests with a variant constant constructor.
3976- The -dllib options recorded in libraries are no longer ignored when
3977  -use_runtime or -use_prims is used (unless -no_auto_link is
3978  explicitly used).
3979- Check that at most one of -pack, -a, -shared, -c, -output-obj is
3980  given on the command line.
3981- Optimized compilation of private types as regular manifest types
3982  (e.g. abbreviation to float, float array or record types with only
3983   float fields).
3984
3985Native-code compiler:
3986- New port: Mac OS X / Intel in 64-bit mode (configure with -cc "gcc -m64").
3987- A new option "-shared" to produce a plugin that can be dynamically
3988  loaded with the native version of Dynlink.
3989- A new option "-nodynlink" to enable optimizations valid only for code
3990  that is never dynlinked (no-op except for AMD64).
3991- More aggressive unboxing of floats and boxed integers.
3992- Can select which assembler and asm options to use at configuration time.
3993
3994Run-time system:
3995- New implementation of the page table describing the heap (two-level
3996  array in 32 bits, sparse hashtable in 64 bits), fixes issues with address
3997  space randomization on 64-bit OS (PR#4448).
3998- New "generational" API for registering global memory roots with the GC,
3999  enables faster scanning of global roots.
4000  (The functions are caml_*_generational_global_root in <caml/memory.h>.)
4001- New function "caml_raise_with_args" to raise an exception with several
4002  arguments from C.
4003- Changes in implementation of dynamic linking of C code:
4004  under Win32, use Alain Frisch's flexdll implementation of the dlopen
4005  API; under MacOSX, use dlopen API instead of MacOSX bundle API.
4006- Programs may now choose a first-fit allocation policy instead of
4007  the default next-fit.  First-fit reduces fragmentation but is
4008  slightly slower in some cases.
4009
4010Standard library:
4011- Parsing library: new function "set_trace" to programmatically turn
4012  on or off the printing of a trace during parsing.
4013- Printexc library: new functions "print_backtrace" and "get_backtrace"
4014  to obtain a stack backtrace of the most recently raised exception.
4015  New function "record_backtrace" to turn the exception backtrace mechanism
4016  on or off from within a program.
4017- Scanf library: fine-tuning of meta format implementation;
4018  fscanf behaviour revisited: only one input buffer is allocated for any
4019  given input channel;
4020  the %n conversion does not count a lookahead character as read.
4021
4022Other libraries:
4023- Dynlink: on some platforms, the Dynlink library is now available in
4024  native code. The boolean Dynlink.is_native allows the program to
4025  know whether it has been compiled in bytecode or in native code.
4026- Bigarrays: added "unsafe_get" and "unsafe_set"
4027  (non-bound-checking versions of "get" and "set").
4028- Bigarrays: removed limitation "array dimension < 2^31".
4029- Labltk: added support for TK 8.5.
4030- Num: added conversions between big_int and int32, nativeint, int64.
4031  More efficient implementation of Num.quo_num and Num.mod_num.
4032- Threads: improved efficiency of mutex and condition variable operations;
4033  improved interaction with Unix.fork (PR#4577).
4034- Unix: added getsockopt_error returning type Unix.error.
4035  Added support for TCP_NODELAY and IPV6_ONLY socket options.
4036- Win32 Unix: "select" now supports all kinds of file descriptors.
4037  Improved emulation of "lockf" (PR#4609).
4038
4039Tools:
4040- ocamldebug now supported under Windows (MSVC and Mingw ports),
4041  but without the replay feature.  (Contributed by Dmitry Bely
4042  and Sylvain Le Gall at OCamlCore with support from Lexifi.)
4043- ocamldoc: new option -no-module-constraint-filter to include functions
4044  hidden by signature constraint in documentation.
4045- ocamlmklib and ocamldep.opt now available under Windows ports.
4046- ocamlmklib no longer supports the -implib option.
4047- ocamlnat: an experimental native toplevel (not built by default).
4048
4049Camlp4:
4050* programs linked with camlp4lib.cma now also need dynlink.cma.
4051
4052Bug fixes:
4053- Major GC and heap compaction: fixed bug involving lazy values and
4054  out-of-heap pointers.
4055- PR#3915: updated most man pages.
4056- PR#4261: type-checking of recursive modules
4057- PR#4308: better stack backtraces for "spontaneous" exceptions such as
4058  Stack_overflow, Out_of_memory, etc.
4059- PR#4338: Str.global_substitute, Str.global_replace and the Str.*split*
4060  functions are now tail-recursive.
4061- PR#4503: fixed bug in classify_float on ARM.
4062- PR#4512: type-checking of recursive modules
4063- PR#4517: crash in ocamllex-generated lexers.
4064- PR#4542: problem with return value of Unix.nice.
4065- PR#4557: type-checking of recursive modules.
4066- PR#4562: strange %n semantics in scanf.
4067- PR#4564: add note "stack is not executable" to object files generated by
4068  ocamlopt (Linux/x86, Linux/AMD64).
4069- PR#4566: bug in Ratio.approx_ratio_fix and Num.approx_num_fix.
4070- PR#4582: clarified the documentation of functions in the String module.
4071- PR#4583: stack overflow in "ocamlopt -g" during closure conversion pass.
4072- PR#4585: ocamldoc and "val virtual" declarations.
4073- PR#4587: ocamldoc and escaped @ characters.
4074- PR#4605: Buffer.add_substitute was sometime wrong when target string had
4075           backslashes.
4076- PR#4614: Inconsistent declaration of CamlCBCmd in LablTk library.
4077
4078
4079Objective Caml 3.10.2 (29 Feb 2008):
4080------------------------------------
4081
4082Bug fixes:
4083- PR#1217 (partial) Typo in ocamldep man page
4084- PR#3952 (partial) ocamlopt: allocation problems on ARM
4085- PR#4339 (continued) ocamlopt: problems on HPPA
4086- PR#4455 str.mli not installed under Windows
4087- PR#4473 crash when accessing float array with polymorphic method
4088- PR#4480 runtime would not compile without gcc extensions
4089- PR#4481 wrong typing of exceptions with object arguments
4090- PR#4490 typo in error message
4091- Random crash on 32-bit when major_heap_increment >= 2^22
4092- Big performance bug in Weak hashtables
4093- Small bugs in the make-package-macosx script
4094- Bug in typing of polymorphic variants (reported on caml-list)
4095
4096
4097Objective Caml 3.10.1 (11 Jan 2008):
4098------------------------------------
4099
4100Bug fixes:
4101- PR#3830 small bugs in docs
4102- PR#4053 compilers: improved compilation time for large variant types
4103- PR#4174 ocamlopt: fixed ocamlopt -nopervasives
4104- PR#4199 otherlibs: documented a small problem in Unix.utimes
4105- PR#4280 camlp4: parsing of identifier (^)
4106- PR#4281 camlp4: parsing of type constraint
4107- PR#4285 runtime: cannot compile under AIX
4108- PR#4286 ocamlbuild: cannot compile under AIX and SunOS
4109- PR#4288 compilers: including a functor application with side effects
4110- PR#4295 camlp4 toplevel: synchronization after an error
4111- PR#4300 ocamlopt: crash with backtrace and illegal array access
4112- PR#4302 camlp4: list comprehension parsing problem
4113- PR#4304 ocamlbuild: handle -I correctly
4114- PR#4305 stdlib: alignment of Arg.Symbol
4115- PR#4307 camlp4: assertion failure
4116- PR#4312 camlp4: accept "let _ : int = 1"
4117- PR#4313 ocamlbuild: -log and missing directories
4118- PR#4315 camlp4: constraints in classes
4119- PR#4316 compilers: crash with recursive modules and Lazy
4120- PR#4318 ocamldoc: installation problem with Cygwin (tentative fix)
4121- PR#4322 ocamlopt: stack overflow under Windows
4122- PR#4325 compilers: wrong error message for unused var
4123- PR#4326 otherlibs: marshal Big_int on win64
4124- PR#4327 ocamlbuild: make emacs look for .annot in _build directory
4125- PR#4328 camlp4: stack overflow with nil nodes
4126- PR#4331 camlp4: guards on fun expressions
4127- PR#4332 camlp4: parsing of negative 32/64 bit numbers
4128- PR#4336 compilers: unsafe recursive modules
4129- PR#4337 (note) camlp4: invalid character escapes
4130- PR#4339 ocamlopt: problems on HP-UX (tentative fix)
4131- PR#4340 camlp4: wrong pretty-printing of optional arguments
4132- PR#4348 ocamlopt: crash on Mac Intel
4133- PR#4349 camlp4: bug in private type definitions
4134- PR#4350 compilers: type errors with records and polymorphic variants
4135- PR#4352 compilers: terminal recursion under Windows (tentative fix)
4136- PR#4354 ocamlcp: mismatch with ocaml on polymorphic let
4137- PR#4358 ocamlopt: float constants wrong on ARM
4138- PR#4360 ocamldoc: string inside comment
4139- PR#4365 toplevel: wrong pretty-printing of polymorphic variants
4140- PR#4373 otherlibs: leaks in win32unix
4141- PR#4374 otherlibs: threads module not initialized
4142- PR#4375 configure: fails to build on bytecode-only architectures
4143- PR#4377 runtime: finalisation of infix pointers
4144- PR#4378 ocamlbuild: typo in plugin.ml
4145- PR#4379 ocamlbuild: problem with plugins under Windows
4146- PR#4382 compilers: typing of polymorphic record fields
4147- PR#4383 compilers: including module with private type
4148- PR#4385 stdlib: Int32/Int64.format are unsafe
4149- PR#4386 otherlibs: wrong signal numbers with Unix.sigprocmask etc.
4150- PR#4387 ocamlbuild: build directory not used properly
4151- PR#4392 ocamldep: optional argument of class
4152- PR#4394 otherlibs: infinite loops in Str
4153- PR#4397 otherlibs: wrong size for flag arrays in win32unix
4154- PR#4402 ocamldebug: doesn't work with -rectypes
4155- PR#4410 ocamlbuild: problem with plugin and -build
4156- PR#4411 otherlibs: crash with Unix.access under Windows
4157- PR#4412 stdlib: marshalling broken on 64 bit architectures
4158- PR#4413 ocamlopt: crash on AMD64 with out-of-bound access and reraise
4159- PR#4417 camlp4: pretty-printing of unary minus
4160- PR#4419 camlp4: problem with constraint in type class
4161- PR#4426 compilers: problem with optional labels
4162- PR#4427 camlp4: wrong pretty-printing of lists of functions
4163- PR#4433 ocamlopt: fails to build on MacOSX 10.5
4164- PR#4435 compilers: crash with objects
4165- PR#4439 fails to build on MacOSX 10.5
4166- PR#4441 crash when build on sparc64 linux
4167- PR#4442 stdlib: crash with weak pointers
4168- PR#4446 configure: fails to detect X11 on MacOSX 10.5
4169- PR#4448 runtime: huge page table on 64-bit architectures
4170- PR#4450 compilers: stack overflow with recursive modules
4171- PR#4470 compilers: type-checking of recursive modules too restrictive
4172- PR#4472 configure: autodetection of libX11.so on Fedora x86_64
4173- printf: removed (partially implemented) positional specifications
4174- polymorphic < and <= comparisons: some C compiler optimizations
4175  were causing incorrect results when arguments are incomparable
4176
4177New features:
4178- made configure script work on PlayStation 3
4179- ARM port: brought up-to-date for Debian 4.0 (Etch)
4180- many other small changes and bugfixes in camlp4, ocamlbuild, labltk,
4181  emacs files
4182
4183
4184Objective Caml 3.10.0 (18 May 2007):
4185------------------------------------
4186
4187(Changes that can break existing programs are marked with a "*"  )
4188
4189Language features:
4190- Added virtual instance variables in classes "val virtual v : t"
4191* Changed the behaviour of instance variable overriding; the new
4192  definition replaces the old one, rather than creating a new
4193  variable.
4194
4195New tools:
4196- ocamlbuild: compilation manager for OCaml applications and libraries.
4197  See draft documentation at http://gallium.inria.fr/~pouillar/
4198* Camlp4: heavily revised implementation, new API.
4199
4200New ports:
4201- MacOS X PowerPC 64 bits.
4202- MS Windows 64 bits (x64) using the Microsoft PSDK toolchain.
4203- MS Windows 32 bits using the Visual Studio 2005 toolchain.
4204
4205Compilers:
4206- Faster type-checking of functor applications.
4207- Referencing an interface compiled with -rectypes from a module
4208    not compiled with -rectypes is now an error.
4209- Revised the "fragile matching" warning.
4210
4211Native-code compiler:
4212- Print a stack backtrace on an uncaught exception.
4213  (Compile and link with ocamlopt -g; execute with OCAMLRUNPARAM=b.)
4214  Supported on Intel/AMD in 32 and 64 bits, PPC in 32 and 64 bits.
4215- Stack overflow detection on MS Windows 32 bits (courtesy O. Andrieu).
4216- Stack overflow detection on MacOS X PPC and Intel.
4217- Intel/AMD 64 bits: generate position-independent code by default.
4218- Fixed bug involving -for-pack and missing .cmx files (PR#4124).
4219- Fixed bug causing duplication of literals  (PR#4152).
4220
4221Run-time system:
4222- C/Caml interface functions take "char const *" arguments
4223  instead of "char *" when appropriate.
4224- Faster string comparisons (fast case if strings are ==).
4225
4226Standard library:
4227- Refined typing of format strings (type format6).
4228- Printf, Format: new function ifprintf that consumes its arguments
4229    and prints nothing (useful to print conditionally).
4230- Scanf:
4231    new function format_from_string to convert a string to a format string;
4232    new %r conversion to accomodate user defined scanners.
4233- Filename: improved Win32 implementation of Filename.quote.
4234- List: List.nth now tail-recursive.
4235- Sys: added Sys.is_directory.  Some functions (e.g. Sys.command) that
4236    could incorrectly raise Sys_io_blocked now raise Sys_error as intended.
4237- String and Char: the function ``escaped'' now escapes all the characters
4238    especially handled by the compiler's lexer (PR#4220).
4239
4240Other libraries:
4241- Bigarray: mmap_file takes an optional argument specifying
4242    the start position of the data in the mapped file.
4243- Dynlink: now defines only two modules, Dynlink and Dynlinkaux (internal),
4244    reducing risks of name conflicts with user modules.
4245- Labltk under Win32: now uses Tcl/Tk 8.4 instead of 8.3 by default.
4246- VM threads: improved performance of I/O operations (less polling).
4247- Unix: new function Unix.isatty.
4248- Unix emulation under Win32:
4249    fixed incorrect error reporting in several functions (PR#4097);
4250    better handling of channels opened on sockets (PR#4098);
4251    fixed GC bug in Unix.system (PR#4112).
4252
4253Documentation generator (OCamldoc):
4254- correctly handle '?' in value names (PR#4215)
4255- new option -hide-warnings not to print ocamldoc warnings
4256
4257Lexer generator (ocamllex): improved error reporting.
4258
4259License: fixed a typo in the "special exception" to the LGPL.
4260
4261
4262Objective Caml 3.09.3 (15 Sep 2006):
4263------------------------------------
4264
4265Bug fixes:
4266- ocamldoc: -using modtype constraint to filter module elements displayed
4267    in doc PR#4016
4268- ocamldoc: error in merging of top dependencies of modules PR#4007
4269- ocamldoc: -dot-colors has no effect PR#3981
4270- ocamdloc: missing crossref in text from intro files PR#4066
4271- compilers: segfault with recursive modules PR#4008
4272- compilers: infinite loop when compiling objects PR#4018
4273- compilers: bad error message when signature mismatch PR#4001
4274- compilers: infinite loop with -rectypes PR#3999
4275- compilers: contravariance bug in private rows
4276- compilers: unsafe cast with polymorphic exception PR#4002
4277- native compiler: bad assembly code generated for AMD64 PR#4067
4278- native compiler: stack alignment problems on MacOSX/i386 PR#4036
4279- stdlib: crash in marshalling PR#4030
4280- stdlib: crash when closing a channel twice PR#4039
4281- stdlib: memory leak in Sys.readdir PR#4093
4282- C interface: better definition of CAMLreturn PR#4068
4283- otherlibs/unix: crash in gethostbyname PR#3043
4284- tools: subtle problem with unset in makefile PR#4048
4285- camlp4: install pa_o_fast.o PR#3812
4286- camlp4: install more modules PR#3689
4287
4288New features:
4289- ocamldoc: name resolution in cross-referencing {!name}: if name is not
4290    found, then it is searched in the parent module/class, and in the parent
4291    of the parent, and so on until it is found.
4292- ocamldoc: new option -short-functors to use a short form to display
4293    functors in html generator PR#4017
4294- ocamlprof: added "-version" option
4295
4296
4297
4298Objective Caml 3.09.2 (14 Apr 2006):
4299------------------------------------
4300
4301Bug fixes:
4302- Makefile: problem with "make world.opt" PR#3954
4303- compilers: problem compiling several modules with one command line PR#3979
4304- compilers,ocamldoc: error message that Emacs cannot parse
4305- compilers: crash when printing type error PR#3968
4306- compilers: -dtypes wrong for monomorphic type variables PR#3894
4307- compilers: wrong warning on optional arguments PR#3980
4308- compilers: crash when wrong use of type constructor in let rec PR#3976
4309- compilers: better wording of "statement never returns" warning PR#3889
4310- runtime: inefficiency of signal handling PR#3990
4311- runtime: crashes with I/O in multithread programs PR#3906
4312- camlp4: empty file name in error messages PR#3886
4313- camlp4: stack overflow PR#3948
4314- otherlibs/labltk: ocamlbrowser ignores its command line options PR#3961
4315- otherlibs/unix: Unix.times wrong under Mac OS X PR#3960
4316- otherlibs/unix: wrong doc for execvp and execvpe PR#3973
4317- otherlibs/win32unix: random crash in Unix.stat PR#3998
4318- stdlib: update_mod not found under Windows PR#3847
4319- stdlib: Filename.dirname/basename wrong on Win32 PR#3933
4320- stdlib: incomplete documentation of Pervasives.abs PR#3967
4321- stdlib: Printf bugs PR#3902, PR#3955
4322- tools/checkstack.c: missing include
4323- yacc: crash when given argument "-" PR#3956
4324
4325New features:
4326- ported to MacOS X on Intel PR#3985
4327- configure: added support for GNU Hurd PR#3991
4328
4329Objective Caml 3.09.1 (4 Jan 2006):
4330-----------------------------------
4331
4332Bug fixes:
4333- compilers: raise not_found with -principal PR#3855
4334- compilers: assert failure in typeclass.cml PR#3856
4335- compilers: assert failure in typing/ctype.ml PR#3909
4336- compilers: fatal error exception Ctype.Unify PR#3918
4337- compilers: spurious warning Y in objects PR#3868
4338- compilers: spurious warning Z on loop index PR#3907
4339- compilers: error message that emacs cannot parse
4340- ocamlopt: problems with -for-pack/-pack PR#3825, PR#3826, PR#3919
4341- ocamlopt: can't produce shared libraries on x86_64 PR#3869, PR#3924
4342- ocamlopt: float alignment problem on SPARC PR#3944
4343- ocamlopt: can't compile on MIPS PR#3936
4344- runtime: missing dependence for ld.conf
4345- runtime: missing dependence for .depend.nt PR#3880
4346- runtime: memory leak in caml_register_named_value PR#3940
4347- runtime: crash in Marshal.to_buffer PR#3879
4348- stdlib: Sys.time giving wrong results on Mac OS X PR#3850
4349- stdlib: Weak.get_copy causing random crashes in rare cases
4350- stdlib, debugger, labltk: use TMPDIR if set PR#3895
4351- stdlib: scanf bug on int32 and nativeint PR#3932
4352- camlp4: mkcamlp4 option parsing problem PR#3941
4353- camlp4: bug in pretty-printing of lazy/assert/new
4354- camlp4: update the unmaintained makefile for _loc name
4355- ocamldoc: several fixes see ocamldoc/Changes.txt
4356- otherlibs/str: bug in long sequences of alternatives PR#3783
4357- otherlibs/systhreads: deadlock in Windows PR#3910
4358- tools: update dumpobj to handle new event format PR#3873
4359- toplevel: activate warning Y in toplevel PR#3832
4360
4361New features:
4362- otherlibs/labltk: browser uses menu bars instead of menu buttons
4363
4364Objective Caml 3.09.0 (27 Oct 2006):
4365------------------------------------
4366
4367(Changes that can break existing programs are marked with a "*"  )
4368
4369Language features:
4370- Introduction of private row types, for abstracting the row in object
4371  and variant types.
4372
4373Type checking:
4374- Polymorphic variants with at most one constructor [< `A of t] are no
4375  longer systematically promoted to the exact type [`A of t]. This was
4376  more confusing than useful, and created problems with private row
4377  types.
4378
4379Both compilers:
4380- Added warnings 'Y' and 'Z' for local variables that are bound but
4381  never used.
4382- Added warning for some uses non-returning functions (e.g. raise), when they
4383  are passed extra arguments, or followed by extra statements.
4384- Pattern matching: more prudent compilation in case of guards; fixed PR#3780.
4385- Compilation of classes: reduction in size of generated code.
4386- Compilation of "module rec" definitions: fixed a bad interaction with
4387  structure coercion (to a more restrictive signature).
4388
4389Native-code compiler (ocamlopt):
4390* Revised implementation of the -pack option (packing of several compilation
4391  units into one).  The .cmx files that are to be packed with
4392  "ocamlopt -pack -o P.cmx" must be compiled with "ocamlopt -for-pack P".
4393  In exchange for this additional constraint, ocamlopt -pack is now
4394  available on all platforms (no need for binutils).
4395* Fixed wrong evaluation order for arguments to certain inlined functions.
4396- Modified code generation for "let rec ... and ..." to reduce compilation
4397  time (which was quadratic in the number of mutually-recursive functions).
4398- x86 port: support tail-calls for functions with up to 21 arguments.
4399- AMD64 port, Linux: recover from system stack overflow.
4400- Sparc port: more portable handling of out-of-bound conditions
4401  on systems other than Solaris.
4402
4403Standard library:
4404- Pervasives: faster implementation of close_in, close_out.
4405  set_binary_mode_{out,in} now working correctly under Cygwin.
4406- Printf: better handling of partial applications of the printf functions.
4407- Scanf: new function sscanf_format to read a format from a
4408  string. The type of the resulting format is dynamically checked and
4409  should be the type of the template format which is the second argument.
4410- Scanf: no more spurious lookahead attempt when the end of file condition
4411  is set and a correct token has already been read and could be returned.
4412
4413Other libraries:
4414- System threads library: added Thread.sigmask; fixed race condition
4415  in signal handling.
4416- Bigarray library: fixed bug in Array3.of_array.
4417- Unix library: use canonical signal numbers in results of Unix.wait*;
4418  hardened Unix.establish_server against EINTR errors.
4419
4420Run-time system:
4421- Support platforms where sizeof(void *) = 8 and sizeof(long) = 4.
4422- Improved and cleaned up implementation of signal handling.
4423
4424Replay debugger:
4425- Improved handling of locations in source code.
4426
4427OCamldoc:
4428- extensible {foo } syntax
4429- user can give .txt files on the command line, containing ocamldoc formatted
4430  text, to be able to include bigger texts out of source files
4431- -o option is now used by the html generator to indicate the prefix
4432  of generated index files (to avoid conflict when a Index module exists
4433  on case-insensitive file systems).
4434
4435Miscellaneous:
4436- Configuration information is installed in `ocamlc -where`/Makefile.config
4437  and can be used by client Makefiles or shell scripts.
4438
4439Objective Caml 3.08.4 (11 Aug 2005):
4440------------------------------------
4441
4442New features:
4443- configure: find X11 config in some 64-bit Linux distribs
4444- ocamldoc: (**/**) can be canceled with another (**/**) PR#3665
4445- graphics: added resize_window
4446- graphics: check for invalid arguments to drawing primitives PR#3595
4447- ocamlbrowser: use windows subsystem on mingw
4448
4449Bug fixes:
4450- ocamlopt: code generation problem on AMD64 PR#3640
4451- wrong code generated for some classes PR#3576
4452- fatal error when compiling some OO code PR#3745
4453- problem with comparison on constant constructors PR#3608
4454- camlp4: cryptic error message PR#3592
4455- camlp4: line numbers in multi-line antiquotations PR#3549
4456- camlp4: problem with make depend
4457- camlp4: parse error with :> PR#3561
4458- camlp4: ident conversion problem with val/contents/contents__
4459- camlp4: several small parsing problems PR#3688
4460- ocamldebug: handling of spaces in executable file name PR#3736
4461- emacs-mode: problem when caml-types-buffer is deleted by user PR#3704
4462- ocamldoc: extra backslash in ocamldoc man page PR#3687
4463- ocamldoc: improvements to HTML display PR#3698
4464- ocamldoc: escaping of @ in info files
4465- ocamldoc: escaping of . and \ in man pages PR#3686
4466- ocamldoc: better error reporting of misplaced comments
4467- graphics: fixed .depend file PR#3558
4468- graphics: segfault with threads and graphics PR#3651
4469- nums: several bugs: PR#3718, PR#3719, others
4470- nums: inline asm problems with gcc 4.0 PR#3604, PR#3637
4471- threads: problem with backtrace
4472- unix: problem with getaddrinfo PR#3565
4473- stdlib: documentation of Int32.rem and Int64.rem PR#3573
4474- stdlib: documentation of List.rev_map2 PR#3685
4475- stdlib: wrong order in Map.fold PR#3607
4476- stdlib: documentation of maximum float array length PR#3714
4477- better detection of cycles when using -rectypes
4478- missing case of module equality PR#3738
4479- better error messages for unbound type variables
4480- stack overflow while printing type error message PR#3705
4481- assert failure when typing some classes PR#3638
4482- bug in type_approx
4483- better error messages related to type variance checking
4484- yacc: avoid name capture for idents of the Parsing module
4485
4486
4487Objective Caml 3.08.3 (24 Mar 2005):
4488------------------------------------
4489
4490New features:
4491- support for ocamlopt -pack under Mac OS X (PR#2634, PR#3320)
4492- ignore unknown warning options for forward and backward compatibility
4493- runtime: export caml_compare_unordered (PR#3479)
4494- camlp4: install argl.* files (PR#3439)
4495- ocamldoc: add -man-section option
4496- labltk: add the "solid" relief option (PR#3343)
4497
4498Bug fixes:
4499- typing: fix unsoundness in type declaration variance inference.
4500    Type parameters which are constrained must now have an explicit variant
4501    annotation, otherwise they are invariant. This is not backward
4502    compatible, so this might break code which either uses subtyping or
4503    uses the relaxed value restriction (i.e. was not typable before 3.07)
4504- typing: erroneous partial match warning for polymorphic variants (PR#3424)
4505- runtime: handle the case of an empty command line (PR#3409, PR#3444)
4506- stdlib: make Sys.executable_name an absolute path in native code (PR#3303)
4507- runtime: fix memory leak in finalise.c
4508- runtime: auto-trigger compaction even if gc is called manually (PR#3392)
4509- stdlib: fix segfault in Obj.dup on zero-sized values (PR#3406)
4510- camlp4: correct parsing of the $ identifier (PR#3310, PR#3469)
4511- windows (MS tools): use link /lib instead of lib (PR#3333)
4512- windows (MS tools): change default install destination
4513- autoconf: better checking of SSE2 instructions (PR#3329, PR#3330)
4514- graphics: make close_graph close the X display as well as the window (PR#3312)
4515- num: fix big_int_of_string (empty string) (PR#3483)
4516- num: fix big bug on 64-bit architecture (PR#3299)
4517- str: better documentation of string_match and string_partial_match (PR#3395)
4518- unix: fix file descriptor leak in Unix.accept (PR#3423)
4519- unix: miscellaneous clean-ups
4520- unix: fix documentation of Unix.tm (PR#3341)
4521- graphics: fix problem when allocating lots of images under Windows (PR#3433)
4522- compiler: fix error message with -pack when .cmi is missing (PR#3028)
4523- cygwin: fix problem with compilation of camlheader (PR#3485)
4524- stdlib: Filename.basename doesn't return an empty string any more (PR#3451)
4525- stdlib: better documentation of Open_excl flag (PR#3450)
4526- ocamlcp: accept -thread option (PR#3511)
4527- ocamldep: handle spaces in file names (PR#3370)
4528- compiler: remove spurious warning in pattern-matching on variants (PR#3424)
4529- windows: better handling of InterpreterPath registry entry (PR#3334, PR#3432)
4530
4531
4532Objective Caml 3.08.2 (22 Nov 2004):
4533------------------------------------
4534
4535Bug fixes:
4536- runtime: memory leak when unmarshalling big data structures (PR#3247)
4537- camlp4: incorrect line numbers in errors (PR#3188)
4538- emacs: xemacs-specific code, wrong call to "sit-for"
4539- ocamldoc: "Lexing: empty token" (PR#3173)
4540- unix: problem with close_process_* (PR#3191)
4541- unix: possible coredumps (PR#3252)
4542- stdlib: wrong order in Set.fold (PR#3161)
4543- ocamlcp: array out of bounds in profiled programs (PR#3267)
4544- yacc: problem with polymorphic variant types for grammar entries (PR#3033)
4545
4546Misc:
4547- export <caml/printexc.h> for caml_format_exception (PR#3080)
4548- clean up caml_search_exe_in_path (maybe PR#3079)
4549- camlp4: new function "make_lexer" for new-style locations
4550- unix: added missing #includes (PR#3088)
4551
4552
4553Objective Caml 3.08.1 (19 Aug 2004):
4554------------------------------------
4555
4556Licence:
4557- The emacs files are now under GPL
4558- Slightly relaxed some conditions of the QPL
4559
4560Bug fixes:
4561- ld.conf now generated at compile-time instead of install-time
4562- fixed -pack on Windows XP (PR#2935)
4563- fixed Obj.tag (PR#2946)
4564- added support for multiple dlopen in Darwin
4565- run ranlib when installing camlp4 libraries (PR#2944)
4566- link camlp4opt with -linkall (PR#2949)
4567- camlp4 parsing of patterns now conforms to normal parsing (PR#3015)
4568- install camlp4 *.cmx files (PR#2955)
4569- fixed handling of linefeed in string constants in camlp4 (PR#3074)
4570- ocamldoc: fixed display of class parameters in HTML and LaTeX (PR#2994)
4571- ocamldoc: fixed display of link to class page in html (PR#2994)
4572- Windows toplevel GUI: assorted fixes (including PR#2932)
4573
4574Misc:
4575- added -v option to ocamllex
4576- ocamldoc: new -intf and -impl options supported (PR#3036)
4577
4578Objective Caml 3.08.0 (13 Jul 2004):
4579------------------------------------
4580
4581(Changes that can break existing programs are marked with a "*"  )
4582
4583Language features:
4584- Support for immediate objects, i.e. objects defined without going
4585  through a class.  (Syntax is "object <fields and methods> end".)
4586
4587Type-checking:
4588- When typing record construction and record patterns, can omit
4589  the module qualification on all labels except one.  I.e.
4590  { M.l1 = ...; l2 = ... } is interpreted as { M.l1 = ...; M.l2 = ... }
4591
4592Both compilers:
4593- More compact compilation of classes.
4594- Much more efficient handling of class definitions inside functors
4595  or local modules.
4596- Simpler representation for method tables. Objects can now be marshaled
4597  between identical programs with the flag Marshal.Closures.
4598- Improved error messages for objects and variants.
4599- Improved printing of inferred module signatures (toplevel and ocamlc -i).
4600  Recursion between type, class, class type and module definitions is now
4601  correctly printed.
4602- The -pack option now accepts compiled interfaces (.cmi files) in addition
4603  to compiled implementations (.cmo or .cmx).
4604* A compile-time error is signaled if an integer literal exceeds the
4605  range of representable integers.
4606- Fixed code generation error for "module rec" definitions.
4607- The combination of options -c -o sets the name of the generated
4608  .cmi / .cmo / .cmx files.
4609
4610Bytecode compiler:
4611- Option -output-obj is now compatible with Dynlink and
4612  with embedded toplevels.
4613
4614Native-code compiler:
4615- Division and modulus by zero correctly raise exception Division_by_zero
4616  (instead of causing a hardware trap).
4617- Improved compilation time for the register allocation phase.
4618- The float constant -0.0 was incorrectly treated as +0.0 on some processors.
4619- AMD64: fixed bugs in asm glue code for GC invocation and exception raising
4620  from C.
4621- IA64: fixed incorrect code generated for "expr mod 1".
4622- PowerPC: minor performance tweaks for the G4 and G5 processors.
4623
4624Standard library:
4625* Revised handling of NaN floats in polymorphic comparisons.
4626  The polymorphic boolean-valued comparisons (=, <, >, etc) now treat
4627  NaN as uncomparable, as specified by the IEEE standard.
4628  The 3-valued comparison (compare) treats NaN as equal to itself
4629  and smaller than all other floats.  As a consequence, x == y
4630  no longer implies x = y but still implies compare x y = 0.
4631* String-to-integer conversions now fail if the result overflows
4632  the range of integers representable in the result type.
4633* All array and string access functions now raise
4634  Invalid_argument("index out of bounds") when a bounds check fails.
4635  In earlier releases, different exceptions were raised
4636  in bytecode and native-code.
4637- Module Buffer: new functions Buffer.sub, Buffer.nth
4638- Module Int32: new functions Int32.bits_of_float, Int32.float_of_bits.
4639- Module Map: new functions is_empty, compare, equal.
4640- Module Set: new function split.
4641* Module Gc: in-order finalisation, new function finalise_release.
4642
4643Other libraries:
4644- The Num library: complete reimplementation of the C/asm lowest
4645  layer to work around potential licensing problems.
4646  Improved speed on the PowerPC and AMD64 architectures.
4647- The Graphics library: improved event handling under MS Windows.
4648- The Str library: fixed bug in "split" functions with nullable regexps.
4649- The Unix library:
4650   . Added Unix.single_write.
4651   . Added support for IPv6.
4652   . Bug fixes in Unix.closedir.
4653   . Allow thread switching on Unix.lockf.
4654
4655Runtime System:
4656* Name space depollution: all global C identifiers are now prefixed
4657  with "caml" to avoid name clashes with other libraries.  This
4658  includes the "external" primitives of the standard runtime.
4659
4660Ports:
4661- Windows ports: many improvements in the OCamlWin toplevel application
4662  (history, save inputs to file, etc).  Contributed by Christopher A. Watford.
4663- Native-code compilation supported for HPPA/Linux. Contributed by Guy Martin.
4664- Removed support for MacOS9.  Mac OS 9 is obsolete and the port was not
4665  updated since 3.05.
4666- Removed ocamlopt support for HPPA/Nextstep and Power/AIX.
4667
4668Ocamllex:
4669- #line directives in the input file are now accepted.
4670- Added character set concatenation operator "cset1 # cset2".
4671
4672Ocamlyacc:
4673- #line directives in the input file are now accepted.
4674
4675Camlp4:
4676* Support for new-style locations (line numbers, not just character numbers).
4677- See camlp4/CHANGES and camlp4/ICHANGES for more info.
4678
4679
4680Objective Caml 3.07 (29 Sep 2003):
4681----------------------------------
4682
4683Language features:
4684- Experimental support for recursive module definitions
4685      module rec A : SIGA = StructA and B : SIGB = StructB and ...
4686- Support for "private types", or more exactly concrete data types
4687  with private constructors or labels.  These data types can be
4688  de-structured normally in pattern matchings, but values of these
4689  types cannot be constructed directly outside of their defining module.
4690- Added integer literals of types int32, nativeint, int64
4691  (written with an 'l', 'n' or 'L' suffix respectively).
4692
4693Type-checking:
4694- Allow polymorphic generalization of covariant parts of expansive
4695  expressions.  For instance, if f: unit -> 'a list, "let x = f ()"
4696  gives "x" the generalized type forall 'a. 'a list, instead of '_a list
4697  as before.
4698- The typing of polymorphic variants in pattern matching has changed.
4699  It is intended to be more regular, sticking to the principle of "closing
4700  only the variants which would be otherwise incomplete". Two potential
4701  consequences: (1) some types may be left open which were closed before,
4702  and the resulting type might not match the interface anymore (expected to
4703  be rare); (2) in some cases an incomplete match may be generated.
4704- Lots of bug fixes in the handling of polymorphism and recursion inside
4705  types.
4706- Added a new "-dtypes" option to ocamlc/ocamlopt, and an emacs extension
4707  "emacs/caml-types.el".  The compiler option saves inferred type information
4708  to file *.annot, and the emacs extension allows the user to look at the
4709  type of any subexpression in the source file.  Works even in the case
4710  of a type error (all the types computed up to the error are available).
4711  This new feature is also supported by ocamlbrowser.
4712- Disable "method is overridden" warning when the method was explicitly
4713  redefined as virtual beforehand (i.e. not through inheritance). Typing
4714  and semantics are unchanged.
4715
4716Both compilers:
4717- Added option "-dtypes" to dump detailed type information to a file.
4718- The "-i" option no longer generates compiled files, it only prints
4719  the inferred types.
4720- The sources for the module named "Mod" can be placed either in Mod.ml or
4721  in mod.ml.
4722- Compilation of "let rec" on non-functional values: tightened some checks,
4723  relaxed some other checks.
4724- Fixed wrong code that was generated for "for i = a to max_int"
4725  or "for i = a downto min_int".
4726- An explicit interface Mod.mli can now be provided for the module obtained
4727  by ocamlc -pack -o Mod.cmo ... or ocamlopt -pack -o Mod.cmx ...
4728- Revised internal handling of source code locations, now handles
4729  preprocessed code better.
4730- Pattern-matching bug on float literals fixed.
4731- Minor improvements on pattern-matching over variants.
4732- More efficient compilation of string comparisons and the "compare" function.
4733- More compact code generated for arrays of constants.
4734- Fixed GC bug with mutable record fields of type "exn".
4735- Added warning "E" for "fragile patterns": pattern matchings that would
4736  not be flagged as partial if new constructors were added to the data type.
4737
4738Bytecode compiler:
4739- Added option -vmthread to select the threads library with VM-level
4740  scheduling.  The -thread option now selects the system threads library.
4741
4742Native-code compiler:
4743- New port: AMD64 (Opteron).
4744- Fixed instruction selection bug on expressions of the kind (raise Exn)(arg).
4745- Several bug fixes in ocamlopt -pack (tracking of imported modules,
4746  command line too long).
4747- Signal handling bug fixed.
4748- x86 port:
4749    Added -ffast-math option to use inline trigo and log functions.
4750    Small performance tweaks for the Pentium 4.
4751    Fixed illegal "imul" instruction generated by reloading phase.
4752- Sparc port:
4753    Enhanced code generation for Sparc V8 (option -march=v8) and
4754    Sparc V9 (option -march=v9).
4755    Profiling support added for Solaris.
4756- PowerPC port:
4757    Keep stack 16-aligned for compatibility with C calling conventions.
4758
4759Toplevel interactive system:
4760- Tightened interface consistency checks between .cmi files, .cm[oa] files
4761  loaded by #load, and the running toplevel.
4762- #trace on mutually-recursive functions was broken, works again.
4763- Look for .ocamlinit file in home directory in addition to the current dir.
4764
4765Standard library:
4766- Match_failure and Assert_failure exceptions now report
4767  (file, line, column), instead of (file, starting char, ending char).
4768- float_of_string, int_of_string: some ill-formed input strings were not
4769    rejected.
4770- Added format concatenation, string_of_format, format_of_string.
4771- Module Arg: added new option handlers Set_string, Set_int, Set_float,
4772    Symbol, Tuple.
4773- Module Format: tag handling is now turned off by default,
4774    use [Format.set_tags true] to activate.
4775- Modules Lexing and Parsing: added better handling of positions
4776    in source file.  Added function Lexing.flush_input.
4777- Module Scanf: %n and %N formats to count characters / items read so far;
4778    assorted bug fixes, %! to match end of input. New ``_'' special
4779    flag to skip reresulting value.
4780- Module Format: tags are not activated by default.
4781- Modules Set and Map: fixed bugs causing trees to become unbalanced.
4782- Module Printf: less restrictive typing of kprintf.
4783- Module Random: better seeding; functions to generate random int32, int64,
4784    nativeint; added support for explicit state management.
4785- Module Sys: added Sys.readdir for reading the contents of a directory.
4786
4787Runtime system:
4788- output_value/input_value: fixed bug with large blocks (>= 4 Mwords)
4789  produced on a 64-bit platform and incorrectly read back on a 32-bit
4790  platform.
4791- Fixed memory compaction bug involving input_value.
4792- Added MacOS X support for dynamic linking of C libraries.
4793- Improved stack backtraces on uncaught exceptions.
4794- Fixed float alignment problem on Sparc V9 with gcc 3.2.
4795
4796Other libraries:
4797- Dynlink:
4798    By default, dynamically-loaded code now has access to all
4799      modules defined by the program; new functions Dynlink.allow_only
4800      and Dynlink.prohibit implement access control.
4801    Fixed Dynlink problem with files generated with ocamlc -pack.
4802    Protect against references to modules not yet fully initialized.
4803- LablTK/CamlTK: added support for TCL/TK 8.4.
4804- Str: reimplemented regexp matching engine, now less buggy, faster,
4805    and LGPL instead of GPL.
4806- Graphics: fixed draw_rect and fill_rect bug under X11.
4807- System threads and bytecode threads libraries can be both installed.
4808- System threads: better implementation of Thread.exit.
4809- Bytecode threads: fixed two library initialization bugs.
4810- Unix: make Unix.openfile blocking to account for named pipes;
4811  GC bug in Unix.*stat fixed; fixed problem with Unix.dup2 on Windows.
4812
4813Ocamllex:
4814- Can name parts of the matched input text, e.g.
4815    "0" (['0'-'7']+ as s) { ... s ... }
4816
4817Ocamldebug:
4818- Handle programs that run for more than 2^30 steps.
4819
4820Emacs mode:
4821- Added file caml-types.el to interactively display the type information
4822  saved by option -dtypes.
4823
4824Win32 ports:
4825- Cygwin port: recognize \ as directory separator in addition to /
4826- MSVC port: ocamlopt -pack works provided GNU binutils are installed.
4827- Graphics library: fixed bug in Graphics.blit_image; improved event handling.
4828
4829OCamldoc:
4830- new ty_code field for types, to keep code of a type (with option -keep-code)
4831- new ex_code field for types, to keep code of an exception
4832    (with option -keep-code)
4833- some fixes in html generation
4834- don't overwrite existing style.css file when generating HTML
4835- create the ocamldoc.sty file when generating LaTeX (if nonexistent)
4836- man pages are now installed in man/man3 rather than man/mano
4837- fix: empty [] in generated HTML indexes
4838
4839
4840Objective Caml 3.06 (20 Aug 2002):
4841----------------------------------
4842
4843Type-checking:
4844- Apply value restriction to polymorphic record fields.
4845
4846Run-time system:
4847- Fixed GC bug affecting lazy values.
4848
4849Both compilers:
4850- Added option "-version" to print just the version number.
4851- Fixed wrong dependencies in .cmi generated with the -pack option.
4852
4853Native-code compiler:
4854- Fixed wrong return value for inline bigarray assignments.
4855
4856Libraries:
4857- Unix.getsockopt: make sure result is a valid boolean.
4858
4859Tools:
4860- ocamlbrowser: improved error reporting; small Win32 fixes.
4861
4862Windows ports:
4863- Fixed two problems with the Mingw port under Cygwin 1.3.
4864
4865
4866Objective Caml 3.05 (29 Jul 2002):
4867----------------------------------
4868
4869Language features:
4870- Support for polymorphic methods and record fields.
4871- Allows _ separators in integer and float literals, e.g. 1_000_000.
4872
4873Type-checker:
4874- New flag -principal to enforce principality of type inference.
4875- Fixed subtle typing bug with higher-order functors.
4876- Fixed several complexity problems; changed (again) the  behaviour of
4877  simple coercions.
4878- Fixed various bugs with objects and polymorphic variants.
4879- Improved some error messages.
4880
4881Both compilers:
4882- Added option "-pack" to assemble several compilation units as one unit
4883  having the given units as sub-modules.
4884- More precise detection of unused sub-patterns in "or" patterns.
4885- Warnings for ill-formed \ escapes in string and character literals.
4886- Protect against spaces and other special characters in directory names.
4887- Added interface consistency check when building a .cma or .cmxa library.
4888- Minor reduction in code size for class initialization code.
4889- Added option "-nostdlib" to ignore standard library entirely.
4890
4891Bytecode compiler:
4892- Fixed issue with ocamlc.opt and dynamic linking.
4893
4894Native-code compiler:
4895- Added link-time check for multiply-defined module names.
4896- Fixed GC bug related to constant constructors of polymorphic variant types.
4897- Fixed compilation bug for top-level "include" statements.
4898- PowerPC port: work around limited range for relative branches,
4899  thus removing assembler failures on large functions.
4900- IA64 port: fixed code generation bug for 3-way constructor matching.
4901
4902Toplevel interactive system:
4903- Can load object files given on command line before starting up.
4904- ocamlmktop: minimized possibility of name clashes with user-provided modules.
4905
4906Run-time system:
4907- Minor garbage collector no longer recursive.
4908- Better support for lazy data in the garbage collector.
4909- Fixed issues with the heap compactor.
4910- Fixed issues with finalized Caml values.
4911- The type "int64" is now supported on all platforms: we use software
4912  emulation if the C compiler doesn't support 64-bit integers.
4913- Support for float formats that are neither big-endian nor little-endian
4914  (one known example: the ARM).
4915- Fixed bug in callback*_exn functions in the exception-catching case.
4916- Work around gcc 2.96 bug on RedHat 7.2 and Mandrake 8.0, 8.1 among others.
4917- Stub DLLs now installed in subdir stublibs/ of standard library dir.
4918
4919Standard library:
4920- Protect against integer overflow in sub-string and sub-array bound checks.
4921- New module Complex implementing arithmetic over complex numbers.
4922- New module Scanf implementing format-based scanning a la scanf() in C.
4923- Module Arg: added alternate entry point Arg.parse_argv.
4924- Modules Char, Int32, Int64, Nativeint, String: added type "t" and function
4925  "compare" so that these modules can be used directly with e.g. Set.Make.
4926- Module Digest: fixed issue with Digest.file on large files (>= 1Gb);
4927    added Digest.to_hex.
4928- Module Filename: added Filename.open_temp_file to atomically create and
4929    open the temp file; improved security of Filename.temp_file.
4930- Module Genlex: allow _ as first character of an identifier.
4931- Module Lazy: more efficient implementation.
4932- Module Lexing: improved performances for very large tokens.
4933- Module List: faster implementation of sorting functions.
4934- Module Printf:
4935    added %S and %C formats (quoted, escaped strings and characters);
4936    added kprintf (calls user-specified continuation on formatted string).
4937- Module Queue: faster implementation (courtesy of François Pottier).
4938- Module Random: added Random.bool.
4939- Module Stack: added Stack.is_empty.
4940- Module Pervasives:
4941    added sub-module LargeFile to support files larger than 1Gb
4942      (file offsets are int64 rather than int);
4943    opening in "append" mode automatically sets "write" mode;
4944    files are now opened in close-on-exec mode;
4945    string_of_float distinguishes its output from a plain integer;
4946    faster implementation of input_line for long lines.
4947- Module Sys:
4948     added Sys.ocaml_version containing the OCaml version number;
4949     added Sys.executable_name containing the (exact) path of the
4950       file being executable;
4951     Sys.argv.(0) is now unchanged w.r.t. what was provided as 0-th argument
4952       by the shell.
4953- Module Weak: added weak hash tables.
4954
4955Other libraries:
4956- Bigarray:
4957    support for bigarrays of complex numbers;
4958    added functions Genarray.dims,
4959      {Genarray,Array1,Array2,Array3}.{kind,layout}.
4960- Dynlink: fixed bug with loading of mixed-mode Caml/C libraries.
4961- LablTK:
4962    now supports also the CamlTK API (no labels);
4963    support for Activate and Deactivate events;
4964    support for virtual events;
4965    added UTF conversion;
4966    export the tcl interpreter as caml value, to avoid DLL dependencies.
4967- Unix:
4968    added sub-module LargeFile to support files larger than 1Gb
4969      (file offsets are int64 rather than int);
4970    added POSIX opening flags (O_NOCTTY, O_*SYNC);
4971    use reentrant functions for gethostbyname and gethostbyaddr when available;
4972    fixed bug in Unix.close_process and Unix.close_process_full;
4973    removed some overhead in Unix.select.
4974
4975Tools:
4976- ocamldoc (the documentation generator) is now part of the distribution.
4977- Debugger: now supports the option -I +dir.
4978- ocamllex: supports the same identifiers as ocamlc; warns for
4979  bad \ escapes in strings and characters.
4980- ocamlbrowser:
4981    recenter the module boxes when showing a cross-reference;
4982    include the current directory in the ocaml path.
4983
4984Windows port:
4985- Can now compile with Mingw (the GNU compilers without the Cygwin
4986  runtime library) in addition to MSVC.
4987- Toplevel GUI: wrong filenames were given to #use and #load commands;
4988  read_line() was buggy for short lines (2 characters or less).
4989- OCamlBrowser: now fully functional.
4990- Graphics library: fixed several bugs in event handling.
4991- Threads library: fixed preemption bug.
4992- Unix library: better handling of the underlying differences between
4993  sockets and regular file descriptors;
4994  added Unix.lockf and a better Unix.rename (thanks to Tracy Camp).
4995- LablTk library: fixed a bug in Fileinput
4996
4997
4998Objective Caml 3.04 (13 Dec 2001):
4999----------------------------------
5000
5001Type-checker:
5002- Allowed coercing self to the type of the current class, avoiding
5003  an obscure error message about "Self type cannot be unified..."
5004
5005Both compilers:
5006- Use OCAMLLIB environment variable to find standard library, falls
5007  back on CAMLLIB if not defined.
5008- Report out-of-range ASCII escapes in character or string literals
5009  such as "\256".
5010
5011Byte-code compiler:
5012- The -use-runtime and -make-runtime flags are back by popular demand
5013  (same behavior as in 3.02).
5014- Dynamic loading (of the C part of mixed Caml/C libraries): arrange that
5015  linking in -custom mode uses the static libraries for the C parts,
5016  not the shared libraries, for maximal robustness and compatibility with
5017  3.02.
5018
5019Native-code compiler:
5020- Fixed bug in link-time consistency checking.
5021
5022Tools:
5023- ocamlyacc: added parser debugging support (set OCAMLRUNPARAM=p to get
5024  a trace of the pushdown automaton actions).
5025- ocamlcp: was broken in 3.03 (Sys_error), fixed.
5026
5027Run-time system:
5028- More work on dynamic loading of the C part of mixed Caml/C libraries.
5029- On uncaught exception, flush output channels before printing exception
5030  message and backtrace.
5031- Corrected several errors in exception backtraces.
5032
5033Standard library:
5034- Pervasives: integer division and modulus are now fully specified
5035  on negative arguments (with round-towards-zero semantics).
5036- Pervasives.float_of_string: now raises Failure on ill-formed input.
5037- Pervasives: added useful float constants max_float, min_float, epsilon_float.
5038- printf functions in Printf and Format: added % formats for int32, nativeint,
5039  int64; "*" in width and precision specifications now supported
5040  (contributed by Thorsten Ohl).
5041- Added Hashtbl.copy, Stack.copy.
5042- Hashtbl: revised resizing strategy to avoid quadratic behavior
5043  on Hashtbl.add.
5044- New module MoreLabels providing labelized versions of modules
5045  Hashtbl, Map and Set.
5046- Pervasives.output_value and Marshal.to_* : improved hashing strategy
5047  for internal data structures, avoid excessive slowness on
5048  quasi-linearly-allocated inputs.
5049
5050Other libraries:
5051- Num: fixed bug in big integer exponentiation (Big_int.power_*).
5052
5053Windows port:
5054- New GUI for interactive toplevel (Jacob Navia).
5055- The Graphics library is now available for stand-alone executables
5056  (Jacob Navia).
5057- Unix library: improved reporting of system error codes.
5058- Fixed error in "globbing" of * and ? patterns on command line.
5059
5060Emacs mode: small fixes; special color highlighting for ocamldoc comments.
5061
5062License: added special exception to the LGPL'ed code (libraries and
5063  runtime system) allowing unrestricted linking, whether static or dynamic.
5064
5065
5066Objective Caml 3.03 ALPHA (12 Oct 2001):
5067----------------------------------------
5068
5069Language:
5070- Removed built-in syntactic sugar for streams and stream patterns
5071  [< ... >], now supported via CamlP4, which is now included in the
5072  distribution.
5073- Switched the default behaviour to labels mode (labels are compulsory),
5074  but allows omitting labels when a function application is complete.
5075  -nolabels mode is available but deprecated for programming.
5076  (See also scrapelabels and addlabels tools below.)
5077- Removed all labels in the standard libraries, except labltk.
5078  Labelized versions are kept for ArrayLabels, ListLabels, StringLabels
5079  and UnixLabels. "open StdLabels" gives access to the first three.
5080- Extended polymorphic variant type syntax, allowing union types and
5081  row abbreviations for both sub- and super-types. #t deprecated in types.
5082- See the Upgrading file for how to adapt to all the changes above.
5083
5084Type-checker:
5085- Fixed obscure bug in module typing causing the type-checker to loop
5086  on signatures of the form
5087        module type M
5088        module A: sig module type T = sig module T: M end end
5089        module B: A.T
5090- Improved efficiency of module type-checking via lazy computation of
5091  certain signature summary information.
5092- An empty polymorphic variant type is now an error.
5093
5094Both compilers:
5095- Fixed wrong code generated for "struct include M ... end" when M
5096  contains one or several "external" declarations.
5097
5098Byte-code compiler:
5099- Protect against VM stack overflow caused by module initialization code
5100  with many local variables.
5101- Support for dynamic loading of the C part of mixed Caml/C libraries.
5102- Removed the -use-runtime and -make-runtime flags, obsoleted by dynamic
5103  loading of C libraries.
5104
5105Native-code compiler:
5106- Attempt to recover gracefully from system stack overflow.  Currently
5107  works on x86 under Linux and BSD.
5108- Alpha: work around "as" bug in Tru64 5.1.
5109
5110Toplevel environment:
5111- Revised printing of inferred types and evaluation results
5112  so that an external printer (e.g. Camlp4's) can be hooked in.
5113
5114Tools:
5115- The CamlP4 pre-processor-pretty-printer is now included in the standard
5116  distribution.
5117- New tool ocamlmklib to help build mixed Caml/C libraries.
5118- New tool scrapelabels and addlabels, to either remove (non-optional)
5119  labels in interfaces, or automatically add them in the definitions.
5120  They provide easy transition from classic mode ocaml 3.02 sources,
5121  depending on whether you want to keep labels or not.
5122- ocamldep: added -pp option to handle preprocessed source files.
5123
5124Run-time system:
5125- Support for dynamic loading of the C part of mixed Caml/C libraries.
5126  Currently works under Linux, FreeBSD, Windows, Tru64, Solaris and Irix.
5127- Implemented registration of global C roots with a skip list,
5128  runs much faster when there are many global C roots.
5129- Autoconfiguration script: fixed wrong detection of Mac OS X; problem
5130  with the Sparc, gcc 3.0, and float alignment fixed.
5131
5132Standard library:
5133- Added Pervasives.flush_all to flush all opened output channels.
5134
5135Other libraries:
5136- All libraries revised to allow dynamic loading of the C part.
5137- Graphics under X Windows: revised event handling, should no longer lose
5138    mouse events between two calls to wait_next_event(); wait_next_event()
5139    now interruptible by signals.
5140- Bigarrays: fixed bug in marshaling of big arrays.
5141
5142Windows port:
5143- Fixed broken Unix.{get,set}sockopt*
5144
5145
5146
5147Objective Caml 3.02 (30 Jul 2001):
5148----------------------------------
5149
5150Both compilers:
5151- Fixed embarrassing bug in pattern-matching compilation
5152  (affected or-patterns containing variable bindings).
5153- More optimizations in pattern-matching compilation.
5154
5155Byte-code compiler:
5156- Protect against VM stack overflow caused by functions with many local
5157  variables.
5158
5159Native-code compiler:
5160- Removed re-sharing of string literals, causes too many surprises with
5161  in-place string modifications.
5162- Corrected wrong compilation of toplevel "include" statements.
5163- Fixed bug in runtime function "callbackN_exn".
5164- Signal handlers receive the conventional signal number as argument
5165  instead of the system signal number (same behavior as with the
5166  bytecode compiler).
5167- ARM port: fixed issue with immediate operand overflow in large functions.
5168
5169Toplevel environment:
5170- User-definer printers (for #install_printer) now receive as first argument
5171  the pretty-printer formatter where to print their second argument.
5172  Old printers (with only one argument) still supported for backward
5173  compatibility.
5174
5175Standard library:
5176- Module Hashtbl: added Hashtbl.fold.
5177
5178Other libraries:
5179- Dynlink: better error reporting in add_interfaces for missing .cmi files.
5180- Graphics: added more drawing functions (multiple points, polygons,
5181    multiple lines, splines).
5182- Bytecode threads: the module Unix is now thread-safe, ThreadUnix is
5183    deprecated.  Unix.exec* now resets standard descriptors to blocking mode.
5184- Native threads: fixed a context-switch-during-GC problem causing
5185    certain C runtime functions to fail, most notably input_value.
5186- Unix.inet_addr_of_string: call inet_aton() when available so as to
5187    handle correctly the address 255.255.255.255.
5188- Unix: added more getsockopt and setsockopt functions to get/set
5189    options that have values other than booleans.
5190- Num: added documentation for the Big_int module.
5191
5192Tools:
5193- ocamldep: fixed wrong dependency issue with nested modules.
5194
5195Run-time system:
5196- Removed floating-point error at start-up on some non-IEEE platforms
5197  (e.g. FreeBSD prior to 4.0R).
5198- Stack backtrace mechanism now works for threads that terminate on
5199  an uncaught exception.
5200
5201Auto-configuration:
5202- Updated config.guess and config.sub scripts, should recognize a greater
5203  number of recent platform.
5204
5205Windows port:
5206- Fixed broken Unix.waitpid.  Unix.file_descr can now be compared or hashed.
5207- Toplevel application: issue with spaces in name of stdlib directory fixed.
5208
5209MacOS 9 port:
5210- Removed the last traces of support for 68k
5211
5212
5213Objective Caml 3.01 (09 Mar 2001):
5214----------------------------------
5215
5216New language features:
5217- Variables are allowed in "or" patterns, e.g.
5218     match l with [t] | [_;t] -> ... t ...
5219- "include <structure expression>" to re-export all components of a
5220  structure inside another structure.
5221- Variance annotation on parameters of type declarations, e.g.
5222    type (+'a,-'b,'c) t (covariant in 'a, contravariant in 'b, invariant in 'c)
5223
5224New ports:
5225- Intel IA64/Itanium under Linux (including the native-code compiler).
5226- Cygwin under MS Windows.  This port is an alternative to the earlier
5227  Windows port of OCaml, which relied on MS compilers; the Cygwin
5228  Windows port does not need MS Visual C++ nor MASM, runs faster
5229  in bytecode, and has a better implementation of the Unix library,
5230  but currently lacks threads and COM component support.
5231
5232Type-checking:
5233- Relaxed "monomorphic restriction" on type constructors in a
5234  mutually-recursive type definition, e.g. the following is again allowed
5235    type u = C of int t | D of string t and 'a t = ...
5236- Fixed name-capture bug in "include SIG" and "SIG with ..." constructs.
5237- Improved implicit subtypes built by (... :> ty), closer to intuition.
5238- Several bug fixes in type-checking of variants.
5239- Typing of polymorphic variants is more restrictive:
5240   do not allow conjunctive types inside the same pattern matching.
5241   a type has either an upper bound, or all its tags are in the lower bound.
5242  This may break some programs (this breaks lablgl-0.94).
5243
5244Both compilers:
5245- Revised compilation of pattern matching.
5246- Option -I +<subdir> to search a subdirectory <subdir> of the standard
5247  library directory (i.e. write "ocamlc -I +labltk" instead of
5248  "ocamlc -I /usr/local/lib/ocaml/labltk").
5249- Option -warn-error to turn warnings into errors.
5250- Option -where to print the location of the standard library directory.
5251- Assertions are now type-checked even if the -noassert option is given,
5252  thus -noassert can no longe change the types of modules.
5253
5254Bytecode compiler and bytecode interpreter:
5255- Print stack backtrace when a program aborts due to an uncaught exception
5256  (requires compilation with -g and running with ocamlrun -b or
5257   OCAMLRUNPARAM="b=1").
5258
5259Native-code compiler:
5260- Better unboxing optimizations on the int32, int64, and nativeint types.
5261- Tail recursion preserved for functions having more parameters than
5262  available registers (but tail calls to other functions are still
5263  turned off if parameters do not fit entirely in registers).
5264- Fixed name-capture bug in function inlining.
5265- Improved spilling/reloading strategy for conditionals.
5266- IA32, Alpha: better alignment of branch targets.
5267- Removed spurious dependency on the -lcurses library.
5268
5269Toplevel environment:
5270- Revised handling of top-level value definitions, allows reclaimation
5271  of definitions that are shadowed by later definitions with the same names.
5272  (E.g. "let x = <big list>;; let x = 1;;" allows <big list> to be reclaimed.)
5273- Revised the tracing facility so that for standard library functions,
5274  only calls from user code are traced, not calls from the system.
5275- Added a "*" prompt when within a comment.
5276
5277Runtime system:
5278- Fixed portability issue on bcopy() vs memmove(), affecting Linux RedHat 7.0
5279  in particular.
5280- Structural comparisons (=, <>, <, <=, >, >=, compare) reimplemented
5281  so as to avoid overflowing the C stack.
5282- Input/output functions: arrange so that reads and writes on closed
5283  in_channel or out_channel raise Sys_error immediately.
5284
5285Standard library:
5286- Module Gc: changed some counters to float in order to avoid overflow;
5287    added alarms
5288- Module Hashtbl: added Hashtbl.replace.
5289- Module Int64: added bits_of_float, float_of_bits (access to IEEE 754
5290    representation of floats).
5291- Module List:  List.partition now tail-rec;
5292    improved memory behavior of List.stable_sort.
5293- Module Nativeint: added Nativeint.size (number of bits in a nativeint).
5294- Module Obj: fixed incorrect resizing of float arrays in Obj.resize.
5295- Module Pervasives: added float constants "infinity", "neg_infinity", "nan";
5296    added a "classify_float" function to test a float for NaN, infinity, etc.
5297- Pervasives.input_value: fixed bug affecting shared custom objects.
5298- Pervasives.output_value: fixed size bug affecting "int64" values.
5299- Pervasives.int_of_string, {Int32,Int64,Nativeint}.of_string:
5300  fixed bug causing bad digits to be accepted without error.
5301- Module Random: added get_state and set_state to checkpoint the generator.
5302- Module Sys: signal handling functions are passed the system-independent
5303  signal number rather than the raw system signal number whenever possible.
5304- Module Weak: added Weak.get_copy.
5305
5306Other libraries:
5307- Bigarray: added Bigarray.reshape to take a view of the elements of a
5308  bigarray with different dimensions or number of dimensions;
5309  fixed bug causing "get" operations to be unavailable in custom
5310  toplevels including Bigarray.
5311- Dynlink: raise an error instead of crashing when the loaded module
5312  refers to the not-yet-initialized module performing a dynlink operation.
5313- Bytecode threads: added a thread-safe version of the Marshal module;
5314    fixed a rare GC bug in the thread scheduler.
5315- POSIX threads: fixed compilation problem with threads.cmxa.
5316- Both thread libraries: better tail-recursion in Event.sync.
5317- Num library: fixed bug in square roots (Nat.sqrt_nat, Big_int.sqrt_big_int).
5318
5319Tools:
5320- ocamldep: fixed missing dependencies on labels of record patterns and
5321    record construction operations
5322
5323Win32 port:
5324- Unix.waitpid now implements the WNOHANG option.
5325
5326Mac OS ports:
5327- Mac OS X public beta is supported.
5328- Int64.format works on Mac OS 8/9.
5329
5330
5331Objective Caml 3.00 (25 Apr 2000):
5332----------------------------------
5333
5334Language:
5335- OCaml/OLabl merger:
5336  * Support for labeled and optional arguments for functions and classes.
5337  * Support for variant types (sum types compared by structure).
5338  See tutorial (chapter 2 of the OCaml manual) for more information.
5339- Syntactic change: "?" in stream error handlers changed to "??".
5340- Added exception renaming in structures (exception E = F).
5341- (OCaml 2.99/OLabl users only) Label syntax changed to preserve
5342  backward compatibility with 2.0x (labeled function application
5343  is f ~lbl:arg instead of f lbl:arg).  A tool is provided to help
5344  convert labelized programs to OCaml 3.00.
5345
5346Both compilers:
5347- Option -labels to select commuting label mode (labels are mandatory,
5348  but labeled arguments can be passed in a different order than in
5349  the definition of the function; in default mode, labels may be omitted,
5350  but argument reordering is only allowed for optional arguments).
5351- Libraries (.cma and .cmxa files) now "remember" C libraries given
5352  at library construction time, and add them back at link time.
5353  Allows linking with e.g. just unix.cma instead of
5354  unix.cma -custom -cclib -lunix
5355- Revised printing of error messages, now use Format.fprintf; no visible
5356  difference for users, but could facilitate internationalization later.
5357- Fixed bug in unboxing of records containing only floats.
5358- Fixed typing bug involving applicative functors as components of modules.
5359- Better error message for inconsistencies between compiled interfaces.
5360
5361Bytecode compiler:
5362- New "modular" format for bytecode executables; no visible differences
5363  for users, but will facilitate further extensions later.
5364- Fixed problems in signal handling.
5365
5366Native-code compiler:
5367- Profiling support on x86 under FreeBSD
5368- Open-coding and unboxing optimizations for the new integer types
5369  int32, int64, nativeint, and for bigarrays.
5370- Fixed instruction selection bug with "raise" appearing in arguments
5371  of strict operators, e.g. "1 + raise E".
5372- Better error message when linking incomplete/incorrectly ordered set
5373  of .cmx files.
5374- Optimized scanning of global roots during GC, can reduce total running
5375  time by up to 8% on GC-intensive programs.
5376
5377Interactive toplevel:
5378- Better printing of exceptions, including arguments, when possible.
5379- Fixed rare GC bug occurring during interpretation of scripts.
5380- Added consistency checks between interfaces and implementations
5381  during #load.
5382
5383Run-time system:
5384- Added support for "custom" heap blocks (heap blocks carrying
5385  C functions for finalization, comparison, hashing, serialization
5386  and deserialization).
5387- Support for finalisation functions written in Caml.
5388
5389Standard library:
5390- New modules Int32, Int64, Nativeint for 32-bit, 64-bit and
5391  platform-native integers
5392- Module Array: added Array.sort, Array.stable_sort.
5393- Module Gc: added Gc.finalise to attach Caml finalisation functions to
5394  arbitrary heap-allocated data.
5395- Module Hashtbl: do not bomb when resizing very large table.
5396- Module Lazy: raise Lazy.Undefined when a lazy evaluation needs itself.
5397- Module List: added List.sort, List.stable_sort; fixed bug in List.rev_map2.
5398- Module Map: added mapi (iteration with key and data).
5399- Module Set: added iterators for_all, exists, filter, partition.
5400- Module Sort: still here but deprecated in favor of new sorting functions
5401  in Array and List.
5402- Module Stack: added Stack.top
5403- Module String: fixed boundary condition on String.rindex_from
5404- Added labels on function arguments where appropriate.
5405
5406New libraries and tools:
5407- ocamlbrowser: graphical browser for OCaml sources and compiled interfaces,
5408  supports cross-referencing, editing, running the toplevel.
5409- LablTK: GUI toolkit based on TK, using labeled and optional arguments,
5410  easier to use than CamlTK.
5411- Bigarray: large, multi-dimensional numerical arrays, facilitate
5412  interfacing with C/Fortran numerical code, efficient support for
5413  advanced array operations such as slicing and memory-mapping of files.
5414
5415Other libraries:
5416- Bytecode threads: timer-based preemption was broken, works back again;
5417  fixed bug in Pervasives.input_line; exported Thread.yield.
5418- System threads: several GC / reentrancy bugs fixed in buffered I/O
5419  and Unix I/O; revised Thread.join implementation for strict POSIX
5420  conformance; exported Thread.yield.
5421- Graphics: added support for double buffering; added, current_x, current_y,
5422  rmoveto, rlineto, and draw_rect.
5423- Num: fixed bug in Num.float_of_num.
5424- Str: worked around potential symbol conflicts with C standard library.
5425- Dbm: fixed bug with Dbm.iter on empty database.
5426
5427New or updated ports:
5428- Alpha/Digital Unix: lifted 256M limitation on total memory space
5429  induced by -taso
5430- Port to AIX 4.3 on PowerPC
5431- Port to HPUX 10 on HPPA
5432- Deprecated 680x0 / SunOS port
5433
5434Macintosh port:
5435- Implemented the Unix and Thread libraries.
5436- The toplevel application does not work on 68k Macintoshes; maybe
5437  later if there's a demand.
5438- Added a new tool, ocamlmkappli, to build an application from a
5439  program written in O'Caml.
5440
5441
5442Objective Caml 2.04 (26 Nov 1999):
5443----------------------------------
5444
5445- C interface: corrected inconsistent change in the CAMLparam* macros.
5446- Fixed internal error in ocamlc -g.
5447- Fixed type-checking of "S with ...", where S is a module type name
5448  abbreviating another module type name.
5449- ocamldep: fixed stdout/stderr mismatch after failing on one file.
5450- Random.self_init more random.
5451- Windows port:
5452  - Toplevel application: fixed spurious crash on exit.
5453  - Native-code compiler: fixed bug in assembling certain
5454    floating-point constants (masm doesn't grok 2e5, wants 2.0e5).
5455
5456Objective Caml 2.03 (19 Nov 1999):
5457----------------------------------
5458
5459New ports:
5460- Ported to BeOS / Intel x86 (bytecode and native-code).
5461- BSD / Intel x86 port now supports both a.out and ELF binary formats.
5462- Added support for {Net,Open}BSD / Alpha.
5463- Revamped Rhapsody port, now works on MacOS X server.
5464
5465Syntax:
5466- Warning for "(*)" and "*)" outside comment.
5467- Removed "#line LINENO", too ambiguous with a method invocation;
5468  the equivalent "# LINENO" is still supported.
5469
5470Typing:
5471- When an incomplete pattern-matching is detected, report also a
5472  value or value template that is not covered by the cases of
5473  the pattern-matching.
5474- Several bugs in class type matching and in type error reporting fixed.
5475- Added an option -rectypes to support general recursive types,
5476  not just those involving object types.
5477
5478Bytecode compiler:
5479- Minor cleanups in the bytecode emitter.
5480- Do not remove "let x = y" bindings in -g mode; makes it easier to
5481  debug the code.
5482
5483Native-code compiler:
5484- Fixed bug in grouping of allocations performed in the same basic block.
5485- Fixed bug in constant propagation involving expressions containing
5486  side-effects.
5487- Fixed incorrect code generation for "for" loops whose upper bound is
5488  a reference assigned inside the loop.
5489- MIPS code generator: work around a bug in the IRIX 6 assembler.
5490
5491Toplevel:
5492- Fixed incorrect redirection of standard formatter to stderr
5493  while executing toplevel scripts.
5494
5495Standard library:
5496- Added List.rev_map, List.rev_map2.
5497- Documentation of List functions now says which functions are
5498  tail-rec, and how much stack space is needed for non-tailrec functions.
5499- Wrong type for Printf.bprintf fixed.
5500- Fixed weird behavior of Printf.sprintf and Printf.bprintf in case of
5501  partial applications.
5502- Added Random.self_init, which initializes the PRNG from the system date.
5503- Sort.array: serious bugs fixed.
5504- Stream.count: fixed incorrect behavior with ocamlopt.
5505
5506Run-time system and external interface:
5507- Fixed weird behavior of signal handlers w.r.t. signal masks and exceptions
5508  raised from the signal handler.
5509- Fixed bug in the callback*_exn() functions.
5510
5511Debugger:
5512- Fixed wrong printing of float record fields and elements of float arrays.
5513- Supports identifiers starting with '_'.
5514
5515Profiler:
5516- Handles .mli files, so ocamlcp can be used to replace ocamlc (e.g. in a
5517  makefile).
5518- Now works on programs that use stream expressions and stream parsers.
5519
5520Other libraries:
5521- Graphics: under X11, treat all mouse buttons equally; fixed problem
5522  with current font reverting to the default font when the graphics
5523  window is resized.
5524- Str: fixed reentrancy bugs in Str.replace and Str.full_split.
5525- Bytecode threads: set standard I/O descriptors to non-blocking mode.
5526- OS threads: revised implementation of Thread.wait_signal.
5527- All threads: added Event.wrap_abort, Event.choose [].
5528- Unix.localtime, Unix.gmtime: check for errors.
5529- Unix.create_process: now supports arbitrary redirections of std descriptors.
5530- Added Unix.open_process_full.
5531- Implemented Unix.chmod under Windows.
5532- Big_int.square_big_int now gives the proper sign to its result.
5533
5534Others:
5535- ocamldep: don't stop at first error, skip to next file.
5536- Emacs mode: updated with Garrigue and Zimmerman's snapshot of 1999/10/18.
5537- configure script: added -prefix option.
5538- Windows toplevel application: fixed problem with graphics library
5539  not loading properly.
5540
5541
5542Objective Caml 2.02 (04 Mar 1999):
5543----------------------------------
5544
5545* Type system:
5546  - Check that all components of a signature have unique names.
5547  - Fixed bug in signature matching involving a type component and
5548    a module component, both sharing an abstract type.
5549  - Bug involving recursive classes constrained by a class type fixed.
5550  - Fixed bugs in printing class types and in printing unification errors.
5551
5552* Compilation:
5553  - Changed compilation scheme for "{r with lbl = e}" when r has many fields
5554    so as to avoid code size explosion.
5555
5556* Native-code compiler:
5557  - Better constant propagation in boolean expressions and in conditionals.
5558  - Removal of unused arguments during function inlining.
5559  - Eliminated redundant tagging/untagging in bit shifts.
5560  - Static allocation of closures for functions without free variables,
5561    reduces the size of initialization code.
5562  - Revised compilation scheme for definitions at top level of compilation
5563    units, so that top level functions have no free variables.
5564  - Coalesced multiple allocations of heap blocks inside one expression
5565    (e.g. x :: y :: z allocates the two conses in one step).
5566  - Ix86: better handling of large integer constants in instruction selection.
5567  - MIPS: fixed wrong asm generated for String.length "literal".
5568
5569* Standard library:
5570  - Added the "ignore" primitive function, which just throws away its
5571    argument and returns "()".  It allows to write
5572    "ignore(f x); y" if "f x" doesn't have type unit and you don't
5573    want the warning caused by "f x; y".
5574  - Added the "Buffer" module (extensible string buffers).
5575  - Module Format: added formatting to buffers and to strings.
5576  - Added "mem" functions (membership test) to Hashtbl and Map.
5577  - Module List: added find, filter, partition.
5578    Renamed remove and removeq to remove_assoc and remove_assq.
5579  - Module Marshal: fixed bug in marshaling functions when passed functional
5580    values defined by mutual recursion with other functions.
5581  - Module Printf: added Printf.bprintf (print to extensible buffer);
5582    added %i format as synonymous for %d (as per the docs).
5583  - Module Sort: added Sort.array (Quicksort).
5584
5585* Runtime system:
5586  - New callback functions for callbacks with arbitrary many arguments
5587    and for catching Caml exceptions escaping from a callback.
5588
5589* The ocamldep dependency generator: now performs full parsing of the
5590    sources, taking into account the scope of module bindings.
5591
5592* The ocamlyacc parser generator: fixed sentinel error causing wrong
5593    tables to be generated in some cases.
5594
5595* The str library:
5596  - Added split_delim, full_split as variants of split that control
5597    more precisely what happens to delimiters.
5598  - Added replace_matched for separate matching and replacement operations.
5599
5600* The graphics library:
5601  - Bypass color lookup for 16 bpp and 32 bpp direct-color displays.
5602  - Larger color cache.
5603
5604* The thread library:
5605  - Bytecode threads: more clever use of non-blocking I/O, makes I/O
5606    operations faster.
5607  - POSIX threads: gcc-ism removed, should now compile on any ANSI C compiler.
5608  - Both: avoid memory leak in the Event module when a communication
5609    offer is never selected.
5610
5611* The Unix library:
5612  - Fixed inversion of ctime and mtime in Unix.stat, Unix.fstat, Unix.lstat.
5613  - Unix.establish_connection: properly reclaim socket if connect fails.
5614
5615* The DBM library: no longer crashes when calling Dbm.close twice.
5616
5617* Emacs mode:
5618  - Updated with Garrigue and Zimmerman's latest version.
5619  - Now include an "ocamltags" script for using etags on OCaml sources.
5620
5621* Win32 port:
5622  - Fixed end-of-line bug in ocamlcp causing problems with generated sources.
5623
5624
5625Objective Caml 2.01 (09 Dec 1998):
5626----------------------------------
5627
5628* Typing:
5629  - Added warning for expressions of the form "a; b" where a does not have
5630    type "unit"; catches silly mistake such as
5631    "record.lbl = newval; ..." instead of "record.lbl <- newval; ...".
5632  - Typing bug in "let module" fixed.
5633
5634* Compilation:
5635  - Fixed bug in compilation of recursive and mutually recursive classes.
5636  - Option -w to turn specific warnings on/off.
5637  - Option -cc to choose the C compiler used with ocamlc -custom and ocamlopt.
5638
5639* Bytecode compiler and bytecode interpreter:
5640  - Intel x86: removed asm declaration causing "fixed or forbidden register
5641    spilled" error with egcs and gcc 2.8 (but not with gcc 2.7, go figure).
5642  - Revised handling of debugging information, allows faster linking with -g.
5643
5644* Native-code compiler:
5645  - Fixed bugs in integer constant propagation.
5646  - Out-of-bound accesses in array and strings now raise an Invalid_argument
5647    exception (like the bytecode system) instead of stopping the program.
5648  - Corrected scheduling of bound checks.
5649  - Port to the StrongARM under Linux (e.g. Corel Netwinder).
5650  - I386: fixed bug in profiled code (ocamlopt -p).
5651  - Mips: switched to -n32 model under IRIX; dropped the Ultrix port.
5652  - Sparc: simplified the addressing modes, allows for better scheduling.
5653  - Fixed calling convention bug for Pervasives.modf.
5654
5655* Toplevel:
5656  - #trace works again.
5657  - ocamlmktop: use matching ocamlc, not any ocamlc from the search path.
5658
5659* Memory management:
5660  - Fixed bug in heap expansion that could cause the GC to loop.
5661
5662* C interface:
5663  - New macros CAMLparam... and CAMLlocal... to simplify the handling
5664    of local roots in C code.
5665  - Simplified procedure for allocating and filling Caml blocks from C.
5666  - Declaration of string_length in <caml/mlvalues.h>.
5667
5668* Standard library:
5669  - Module Format: added {get,set}_all_formatter_output_functions,
5670    formatter_of_out_channel, and the control sequence @<n> in printf.
5671  - Module List: added mem_assoc, mem_assq, remove, removeq.
5672  - Module Pervasives: added float_of_int (synonymous for float),
5673    int_of_float (truncate), int_of_char (Char.code), char_of_int (Char.chr),
5674    bool_of_string.
5675  - Module String: added contains, contains_from, rcontains_from.
5676
5677* Unix library:
5678  - Unix.lockf: added F_RLOCK, F_TRLOCK; use POSIX locks whenever available.
5679  - Unix.tc{get,set}attr: added non-standard speeds 57600, 115200, 230400.
5680  - Unix.chroot: added.
5681
5682* Threads:
5683  - Bytecode threads: improved speed of I/O scheduling.
5684  - Native threads: fixed a bug involving signals and exceptions
5685    generated from C.
5686
5687* The "str" library:
5688  - Added Str.string_partial_match.
5689  - Bumped size of internal stack.
5690
5691* ocamlyacc: emit correct '# lineno' directive for prelude part of .mly file.
5692
5693* Emacs editing mode: updated with Jacques Garrigue's newest code.
5694
5695* Windows port:
5696  - Added support for the "-cclib -lfoo" option (instead of
5697     -cclib /full/path/libfoo.lib as before).
5698  - Threads: fixed a bug at initialization time.
5699
5700* Macintosh port: source code for Macintosh application merged in.
5701
5702
5703Objective Caml 2.00 (19 Aug 1998):
5704----------------------------------
5705
5706* Language:
5707  - New class language.  See http://caml.inria.fr/ocaml/refman/
5708    for a tutorial (chapter 2) and for the reference manual (section 4.9).
5709  - Local module definitions "let module X = <module-expr> in <expr>".
5710  - Record copying with update "{r with lbl1 = expr1; ...}".
5711  - Array patterns "[|pat1; ...;patN|]" in pattern-matchings.
5712  - New reserved keywords: "object", "initializer".
5713  - No longer reserved: "closed", "protected".
5714
5715* Bytecode compiler:
5716  - Use the same compact memory representations for float arrays, float
5717    records and recursive closures as the native-code compiler.
5718  - More type-dependent optimizations.
5719  - Added the -use_runtime and -make_runtime flags to build separately
5720    and reuse afterwards custom runtime systems
5721    (inspired by Fabrice Le Fessant's patch).
5722
5723* Native-code compiler:
5724  - Cross-module constant propagation of integer constants.
5725  - More type-dependent optimizations.
5726  - More compact code generated for "let rec" over data structures.
5727  - Better code generated for "for" loops (test at bottom of code).
5728  - More aggressive scheduling of stores.
5729  - Added -p option for time profiling with gprof
5730    (fully supported on Intel x86/Linux and Alpha/Digital Unix only)
5731    (inspired by Aleksey Nogin's patch).
5732  - A case of bad spilling with high register pressure fixed.
5733  - Fixed GC bug when GC called from C without active Caml code.
5734  - Alpha: $gp handling revised to follow Alpha's standard conventions,
5735    allow running "atom" and "pixie" on ocamlopt-generated binaries.
5736  - Intel x86: use movzbl and movsbl systematically to load 8-bit and 16-bit
5737    quantities, no more hacks with partial registers (better for the
5738    Pentium Pro, worse for the Pentium).
5739  - PowerPC: more aggressive scheduling of return address reloading.
5740  - Sparc: scheduling bug related to register pairs fixed.
5741
5742* Runtime system:
5743  - Better printing of uncaught exceptions (print a fully qualified
5744    name whenever possible).
5745
5746* New ports:
5747  - Cray T3E (bytecode only) (in collaboration with CEA).
5748  - PowerMac under Rhapsody.
5749  - SparcStations under Linux.
5750
5751* Standard library:
5752  - Added set_binary_mode_in and set_binary_mode_out in Pervasives
5753    to toggle open channels between text and binary modes.
5754  - output_value and input_value check that the given channel is in
5755    binary mode.
5756  - input_value no longer fails on very large marshalled data (> 16 Mbytes).
5757  - Module Arg: added option Rest.
5758  - Module Filename: temp_file no longer loops if temp dir doesn't exist.
5759  - Module List: added rev_append (tail-rec alternative to @).
5760  - Module Set: tell the truth about "elements" returning a sorted list;
5761    added min_elt, max_elt, singleton.
5762  - Module Sys: added Sys.time for simple measuring of CPU time.
5763
5764* ocamllex:
5765  - Check for overflow when generating the tables for the automaton.
5766  - Error messages in generated .ml file now point to .mll source.
5767  - Added "let <id> = <regexp>" to name regular expressions
5768    (inspired by Christian Lindig's patch).
5769
5770* ocamlyacc:
5771  - Better error recovery in presence of EOF tokens.
5772  - Error messages in generated .ml file now point to .mly source.
5773  - Generated .ml file now type-safe even without the generated .mli file.
5774
5775* The Unix library:
5776  - Use float instead of int to represent Unix times (number of seconds
5777    from the epoch).  This fixes a year 2005 problem on 32-bit platforms.
5778    Functions affected: stat, lstat, fstat, time, gmtime, localtime,
5779    mktime, utimes.
5780  - Added putenv.
5781  - Better handling of "unknown" error codes (EUNKNOWNERR).
5782  - Fixed endianness bug in getservbyport.
5783  - win32unix (the Win32 implementation of the Unix library) now has
5784    the same interface as the unix implementation, this allows exchange
5785    of compiled .cmo and .cmi files between Unix and Win32.
5786
5787* The thread libraries:
5788  - Bytecode threads: bug with escaping exceptions fixed.
5789  - System threads (POSIX, Win32): malloc/free bug fixed; signal bug fixed.
5790  - Both: added Thread.wait_signal to wait synchronously for signals.
5791
5792* The graph library: bigger color cache.
5793
5794* The str library: added Str.quote, Str.regexp_string,
5795  Str.regexp_string_case_fold.
5796
5797* Emacs mode:
5798  - Fixed bug with paragraph fill.
5799  - Fixed bug with next-error under Emacs 20.
5800
5801
5802Objective Caml 1.07 (11 Dec 1997):
5803----------------------------------
5804
5805* Native-code compiler:
5806  - Revised interface between generated code and GC, fixes serious GC
5807    problems with signals and native threads.
5808  - Added "-thread" option for compatibility with ocamlc.
5809
5810* Debugger: correctly print instance variables of objects.
5811
5812* Run-time system: ported to OpenBSD.
5813
5814* Standard library: fixed wrong interface for Marshal.to_buffer and
5815  Obj.unmarshal.
5816
5817* Num library: added Intel x86 optimized asm code (courtesy of
5818  Bernard Serpette).
5819
5820* Thread libraries:
5821  - Native threads: fixed GC bugs and installation procedure.
5822  - Bytecode threads: fixed problem with "Marshal" module.
5823  - Both: added Event.always.
5824
5825* MS Windows port: better handling of long command lines in Sys.command
5826
5827Objective Caml 1.06 (18 Nov 1997):
5828----------------------------------
5829
5830* Language:
5831  - Added two new keywords: "assert" (check assertion) and "lazy"
5832    (delay evaluation).
5833  - Allow identifiers to start with "_" (such identifiers are treated
5834    as lowercase idents).
5835
5836* Objects:
5837  - Added "protected" methods (visible only from subclasses, can be hidden
5838    in class type declared in module signature).
5839  - Objects can be compared using generic comparison functions.
5840  - Fixed compilation of partial application of object constructors.
5841
5842* Type system:
5843  - Occur-check now more strict (all recursions must traverse an object).
5844  - A few bugs fixed.
5845
5846* Run-time system:
5847  - A heap compactor was implemented, so long-running programs can now
5848    fight fragmentation.
5849  - The meaning of the "space_overhead" parameter has changed.
5850  - The macros Push_roots and Pop_roots are superseded by Begin_roots* and
5851    End_roots.
5852  - Bytecode executable includes list of primitives used, avoids crashes
5853    on version mismatch.
5854  - Reduced startup overhead for marshalling, much faster marshalling of
5855    small objects.
5856  - New exception Stack_overflow distinct from Out_of_memory.
5857  - Maximum stack size configurable.
5858  - I/O revised for compatibility with compactor and with native threads.
5859  - All C code ANSIfied (new-style function declarations, etc).
5860  - Threaded code work on all 64-bit processors, not just Alpha/Digital Unix.
5861  - Better printing of uncaught exceptions.
5862
5863* Both compilers:
5864  - Parsing: more detailed reporting of syntax errors (e.g. shows
5865    unmatched opening parenthesis on missing closing parenthesis).
5866  - Check consistency between interfaces (.cmi).
5867  - Revised rules for determining dependencies between modules.
5868  - Options "-verbose" for printing calls to C compiler, "-noassert"
5869    for turning assertion checks off.
5870
5871* Native-code compiler:
5872  - Machine-dependent parts rewritten using inheritance instead of
5873    parameterized modules.
5874  - GC bug in value let rec fixed.
5875  - Port to Linux/Alpha.
5876  - Sparc: cleaned up use of %g registers, now compatible with Solaris threads.
5877
5878* Top-level interactive system:
5879  - Can execute Caml script files given on command line.
5880  - Reads commands from ./.ocamlinit on startup.
5881  - Now thread-compatible.
5882
5883* Standard library:
5884  - New library module: Lazy (delayed computations).
5885  - New library module: Marshal.  Allows marshalling to strings and
5886    transmission of closures between identical programs (SPMD parallelism).
5887  - Filename: "is_absolute" is superseded by "is_implicit" and "is_relative".
5888    To adapt old programs, change "is_absolute x" to "not (is_implicit x)"
5889    (but the new "is_relative" is NOT the opposite of the old "is_absolute").
5890  - Array, Hashtbl, List, Map, Queue, Set, Stack, Stream:
5891    the "iter" functions now take as argument a unit-returning function.
5892  - Format: added "printf" interface to the formatter (see the documentation).
5893    Revised behaviour of simple boxes: no more than one new line is output
5894    when consecutive break hints should lead to multiple line breaks.
5895  - Stream: revised implementation, renamed Parse_failure to Failure and
5896    Parse_error to Error (don't you love gratuitous changes?).
5897  - String: added index, rindex, index_from, rindex_from.
5898  - Array: added mapi, iteri, fold_left, fold_right, init.
5899  - Added Map.map, Set.subset, Printexc.to_string.
5900
5901* ocamllex: lexers generated by ocamllex can now handle all characters,
5902  including '\000'.
5903
5904* ocamlyacc: fixed bug with function closures returned by parser rules.
5905
5906* Debugger:
5907  - Revised generation of events.
5908  - Break on function entrance.
5909  - New commands start/previous.
5910  - The command loadprinter now try to recursively load required
5911    modules.
5912  - Numerous small fixes.
5913
5914* External libraries:
5915  - systhreads: can now use POSIX threads; POSIX and Win32 threads are
5916    now supported by the native-code compiler.
5917  - dbm and graph: work in native code.
5918  - num: fixed bug in Nat.nat_of_string.
5919  - str: fixed deallocation bug with case folding.
5920  - win32unix: use Win32 handles instead of (buggy) VC++ emulation of Unix
5921    file handles; added gettimeofday.
5922
5923* Emacs editing mode and debugger interface updated to July '97 version.
5924
5925Objective Caml 1.05 (21 Mar 1997):
5926----------------------------------
5927
5928* Typing: fixed several bugs causing spurious type errors.
5929
5930* Native-code compiler: fixed instruction selection bug causing GC to
5931see ill-formed pointers; fixed callbacks to support invocation from a
5932main program in C.
5933
5934* Standard library: fixed String.lowercase; Weak now resists integers.
5935
5936* Toplevel: multiple phrases without intermediate ";;" now really supported;
5937fixed value printing problems where the wrong printer was selected.
5938
5939* Debugger: fixed printing problem with local references; revised
5940handling of checkpoints; various other small fixes.
5941
5942* Macintosh port: fixed signed division problem in bytecomp/emitcode.ml
5943
5944Objective Caml 1.04 (11 Mar 1997):
5945----------------------------------
5946
5947* Replay debugger ported from Caml Light; added debugger support in
5948  compiler (option -g) and runtime system. Debugger is alpha-quality
5949  and needs testing.
5950
5951* Parsing:
5952  - Support for "# linenum" directives.
5953  - At toplevel, allow several phrases without intermediate ";;".
5954
5955* Typing:
5956  - Allow constraints on datatype parameters, e.g.
5957    type 'a foo = ... constraint 'a = 'b * 'c.
5958  - Fixed bug in signature matching in presence of free type variables '_a.
5959  - Extensive cleanup of internals of type inference.
5960
5961* Native-code compilation:
5962  - Inlining of small functions at point of call (fairly conservative).
5963  - MIPS code generator ported to SGI IRIX 6.
5964  - Better code generated for large integer constants.
5965  - Check for urgent GC when allocating large objects in major heap.
5966  - PowerPC port: better scheduling, reduced TOC consumption.
5967  - HPPA port: handle long conditional branches gracefully,
5968    several span-dependent bugs fixed.
5969
5970* Standard library:
5971  - More floating-point functions (all ANSI C float functions now available).
5972  - Hashtbl: added functorial interface (allow providing own equality
5973    and hash functions); rehash when resizing, avoid memory leak on
5974    Hashtbl.remove.
5975  - Added Char.uppercase, Char.lowercase, String.uppercase, String.lowercase,
5976    String.capitalize, String.uncapitalize.
5977  - New module Weak for manipulating weak pointers.
5978  - New module Callback for registering closures and exceptions to be
5979    used from C.
5980
5981* Foreign interface:
5982  - Better support for callbacks (C calling Caml), exception raising
5983    from C, and main() in C. Added function to remove a global root.
5984  - Option -output-obj to package Caml code as a C library.
5985
5986* Thread library: fixed bug in timed_read and timed_write operations;
5987  Lexing.from_function and Lexing.from_channel now reentrant.
5988
5989* Unix interface: renamed EACCESS to EACCES (the POSIX name); added setsid;
5990  fixed bug in inet_addr_of_string for 64-bit platforms.
5991
5992* Ocamlyacc: default error function no longer prevents error recovery.
5993
5994* Ocamllex: fixed reentrancy problem w.r.t. exceptions during refill;
5995  fixed output problem (\r\r\n) under Win32.
5996
5997* Macintosh port:
5998  - The makefiles are provided for compiling and installing O'Caml on
5999    a Macintosh with MPW 3.4.1.
6000  - An application with the toplevel in a window is forthcoming.
6001
6002* Windows NT/95 port: updated toplevel GUI to that of Caml Light 0.73.
6003
6004* Emacs editing mode and debugger interface included in distribution.
6005
6006
6007Objective Caml 1.03 (29 Oct 1996):
6008----------------------------------
6009
6010* Typing:
6011  - bug with type names escaping their scope via unification with
6012    non-generalized type variables '_a completely fixed;
6013  - fixed bug in occur check : it was too restrictive;
6014  - fixed bug of coercion operators;
6015  - check that no two types of the same name are generated in a module
6016    (there was no check for classes);
6017  - "#install_printer" works again;
6018  - fixed bug in printing of subtyping errors;
6019  - in class interfaces, construct "method m" (without type) change
6020    the status of method m from abstract to concrete;
6021  - in a recursive definition of class interfaces, a class can now
6022    inherit from a previous class;
6023  - typing of a method make use of an eventual previously given type
6024    of this method, yielding clearer type errors.
6025
6026* Compilation (ocamlc and ocamlopt):
6027  - fixed bug in compilation of classes.
6028
6029* Native-code compilation:
6030  - optimization of functions taking tuples of arguments;
6031  - code emitter for the Motorola 680x0 processors (retrocomputing week);
6032  - Alpha/OSF1: generate frame descriptors, avoids crashes when e.g.
6033    exp() or log() cause a domain error; fixed bug with
6034    String.length "literal";
6035  - Sparc, Mips, HPPA: removed marking of scanned stack frames
6036    (benefits do not outweight cost).
6037
6038* Standard library:
6039  - Arg.parse now prints documentation for command-line options;
6040  - I/O buffers (types in_channel and out_channel) now heap-allocated,
6041    avoids crashing when closing a channel several times;
6042  - Overflow bug in compare() fixed;
6043  - GC bug in raising Sys_error from I/O functions fixed;
6044  - Parsing.symbol_start works even for epsilon productions.
6045
6046* Foreign interface: main() in C now working, fixed bug in library
6047  order at link time.
6048
6049* Thread library: guard against calling thread functions before Thread.create.
6050
6051* Unix library: fixed getsockopt, setsockopt, open_process_{in,out}.
6052
6053* Perl-free, cpp-free, cholesterol-free installation procedure.
6054
6055
6056Objective Caml 1.02 (27 Sep 1996):
6057----------------------------------
6058
6059* Typing:
6060  - fixed bug with type names escaping their scope via unification
6061    with non-generalized type variables '_a;
6062  - keep #class abbreviations longer;
6063  - faster checking of well-formed abbreviation definitions;
6064  - stricter checking of "with" constraints over signatures (arity
6065    mismatch, overriding of an already manifest type).
6066
6067* Compilation (ocamlc and ocamlopt):
6068  - fixed bug in compilation of recursive classes;
6069  - [|...|] and let...rec... allowed inside definitions of recursive
6070    data structures;
6071
6072* Bytecode compilation: fixed overflow in linker for programs with
6073  more than 65535 globals and constants.
6074
6075* Native-code compilation:
6076  - ocamlopt ported to HPPA under HP/UX, Intel x86 under Solaris 2,
6077    PowerMacintosh under MkLinux;
6078  - fixed two bugs related to floating-point arrays (one with "t array"
6079    where t is an abstract type implemented as float, one with
6080    comparison between two float arrays on 32 bit platforms);
6081  - fixed reloading/spilling problem causing non-termination of
6082    register allocation;
6083  - fixed bugs in handling of () causing loss of tail recursion;
6084  - fixed reloading bug in indirect calls.
6085
6086* Windows NT/95 port:
6087  - complete port of the threads library (Pascal Cuoq);
6088  - partial port of the Unix library (Pascal Cuoq);
6089  - expansion of *, ? and @ on the command line.
6090
6091* Standard library:
6092  - bug in in List.exists2 fixed;
6093  - bug in "Random.int n" for very large n on 64-bit machines fixed;
6094  - module Format: added a "general purpose" type of box (open_box);
6095    can output on several formatters at the same time.
6096
6097* The "threads" library:
6098  - implementation on top of native threads available for Win32 and
6099    POSIX 1003.1c;
6100  - added -thread option to select a thread-safe version of the
6101    standard library, the ThreadIO module is no longer needed.
6102
6103* The "graph" library: avoid invalid pixmaps when doing
6104  open_graph/close_graph several times.
6105
6106* The "dynlink" library: support for "private" (no re-export) dynamic loading.
6107
6108* ocamlyacc: skip '...' character literals correctly.
6109
6110* C interface: C code linked with O'Caml code can provide its own main()
6111  and call caml_main() later.
6112
6113
6114Objective Caml 1.01 (12 Jun 1996):
6115----------------------------------
6116
6117* Typing: better report of type incompatibilities;
6118  non-generalizable type variables in a struct...end no longer flagged
6119  immediately as an error;
6120  name clashes during "open" avoided.
6121
6122* Fixed bug in output_value where identical data structures
6123  could have different external representations; this bug caused wrong
6124  "inconsistent assumptions" errors when checking compatibility of
6125  interfaces at link-time.
6126
6127* Standard library: fixed bug in Array.blit on overlapping array sections
6128
6129* Unmarshaling from strings now working.
6130
6131* ocamlc, ocamlopt: new flags -intf and -impl to force compilation as
6132  an implementation/an interface, regardless of file extension;
6133  overflow bug on wide-range integer pattern-matchings fixed.
6134
6135* ocamlc: fixed bytecode generation bug causing problems with compilation
6136  units defining more than 256 values
6137
6138* ocamlopt, all platforms:
6139  fixed GC bug in "let rec" over data structures;
6140  link startup file first, fixes "undefined symbol" errors with some
6141  libraries.
6142
6143* ocamlopt, Intel x86:
6144  more efficient calling sequence for calling C functions;
6145  floating-point wars, chapter 5: don't use float stack for holding
6146  float pseudo-registers, stack-allocating them is just as efficient.
6147
6148* ocamlopt, Alpha and Intel x86: more compact calling sequence for garbage
6149  collection.
6150
6151* ocamllex: generated automata no longer use callbacks for refilling
6152  the input buffer (works better with threads); character literals
6153  correctly skipped inside actions.
6154
6155* ocamldep: "-I" directories now searched in the right order
6156
6157* Thread library: incompatibilities with callbacks, signals, and
6158  dynamic linking removed; scheduling bug with Thread.wait fixed.
6159
6160* New "dbm" library, interfaces with NDBM.
6161
6162* Object-oriented extensions:
6163    instance variables can now be omitted in class types;
6164    some error messages have been made clearer;
6165    several bugs fixes.
6166
6167Objective Caml 1.00 (9 May 1996):
6168---------------------------------
6169
6170* Merge of Jérôme Vouillon and Didier Rémy's object-oriented
6171extensions.
6172
6173* All libraries: all "new" functions renamed to "create" because "new"
6174is now a reserved keyword.
6175
6176* Compilation of "or" patterns (pat1 | pat2) completely revised to
6177avoid code size explosion.
6178
6179* Compiler support for preprocessing source files (-pp flag).
6180
6181* Library construction: flag -linkall to force linking of all units in
6182a library.
6183
6184* Native-code compiler: port to the Sparc under NetBSD.
6185
6186* Toplevel: fixed bug when tracing several times the same function
6187under different names.
6188
6189* New format for marshaling arbitrary data structures, allows
6190marshaling to/from strings.
6191
6192* Standard library: new module Genlex (configurable lexer for streams)
6193
6194* Thread library: much better support for I/O and blocking system calls.
6195
6196* Graphics library: faster reclaimation of unused pixmaps.
6197
6198* Unix library: new functions {set,clear}_nonblock, {set,clear}_close_on_exec,
6199{set,get}itimer, inet_addr_any, {get,set}sockopt.
6200
6201* Dynlink library: added support for linking libraries (.cma files).
6202
6203Caml Special Light 1.15 (15 Mar 1996):
6204--------------------------------------
6205
6206* Caml Special Light now runs under Windows NT and 95. Many thanks to
6207Kevin Gallo (Microsoft Research) who contributed his initial port.
6208
6209* csllex now generates tables for a table-driven automaton.
6210The resulting lexers are smaller and run faster.
6211
6212* Completely automatic configuration script.
6213
6214* Typing: more stringent checking of module type definitions against
6215manifest module type specifications.
6216
6217* Toplevel: recursive definitions of values now working.
6218
6219* Native-code compiler, all platforms:
6220        toplevel "let"s with refutable patterns now working;
6221        fixed bug in assignment to float record fields;
6222        direct support for floating-point negation and absolute value.
6223
6224* Native-code compiler, x86: fixed bug with tail calls (with more than
62254 arguments) from a function with a one-word stack frame.
6226
6227* Native-code compiler, Sparc: problem with -compact fixed.
6228
6229* Thread library: support for non-blocking writes; scheduler revised.
6230
6231* Unix library: bug in gethostbyaddr fixed; bounds checking for read,
6232write, etc.
6233
6234Caml Special Light 1.14 (8 Feb 1996):
6235-------------------------------------
6236
6237* cslopt ported to the PowerPC/RS6000 architecture. Better support for
6238AIX in the bytecode system as well.
6239
6240* cslopt, all platforms: fixed bug in live range splitting around catch/exit.
6241
6242* cslopt for the Intel (floating-point wars, chapter 4):
6243implemented Ershov's algorithm to minimize floating-point stack usage;
6244out-of-order pops fixed.
6245
6246* Several bug fixes in callbacks and signals.
6247
6248Caml Special Light 1.13 (4 Jan 1996):
6249-------------------------------------
6250
6251* Pattern-matching compilation revised to factor out accesses inside
6252matched structures.
6253
6254* Callbacks and signals now supported in cslopt.
6255Signals are only detected at allocation points, though.
6256Added callback functions with 2 and 3 arguments.
6257
6258* More explicit error messages when a native-code program aborts due
6259to array or string bound violations.
6260
6261* In patterns, "C _" allowed even if the constructor C has several arguments.
6262
6263* && and || allowed as alternate syntax for & and or.
6264
6265* cslopt for the Intel: code generation for floating-point
6266operations entirely redone for the third time (a pox on whomever at
6267Intel decided to organize the floating-point registers as a stack).
6268
6269* cslopt for the Sparc: don't use Sparc V8 smul and sdiv instructions,
6270emulation on V7 processors is abysmal.
6271
6272Caml Special Light 1.12 (30 Nov 1995):
6273--------------------------------------
6274
6275* Fixed an embarrassing bug with references to floats.
6276
6277Caml Special Light 1.11 (29 Nov 1995):
6278--------------------------------------
6279
6280* Streams and stream parsers a la Caml Light are back (thanks to
6281Daniel de Rauglaudre).
6282
6283* User-level concurrent threads, with low-level shared memory primitives
6284(locks and conditions) as well as channel-based communication primitives
6285with first-class synchronous events, in the style of Reppy's CML.
6286
6287* The native-code compiler has been ported to the HP PA-RISC processor
6288running under NextStep (sorry, no HPUX, its linker keeps dumping
6289core on me).
6290
6291* References not captured in a function are optimized into variables.
6292
6293* Fixed several bugs related to exceptions.
6294
6295* Floats behave a little more as specified in the IEEE standard
6296(believe it or not, but x < y is not the negation of x >= y).
6297
6298* Lower memory consumption for the native-code compiler.
6299
6300Caml Special Light 1.10 (07 Nov 1995):
6301--------------------------------------
6302
6303* Many bug fixes (too many to list here).
6304
6305* Module language: introduction of a "with module" notation over
6306signatures for concise sharing of all type components of a signature;
6307better support for concrete types in signatures.
6308
6309* Native-code compiler: the Intel 386 version has been ported to
6310NextStep and FreeBSD, and generates better code (especially for
6311floats)
6312
6313* Tools and libraries: the Caml Light profiler and library for
6314arbitrary-precision arithmetic have been ported (thanks to John
6315Malecki and Victor Manuel Gulias Fernandez); better docs for the Unix
6316and regexp libraries.
6317
6318Caml Special Light 1.07 (20 Sep 1995):
6319--------------------------------------
6320
6321* Syntax: optional ;; allowed in compilation units and structures
6322(back by popular demand)
6323
6324* cslopt:
6325generic handling of float arrays fixed
6326direct function application when the function expr is not a path fixed
6327compilation of "let rec" over values fixed
6328multiple definitions of a value name in a module correctly handled
6329no calls to ranlib in Solaris
6330
6331* csltop: #trace now working
6332
6333* Standard library: added List.memq; documentation of Array fixed.
6334
6335Caml Special Light 1.06 (12 Sep 1995):
6336--------------------------------------
6337
6338* First public release.
6339