Objective Caml 2.04: -------------------- - C interface: corrected inconsistent change in the CAMLparam* macros. - Fixed internal error in ocamlc -g. - Fixed type-checking of "S with ...", where S is a module type name abbreviating another module type name. - ocamldep: fixed stdout/stderr mismatch after failing on one file. - Random.self_init more random. - Windows port: - Toplevel application: fixed spurious crash on exit. - Native-code compiler: fixed bug in assembling certain floating-point constants (masm doesn't grok 2e5, wants 2.0e5). Objective Caml 2.03: -------------------- New ports: - Ported to BeOS / Intel x86 (bytecode and native-code). - BSD / Intel x86 port now supports both a.out and ELF binary formats. - Added support for {Net,Open}BSD / Alpha. - Revamped Rhapsody port, now works on MacOS X server. Syntax: - Warning for "(*)" and "*)" outside comment. - Removed "#line LINENO", too ambiguous with a method invocation; the equivalent "# LINENO" is still supported. Typing: - When an incomplete pattern-matching is detected, report also a value or value template that is not covered by the cases of the pattern-matching. - Several bugs in class type matching and in type error reporting fixed. - Added an option -rectypes to support general recursive types, not just those involving object types. Bytecode compiler: - Minor cleanups in the bytecode emitter. - Do not remove "let x = y" bindings in -g mode; makes it easier to debug the code. Native-code compiler: - Fixed bug in grouping of allocations performed in the same basic block. - Fixed bug in constant propagation involving expressions containing side-effects. - Fixed incorrect code generation for "for" loops whose upper bound is a reference assigned inside the loop. - MIPS code generator: work around a bug in the IRIX 6 assembler. Toplevel: - Fixed incorrect redirection of standard formatter to stderr while executing toplevel scripts. Standard library: - Added List.rev_map, List.rev_map2. - Documentation of List functions now says which functions are tail-rec, and how much stack space is needed for non-tailrec functions. - Wrong type for Printf.bprintf fixed. - Fixed weird behavior of Printf.sprintf and Printf.bprintf in case of partial applications. - Added Random.self_init, which initializes the PRNG from the system date. - Sort.array: serious bugs fixed. - Stream.count: fixed incorrect behavior with ocamlopt. Run-time system and external interface: - Fixed weird behavior of signal handlers w.r.t. signal masks and exceptions raised from the signal handler. - Fixed bug in the callback*_exn() functions. Debugger: - Fixed wrong printing of float record fields and elements of float arrays. - Supports identifiers starting with '_'. Profiler: - Handles .mli files, so ocamlcp can be used to replace ocamlc (e.g. in a makefile). - Now works on programs that use stream expressions and stream parsers. Other libraries: - Graphics: under X11, treat all mouse buttons equally; fixed problem with current font reverting to the default font when the graphics window is resized. - Str: fixed reentrancy bugs in Str.replace and Str.full_split. - Bytecode threads: set standard I/O descriptors to non-blocking mode. - OS threads: revised implementation of Thread.wait_signal. - All threads: added Event.wrap_abort, Event.choose []. - Unix.localtime, Unix.gmtime: check for errors. - Unix.create_process: now supports arbitrary redirections of std descriptors. - Added Unix.open_process_full. - Implemented Unix.chmod under Windows. - Big_int.square_big_int now gives the proper sign to its result. Others: - ocamldep: don't stop at first error, skip to next file. - Emacs mode: updated with Garrigue and Zimmerman's snapshot of 1999/10/18. - configure script: added -prefix option. - Windows toplevel application: fixed problem with graphics library not loading properly. Objective Caml 2.02: -------------------- * Type system: - Check that all components of a signature have unique names. - Fixed bug in signature matching involving a type component and a module component, both sharing an abstract type. - Bug involving recursive classes constrained by a class type fixed. - Fixed bugs in printing class types and in printing unification errors. * Compilation: - Changed compilation scheme for "{r with lbl = e}" when r has many fields so as to avoid code size explosion. * Native-code compiler: - Better constant propagation in boolean expressions and in conditionals. - Removal of unused arguments during function inlining. - Eliminated redundant tagging/untagging in bit shifts. - Static allocation of closures for functions without free variables, reduces the size of initialization code. - Revised compilation scheme for definitions at top level of compilation units, so that top level functions have no free variables. - Coalesced multiple allocations of heap blocks inside one expression (e.g. x :: y :: z allocates the two conses in one step). - Ix86: better handling of large integer constants in instruction selection. - MIPS: fixed wrong asm generated for String.length "literal". * Standard library: - Added the "ignore" primitive function, which just throws away its argument and returns "()". It allows to write "ignore(f x); y" if "f x" doesn't have type unit and you don't want the warning caused by "f x; y". - Added the "Buffer" module (extensible string buffers). - Module Format: added formatting to buffers and to strings. - Added "mem" functions (membership test) to Hashtbl and Map. - Module List: added find, filter, partition. Renamed remove and removeq to remove_assoc and remove_assq. - Module Marshal: fixed bug in marshaling functions when passed functional values defined by mutual recursion with other functions. - Module Printf: added Printf.bprintf (print to extensible buffer); added %i format as synonymous for %d (as per the docs). - Module Sort: added Sort.array (Quicksort). * Runtime system: - New callback functions for callbacks with arbitrary many arguments and for catching Caml exceptions escaping from a callback. * The ocamldep dependency generator: now performs full parsing of the sources, taking into account the scope of module bindings. * The ocamlyacc parser generator: fixed sentinel error causing wrong tables to be generated in some cases. * The str library: - Added split_delim, full_split as variants of split that control more precisely what happens to delimiters. - Added replace_matched for separate matching and replacement operations. * The graphics library: - Bypass color lookup for 16 bpp and 32 bpp direct-color displays. - Larger color cache. * The thread library: - Bytecode threads: more clever use of non-blocking I/O, makes I/O operations faster. - POSIX threads: gcc-ism removed, should now compile on any ANSI C compiler. - Both: avoid memory leak in the Event module when a communication offer is never selected. * The Unix library: - Fixed inversion of ctime and mtime in Unix.stat, Unix.fstat, Unix.lstat. - Unix.establish_connection: properly reclaim socket if connect fails. * The DBM library: no longer crashes when calling Dbm.close twice. * Emacs mode: - Updated with Garrigue and Zimmerman's latest version. - Now include an "ocamltags" script for using etags on OCaml sources. * Win32 port: - Fixed end-of-line bug in ocamlcp causing problems with generated sources. Objective Caml 2.01: -------------------- * Typing: - Added warning for expressions of the form "a; b" where a does not have type "unit"; catches silly mistake such as "record.lbl = newval; ..." instead of "record.lbl <- newval; ...". - Typing bug in "let module" fixed. * Compilation: - Fixed bug in compilation of recursive and mutually recursive classes. - Option -w to turn specific warnings on/off. - Option -cc to choose the C compiler used with ocamlc -custom and ocamlopt. * Bytecode compiler and bytecode interpreter: - Intel x86: removed asm declaration causing "fixed or forbidden register spilled" error with egcs and gcc 2.8 (but not with gcc 2.7, go figure). - Revised handling of debugging information, allows faster linking with -g. * Native-code compiler: - Fixed bugs in integer constant propagation. - Out-of-bound accesses in array and strings now raise an Invalid_argument exception (like the bytecode system) instead of stopping the program. - Corrected scheduling of bound checks. - Port to the StrongARM under Linux (e.g. Corel Netwinder). - I386: fixed bug in profiled code (ocamlopt -p). - Mips: switched to -n32 model under IRIX; dropped the Ultrix port. - Sparc: simplified the addressing modes, allows for better scheduling. - Fixed calling convention bug for Pervasives.modf. * Toplevel: - #trace works again. - ocamlmktop: use matching ocamlc, not any ocamlc from the search path. * Memory management: - Fixed bug in heap expansion that could cause the GC to loop. * C interface: - New macros CAMLparam... and CAMLlocal... to simplify the handling of local roots in C code. - Simplified procedure for allocating and filling Caml blocks from C. - Declaration of string_length in . * Standard library: - Module Format: added {get,set}_all_formatter_output_functions, formatter_of_out_channel, and the control sequence @ in printf. - Module List: added mem_assoc, mem_assq, remove, removeq. - Module Pervasives: added float_of_int (synonymous for float), int_of_float (truncate), int_of_char (Char.code), char_of_int (Char.chr), bool_of_string. - Module String: added contains, contains_from, rcontains_from. * Unix library: - Unix.lockf: added F_RLOCK, F_TRLOCK; use POSIX locks whenever available. - Unix.tc{get,set}attr: added non-standard speeds 57600, 115200, 230400. - Unix.chroot: added. * Threads: - Bytecode threads: improved speed of I/O scheduling. - Native threads: fixed a bug involving signals and exceptions generated from C. * The "str" library: - Added Str.string_partial_match. - Bumped size of internal stack. * ocamlyacc: emit correct '# lineno' directive for prelude part of .mly file. * Emacs editing mode: updated with Jacques Garrigue's newest code. * Windows port: - Added support for the "-cclib -lfoo" option (instead of -cclib /full/path/libfoo.lib as before). - Threads: fixed a bug at initialization time. * Macintosh port: source code for Macintosh application merged in. Objective Caml 2.00: -------------------- * Language: - New class language. See http://caml.inria.fr/ocaml/refman/ for a tutorial (chapter 2) and for the reference manual (section 4.9). - Local module definitions "let module X = in ". - Record copying with update "{r with lbl1 = expr1; ...}". - Array patterns "[|pat1; ...;patN|]" in pattern-matchings. - New reserved keywords: "object", "initializer". - No longer reserved: "closed", "protected". * Bytecode compiler: - Use the same compact memory representations for float arrays, float records and recursive closures as the native-code compiler. - More type-dependent optimizations. - Added the -use_runtime and -make_runtime flags to build separately and reuse afterwards custom runtime systems (inspired by Fabrice Le Fessant's patch). * Native-code compiler: - Cross-module constant propagation of integer constants. - More type-dependent optimizations. - More compact code generated for "let rec" over data structures. - Better code generated for "for" loops (test at bottom of code). - More aggressive scheduling of stores. - Added -p option for time profiling with gprof (fully supported on Intel x86/Linux and Alpha/Digital Unix only) (inspired by Aleksey Nogin's patch). - A case of bad spilling with high register pressure fixed. - Fixed GC bug when GC called from C without active Caml code. - Alpha: $gp handling revised to follow Alpha's standard conventions, allow running "atom" and "pixie" on ocamlopt-generated binaries. - Intel x86: use movzbl and movsbl systematically to load 8-bit and 16-bit quantities, no more hacks with partial registers (better for the Pentium Pro, worse for the Pentium). - PowerPC: more aggressive scheduling of return address reloading. - Sparc: scheduling bug related to register pairs fixed. * Runtime system: - Better printing of uncaught exceptions (print a fully qualified name whenever possible). * New ports: - Cray T3E (bytecode only) (in collaboration with CEA). - PowerMac under Rhapsody. - SparcStations under Linux. * Standard library: - Added set_binary_mode_in and set_binary_mode_out in Pervasives to toggle open channels between text and binary modes. - output_value and input_value check that the given channel is in binary mode. - input_value no longer fails on very large marshalled data (> 16 Mbytes). - Module Arg: added option Rest. - Module Filename: temp_file no longer loops if temp dir doesn't exist. - Module List: added rev_append (tail-rec alternative to @). - Module Set: tell the truth about "elements" returning a sorted list; added min_elt, max_elt, singleton. - Module Sys: added Sys.time for simple measuring of CPU time. * ocamllex: - Check for overflow when generating the tables for the automaton. - Error messages in generated .ml file now point to .mll source. - Added "let = " to name regular expressions (inspired by Christian Lindig's patch). * ocamlyacc: - Better error recovery in presence of EOF tokens. - Error messages in generated .ml file now point to .mly source. - Generated .ml file now type-safe even without the generated .mli file. * The Unix library: - Use float instead of int to represent Unix times (number of seconds from the epoch). This fixes a year 2005 problem on 32-bit platforms. Functions affected: stat, lstat, fstat, time, gmtime, localtime, mktime, utimes. - Added putenv. - Better handling of "unknown" error codes (EUNKNOWNERR). - Fixed endianness bug in getservbyport. - win32unix (the Win32 implementation of the Unix library) now has the same interface as the unix implementation, this allows exchange of compiled .cmo and .cmi files between Unix and Win32. * The thread libraries: - Bytecode threads: bug with escaping exceptions fixed. - System threads (POSIX, Win32): malloc/free bug fixed; signal bug fixed. - Both: added Thread.wait_signal to wait synchronously for signals. * The graph library: bigger color cache. * The str library: added Str.quote, Str.regexp_string, Str.regexp_string_case_fold. * Emacs mode: - Fixed bug with paragraph fill. - Fixed bug with next-error under Emacs 20. Objective Caml 1.07: -------------------- * Native-code compiler: - Revised interface between generated code and GC, fixes serious GC problems with signals and native threads. - Added "-thread" option for compatibility with ocamlc. * Debugger: correctly print instance variables of objects. * Run-time system: ported to OpenBSD. * Standard library: fixed wrong interface for Marshal.to_buffer and Obj.unmarshal. * Num library: added Intel x86 optimized asm code (courtesy of Bernard Serpette). * Thread libraries: - Native threads: fixed GC bugs and installation procedure. - Bytecode threads: fixed problem with "Marshal" module. - Both: added Event.always. * MS Windows port: better handling of long command lines in Sys.command Objective Caml 1.06: -------------------- * Language: - Added two new keywords: "assert" (check assertion) and "lazy" (delay evaluation). - Allow identifiers to start with "_" (such identifiers are treated as lowercase idents). * Objects: - Added "protected" methods (visible only from subclasses, can be hidden in class type declared in module signature). - Objects can be compared using generic comparison functions. - Fixed compilation of partial application of object constructors. * Type system: - Occur-check now more strict (all recursions must traverse an object). - A few bugs fixed. * Run-time system: - A heap compactor was implemented, so long-running programs can now fight fragmentation. - The meaning of the "space_overhead" parameter has changed. - The macros Push_roots and Pop_roots are superseded by Begin_roots* and End_roots. - Bytecode executable includes list of primitives used, avoids crashes on version mismatch. - Reduced startup overhead for marshalling, much faster marshalling of small objects. - New exception Stack_overflow distinct from Out_of_memory. - Maximum stack size configurable. - I/O revised for compatibility with compactor and with native threads. - All C code ANSIfied (new-style function declarations, etc). - Threaded code work on all 64-bit processors, not just Alpha/Digital Unix. - Better printing of uncaught exceptions. * Both compilers: - Parsing: more detailed reporting of syntax errors (e.g. shows unmatched opening parenthesis on missing closing parenthesis). - Check consistency between interfaces (.cmi). - Revised rules for determining dependencies between modules. - Options "-verbose" for printing calls to C compiler, "-noassert" for turning assertion checks off. * Native-code compiler: - Machine-dependent parts rewritten using inheritance instead of parameterized modules. - GC bug in value let rec fixed. - Port to Linux/Alpha. - Sparc: cleaned up use of %g registers, now compatible with Solaris threads. * Top-level interactive system: - Can execute Caml script files given on command line. - Reads commands from ./.ocamlinit on startup. - Now thread-compatible. * Standard library: - New library module: Lazy (delayed computations). - New library module: Marshal. Allows marshalling to strings and transmission of closures between identical programs (SPMD parallelism). - Filename: "is_absolute" is superseded by "is_implicit" and "is_relative". To adapt old programs, change "is_absolute x" to "not (is_implicit x)" (but the new "is_relative" is NOT the opposite of the old "is_absolute"). - Array, Hashtbl, List, Map, Queue, Set, Stack, Stream: the "iter" functions now take as argument a unit-returning function. - Format: added "printf" interface to the formatter (see the documentation). Revised behaviour of simple boxes: no more than one new line is output when consecutive break hints should lead to multiple line breaks. - Stream: revised implementation, renamed Parse_failure to Failure and Parse_error to Error (don't you love gratuitous changes?). - String: added index, rindex, index_from, rindex_from. - Array: added mapi, iteri, fold_left, fold_right, init. - Added Map.map, Set.subset, Printexc.to_string. * ocamllex: lexers generated by ocamllex can now handle all characters, including '\000'. * ocamlyacc: fixed bug with function closures returned by parser rules. * Debugger: - Revised generation of events. - Break on function entrance. - New commands start/previous. - The command loadprinter now try to recursively load required modules. - Numerous small fixes. * External libraries: - systhreads: can now use POSIX threads; POSIX and Win32 threads are now supported by the native-code compiler. - dbm and graph: work in native code. - num: fixed bug in Nat.nat_of_string. - str: fixed deallocation bug with case folding. - win32unix: use Win32 handles instead of (buggy) VC++ emulation of Unix file handles; added gettimeofday. * Emacs editing mode and debugger interface updated to July '97 version. Objective Caml 1.05: -------------------- * Typing: fixed several bugs causing spurious type errors. * Native-code compiler: fixed instruction selection bug causing GC to see ill-formed pointers; fixed callbacks to support invocation from a main program in C. * Standard library: fixed String.lowercase; Weak now resists integers. * Toplevel: multiple phrases without intermediate ";;" now really supported; fixed value printing problems where the wrong printer was selected. * Debugger: fixed printing problem with local references; revised handling of checkpoints; various other small fixes. * Macintosh port: fixed signed division problem in bytecomp/emitcode.ml Objective Caml 1.04: -------------------- * Replay debugger ported from Caml Light; added debugger support in compiler (option -g) and runtime system. Debugger is alpha-quality and needs testing. * Parsing: - Support for "# linenum" directives. - At toplevel, allow several phrases without intermediate ";;". * Typing: - Allow constraints on datatype parameters, e.g. type 'a foo = ... constraint 'a = 'b * 'c. - Fixed bug in signature matching in presence of free type variables '_a. - Extensive cleanup of internals of type inference. * Native-code compilation: - Inlining of small functions at point of call (fairly conservative). - MIPS code generator ported to SGI IRIX 6. - Better code generated for large integer constants. - Check for urgent GC when allocating large objects in major heap. - PowerPC port: better scheduling, reduced TOC consumption. - HPPA port: handle long conditional branches gracefully, several span-dependent bugs fixed. * Standard library: - More floating-point functions (all ANSI C float functions now available). - Hashtbl: added functorial interface (allow providing own equality and hash functions); rehash when resizing, avoid memory leak on Hashtbl.remove. - Added Char.uppercase, Char.lowercase, String.uppercase, String.lowercase, String.capitalize, String.uncapitalize. - New module Weak for manipulating weak pointers. - New module Callback for registering closures and exceptions to be used from C. * Foreign interface: - Better support for callbacks (C calling Caml), exception raising from C, and main() in C. Added function to remove a global root. - Option -output-obj to package Caml code as a C library. * Thread library: fixed bug in timed_read and timed_write operations; Lexing.from_function and Lexing.from_channel now reentrant. * Unix interface: renamed EACCESS to EACCES (the POSIX name); added setsid; fixed bug in inet_addr_of_string for 64-bit platforms. * Ocamlyacc: default error function no longer prevents error recovery. * Ocamllex: fixed reentrancy problem w.r.t. exceptions during refill; fixed output problem (\r\r\n) under Win32. * Macintosh port: - The makefiles are provided for compiling and installing O'Caml on a Macintosh with MPW 3.4.1. - An application with the toplevel in a window is forthcoming. * Windows NT/95 port: updated toplevel GUI to that of Caml Light 0.73. * Emacs editing mode and debugger interface included in distribution. Objective Caml 1.03: -------------------- * Typing: - bug with type names escaping their scope via unification with non-generalized type variables '_a completely fixed; - fixed bug in occur check : it was too restrictive; - fixed bug of coercion operators; - check that no two types of the same name are generated in a module (there was no check for classes); - "#install_printer" works again; - fixed bug in printing of subtyping errors; - in class interfaces, construct "method m" (without type) change the status of method m from abstract to concrete; - in a recursive definition of class interfaces, a class can now inherit from a previous class; - typing of a method make use of an eventual previously given type of this method, yielding clearer type errors. * Compilation (ocamlc and ocamlopt): - fixed bug in compilation of classes. * Native-code compilation: - optimization of functions taking tuples of arguments; - code emitter for the Motorola 680x0 processors (retrocomputing week); - Alpha/OSF1: generate frame descriptors, avoids crashes when e.g. exp() or log() cause a domain error; fixed bug with String.length "literal"; - Sparc, Mips, HPPA: removed marking of scanned stack frames (benefits do not outweight cost). * Standard library: - Arg.parse now prints documentation for command-line options; - I/O buffers (types in_channel and out_channel) now heap-allocated, avoids crashing when closing a channel several times; - Overflow bug in compare() fixed; - GC bug in raising Sys_error from I/O functions fixed; - Parsing.symbol_start works even for epsilon productions. * Foreign interface: main() in C now working, fixed bug in library order at link time. * Thread library: guard against calling thread functions before Thread.create. * Unix library: fixed getsockopt, setsockopt, open_process_{in,out}. * Perl-free, cpp-free, cholesterol-free installation procedure. Objective Caml 1.02: -------------------- * Typing: - fixed bug with type names escaping their scope via unification with non-generalized type variables '_a; - keep #class abbreviations longer; - faster checking of well-formed abbreviation definitions; - stricter checking of "with" constraints over signatures (arity mismatch, overriding of an already manifest type). * Compilation (ocamlc and ocamlopt): - fixed bug in compilation of recursive classes; - [|...|] and let...rec... allowed inside definitions of recursive data structures; * Bytecode compilation: fixed overflow in linker for programs with more than 65535 globals and constants. * Native-code compilation: - ocamlopt ported to HPPA under HP/UX, Intel x86 under Solaris 2, PowerMacintosh under MkLinux; - fixed two bugs related to floating-point arrays (one with "t array" where t is an abstract type implemented as float, one with comparison between two float arrays on 32 bit platforms); - fixed reloading/spilling problem causing non-termination of register allocation; - fixed bugs in handling of () causing loss of tail recursion; - fixed reloading bug in indirect calls. * Windows NT/95 port: - complete port of the threads library (Pascal Cuoq); - partial port of the Unix library (Pascal Cuoq); - expansion of *, ? and @ on the command line. * Standard library: - bug in in List.exists2 fixed; - bug in "Random.int n" for very large n on 64-bit machines fixed; - module Format: added a "general purpose" type of box (open_box); can output on several formatters at the same time. * The "threads" library: - implementation on top of native threads available for Win32 and POSIX 1003.1c; - added -thread option to select a thread-safe version of the standard library, the ThreadIO module is no longer needed. * The "graph" library: avoid invalid pixmaps when doing open_graph/close_graph several times. * The "dynlink" library: support for "private" (no re-export) dynamic loading. * ocamlyacc: skip '...' character literals correctly. * C interface: C code linked with O'Caml code can provide its own main() and call caml_main() later. Objective Caml 1.01: -------------------- * Typing: better report of type incompatibilities; non-generalizable type variables in a struct...end no longer flagged immediately as an error; name clashes during "open" avoided. * Fixed bug in output_value where identical data structures could have different external representations; this bug caused wrong "inconsistent assumptions" errors when checking compatibility of interfaces at link-time. * Standard library: fixed bug in Array.blit on overlapping array sections * Unmarshaling from strings now working. * ocamlc, ocamlopt: new flags -intf and -impl to force compilation as an implementation/an interface, regardless of file extension; overflow bug on wide-range integer pattern-matchings fixed. * ocamlc: fixed bytecode generation bug causing problems with compilation units defining more than 256 values * ocamlopt, all platforms: fixed GC bug in "let rec" over data structures; link startup file first, fixes "undefined symbol" errors with some libraries. * ocamlopt, Intel x86: more efficient calling sequence for calling C functions; floating-point wars, chapter 5: don't use float stack for holding float pseudo-registers, stack-allocating them is just as efficient. * ocamlopt, Alpha and Intel x86: more compact calling sequence for garbage collection. * ocamllex: generated automata no longer use callbacks for refilling the input buffer (works better with threads); character literals correctly skipped inside actions. * ocamldep: "-I" directories now searched in the right order * Thread library: incompatibilities with callbacks, signals, and dynamic linking removed; scheduling bug with Thread.wait fixed. * New "dbm" library, interfaces with NDBM. * Object-oriented extensions: instance variables can now be omitted in class types; some error messages have been made clearer; several bugs fixes. Objective Caml 1.00: -------------------- * Merge of Jerome Vouillon and Didier Remy's object-oriented extensions. * All libraries: all "new" functions renamed to "create" because "new" is now a reserved keyword. * Compilation of "or" patterns (pat1 | pat2) completely revised to avoid code size explosion. * Compiler support for preprocessing source files (-pp flag). * Library construction: flag -linkall to force linking of all units in a library. * Native-code compiler: port to the Sparc under NetBSD. * Toplevel: fixed bug when tracing several times the same function under different names. * New format for marshaling arbitrary data structures, allows marshaling to/from strings. * Standard library: new module Genlex (configurable lexer for streams) * Thread library: much better support for I/O and blocking system calls. * Graphics library: faster reclaimation of unused pixmaps. * Unix library: new functions {set,clear}_nonblock, {set,clear}_close_on_exec, {set,get}itimer, inet_addr_any, {get,set}sockopt. * Dynlink library: added support for linking libraries (.cma files). Caml Special Light 1.15: ------------------------ * Caml Special Light now runs under Windows NT and 95. Many thanks to Kevin Gallo (Microsoft Research) who contributed his initial port. * csllex now generates tables for a table-driven automaton. The resulting lexers are smaller and run faster. * Completely automatic configuration script. * Typing: more stringent checking of module type definitions against manifest module type specifications. * Toplevel: recursive definitions of values now working. * Native-code compiler, all platforms: toplevel "let"s with refutable patterns now working; fixed bug in assignment to float record fields; direct support for floating-point negation and absolute value. * Native-code compiler, x86: fixed bug with tail calls (with more than 4 arguments) from a function with a one-word stack frame. * Native-code compiler, Sparc: problem with -compact fixed. * Thread library: support for non-blocking writes; scheduler revised. * Unix library: bug in gethostbyaddr fixed; bounds checking for read, write, etc. Caml Special Light 1.14: ------------------------ * cslopt ported to the PowerPC/RS6000 architecture. Better support for AIX in the bytecode system as well. * cslopt, all platforms: fixed bug in live range splitting around catch/exit. * cslopt for the Intel (floating-point wars, chapter 4): implemented Ershov's algorithm to minimize floating-point stack usage; out-of-order pops fixed. * Several bug fixes in callbacks and signals. Caml Special Light 1.13: ------------------------ * Pattern-matching compilation revised to factor out accesses inside matched structures. * Callbacks and signals now supported in cslopt. Signals are only detected at allocation points, though. Added callback functions with 2 and 3 arguments. * More explicit error messages when a native-code program aborts due to array or string bound violations. * In patterns, "C _" allowed even if the constructor C has several arguments. * && and || allowed as alternate syntax for & and or. * cslopt for the Intel: code generation for floating-point operations entirely redone for the third time (a pox on whomever at Intel decided to organize the floating-point registers as a stack). * cslopt for the Sparc: don't use Sparc V8 smul and sdiv instructions, emulation on V7 processors is abysmal. Caml Special Light 1.12: ------------------------ * Fixed an embarrassing bug with references to floats. Caml Special Light 1.11: ------------------------ * Streams and stream parsers a la Caml Light are back (thanks to Daniel de Rauglaudre). * User-level concurrent threads, with low-level shared memory primitives (locks and conditions) as well as channel-based communication primitives with first-class synchronous events, in the style of Reppy's CML. * The native-code compiler has been ported to the HP PA-RISC processor running under NextStep (sorry, no HPUX, its linker keeps dumping core on me). * References not captured in a function are optimized into variables. * Fixed several bugs related to exceptions. * Floats behave a little more as specified in the IEEE standard (believe it or not, but x < y is not the negation of x >= y). * Lower memory consumption for the native-code compiler. Caml Special Light 1.10: ------------------------ * Many bug fixes (too many to list here). * Module language: introduction of a "with module" notation over signatures for concise sharing of all type components of a signature; better support for concrete types in signatures. * Native-code compiler: the Intel 386 version has been ported to NextStep and FreeBSD, and generates better code (especially for floats) * Tools and libraries: the Caml Light profiler and library for arbitrary-precision arithmetic have been ported (thanks to John Malecki and Victor Manuel Gulias Fernandez); better docs for the Unix and regexp libraries. Caml Special Light 1.07: ------------------------ * Syntax: optional ;; allowed in compilation units and structures (back by popular demand) * cslopt: generic handling of float arrays fixed direct function application when the function expr is not a path fixed compilation of "let rec" over values fixed multiple definitions of a value name in a module correctly handled no calls to ranlib in Solaris * csltop: #trace now working * Standard library: added List.memq; documentation of Array fixed. Caml Special Light 1.06: ------------------------ * First public release.