SWI-Prolog ChangeLog ==================== Version 2.1.4 ============= * MODIFIED: Changed definition of absolute_file_name/2. Moved absolute_file_name/3 from library(quintus) to a built-in predicate. * ADDED: file_directory_name/2 and file_base_name/2. * ADDED: end_of_file is now passed to term_expansion/2. * DOC: Many updates. * FIXED: read/1 for foo.%comment (i.e. no space between the . and the comment). Note that foo./*comment*/ doesn't work as this will be tokenised as `foo', `./*', `comment', `*/'. * ADDED: lazy recomputation of clause indexing. This notably speeds up loading .qlf and bootfiles. * ADDED: hash_term/2 for advanced indexing of databases. * ADDED: setting file_search_path through the command line using: pl -p mydir=/foo/bar. * FIXED: Semantics of ensure_loaded/1 if the file is already loaded, combined with the module system. See ensure_loaded/1. * FIXED: Grammar rule compiler's handling of non-proper lists in the head or body (lists ending in a variable). Lists of more then one element are now translated into append/3. The following now compiles ok: string([H|T]) --> [H|T]. * MODIFIED: term_to_atom/2 and atom_to_term/3 to fail silently on a syntax error. Both predicates now also accept a string in the place of the atom to parse strings: term_to_atom(X, "foo(bar)") works as expected. * ADDED: `swi' and `foreign' aliases to file_search_path/2. * MODIFIED: Grammar rule translator now uses 'C'/3 instead of '$char'/3 to extract the head. Compatibility. * MODIFIED: at_initialisation/1 is now called at_initialization/1. * INSTALL: Fixed Makefile and configure to be able to build the system for multiple platforms. * ADDED: Infra-structure for making portable saved-states (equivalents of boot files): + initialization/1 (goals to run at initialization) + volatile/1 (predicates for which not to save clauses) + require/1 (define we require this predicate) + autoload/[0,1] (autoload needed things now) + qsave_program/[1,2] (make a quick-loadable state) * ADDED: compound/1 to test for compound terms. * FIXED: compilation of ``foo:Head :- Body'' to be equivalent to foo:(Head :- Body). * FIXED: problem in read/1 and number_chars/2 that may have lead to garbage collection errors. * FIXED: setarg/3 integrated in the trail-system. Removes its choicepoint and ensures data consistency. Version 2.1.3 ============= * ADDED: setarg/3 for extra-logical assignment to arguments of terms. * MODIFIED: PL_new_integer() now returns a floating point value if the argument exceeds SWI-Prolog's integer range. * ADDED: Automatically dumps the top of the runtime stack on floating point exceptions. * FIXED: Trap floating point exceptions for the win32 version. Version 2.1.2 ============= * FIXED: read/1 problem. Try reading just '0'. ... Reported by Daniela Genius. * FIXED: `toplevel' variable expansion system, leading to various strange behaviours in handling queries from the user. It now can also handle cases as: ?- X = 5. ?- X is $X + 1. Version 2.1.1 ============= * MODIFIED: DCG translation of free variables now calls phrase/3, which has been changed slightly to deal with `un-parsing'. Modification is probably not complete, but it fixes some problems encountered by Michael Boehlen. * MODIFIED: keysort/2 is now stable with regard to multiple values on the same key. Makes this predicate compatible with SICStus and Quintus. * FIXED: :- dynamic, :- multifile, :- module_transparent and :- discontiguous to accept Module:Name/Arity, ... * Moved call/[1..] into the compiler. call/[1..6] is removed from library(quintus) as it is now part of the base system. Also fail/0 and true/0 are now handled by virtual machine instructions. * Upgrade to autoconf 2.3, fixed usage of `tr' for Solaris 2.x and with that the configuration of --enable-shared. * FIXED: number_chars/2 and name/2 now handle floating point numbers. * FIXED: interaction between chdir/1 and absolute_file_name/2. * FIXED: format('~*c', [10,45]) (or more in general, providing an argument to ~c to print the character multiple times). Thanks to Michael Boehlen. * FIXED: PrologPrompt() to allow reading standard input from the -g and/or -t goal options. Version 2.1.0 ============== * Added facilities to allow for embedding SWI-Prolog in C applications. * Fixed semantics of the cut in toplevel queries by compiling the query instead of using meta-call. * Fixed bagof(A, member([B, C]), L) to yield L = [B,C] instead of making new variables. * Fixed typo in dde.pl (reported by Thiebaut Moeglin) * Integration of NeXT patches from Thomas Hoppe (hoppet@cs.tu-berlin.de). Probably still not 100% ok, but should be closer now. * Fixed XPCE event dispatching for pl -tty * PL_univg() C-interface function added for supporting XPCE > 4.8.10 with better interface performance. * Fixed operator precedence problem (reported by Dave Moffat) Version 2.0.9 ============= * ADDED: HPUX interface for shared libraries, but a HPUX guru should fix the import/export details (line was too slow to browse to lots of manual pages). * FIXED: pl-incl.h typo (breaks IRIX 5.3 port and propably others) * FIXED: HPUX detection of mmap()'able stacks fixed. * FIXED: generation of include/SWI-Exports, the AIX export declaration file. Version 2.0.8 ============= * FIXED: loading shared objects using dlopen() for solaris 2.x * FIXED: shlib.pl current_foreign_library/2 administration. Version 2.0.7 ============= * FIXED: compilation (boot and .qlf) now donot look for compiled (.qlf) files. * CHANGED: Default goal writing the banner is now in the flag $banner_goal (used by XPCE as a shared library). Version 2.0.6 ============= * CHANGED: retractall/1 implementation is now compatible to Quintus, avoiding the hacky redefinition in library(quintus.pl). The difference is that now the argument will only be matched against the clause-head. on a match the clause will be removed, regardless of its body. Makes no difference for retractall on facts, but does make a difference on clauses with a non-just-true body. retractall/1 is now a deterministic foreign predicate that no longer decompiles the clause body, making it faster too. * FIXED: made .qlf files independent of the directory they where compiled. * FIXED: Path canonisation problem * FIXED: loading .qlf files holding already-defined modules * ADDED: file_search_path file-location system * ADDED: access_file(File, exists) to check for bare existence. * FIXED: Another clear_uninitialised() problem related to if-then-else causing garbage collector and possibly stack-shift errors. As the implementation is now changed radically, this problem should be gone forever ... * FIXED: copy_term/2. Now creates more efficient terms (less references) and no longer creates bad references. Version 2.0.5 ============= * MODIFIED: Replaced libc based stream IO with more general IOSTREAM package. Deleted folding capabilities as just about any IO device has these built-in these days. These changes are to facilate embedding in window-based environments that do not support stdio. See pl-stream.c * FIX: dwim_match/2 for single character mismatch. * ADDED: atom_chars/2, number_chars/2, atom_char/2, various new unix/1 arguments. Version 2.0.4 ============= * MODIFIED: Consult and friends (ensure_loaded, use_module, etc.) no longer change directory to the directory in which the file lives. As a consequence, directives have to use prolog_load_context/2 or source_location/2 to find the context directory of the directive. consult and related directives still load relative to the directory in which the currently loading file lives. * Added prolog_load_context/2 to provide context for directives. Actually moved from library(quintus) to the boot image as the predicate is now necessary. * Added -DO_RUNTIME support to make a version that is more suitable for distribution of products: no profiling, no tracer, no readline and no interrupt handling. Setup using configure --enable-runtime Version 2.0.3 ============= * Fixed: loading qlf files now push the source context while running a directive, so source_location/2 should work while executing a directive from a .qlf file. * Fixed: recognise MAP_ANONYMOUS for configuring mmap() based stacks. * Added feature(dynamic_stacks, Bool) for detection of virtual memory based stack management. * Fixed feature(open_shared_object, Bool) (Michael Kauschke) Version 2.0.2 ============= * Fixed pl [options] -c file ... * Improved VMI implementation for (if -> then ; else), \+ and (a;b). Reduces overhead of these to about 1/3th. * Added VMI support for fast calling of foreign system predicates that are called with only variable arguments (i.e. `test(X) :- integer(X)' is optimised; `test(X) :- integer(3)' is not). Provides big speedup for fail, true, integer/1 (etc.), and many other commonly called foreign predicates. * Support for mmap() using MAP_ANON. Avoids a file-descriptor and hopefully improves portability of dynamic stacks. * Fix for Solaris 2.4 mmap() detection. * Fix: added autoconf test for using asm("nop") in pl-wam.c or use slower but more portable C alternative (fixes RS/6000 version) Version 2.0.1 ============= * FIX in garbage collector of 2.0.0 was only half the story. Should be ok now. Thanks to Thomas Hoppe for supplying me with the error report. * FIX & performance: current_functor/2 with the first argument is instantiated. * Installation: the libraries are now installed as $(prefix)/lib/$(PL)-$(PLVERSION). A possibly existing executable is moved from $(prefix)/bin/$(PL) to $(prefix)/bin/$(PL).old Version 2.0.0 ============= * Added `Quick Load File' compilation support. See qcompile/1 and qload/1. Alpha stage. * FIXED infrequent segmentation violation occurring on machines with dynamic stack management, but whose signal handler is not provided the address of the fault (Linux and Solaris 2 for example). The crash can be in various foreign predicates that use the local stack as scratch area. * Important FIX to the garbage collector. This bug may happen iff a garbage collection is invoked while clauses are active that have \+ or (a -> b ; c) constructs that are not yet active. Generally the problem is reported as an inconsistency in the relocation count. * Fix to virtual machine encoding that applies to versions compiled with gcc 2.x and whose text-space starts at a high address. * Modified absolute_file_name/2 to take specifications of the form absolute_file_name(library('shell.pl'), X). * Various fixes to the new .qlf format and support for compiliation of individual or combined sources into .qlf files. .qlf files may now be loaded as normal sourcefiles instead of only as `boot' file. Version 1.9.6: ============== * Fixed for BIG_ENDIAN machines (Intel, VAX, ...) * Windows version: added dde_execute/2 * Added Quintus compatible foreign-language (C) interface. * Changed .qlf (former .wic) format drastically. The current format gives about 30% shorter files and loads twice as fast. * Changed basic clause representation. VM op-codes are now full machine words, avoiding the need for the `XR' table management and related indirections. Simplifies the instruction set, speedup for compiler, decompiler (retract, clause) and execution (about 10%). Enlarges program-size with about 10%. Version 1.9.5: ============== alpha-2 * Fixed prolog_frame_attribute/3 for key=parent. * Added at_initialisation(+Goal) for initialisation hooks * Fixed tracer problems introduced in 1.9.5-alpla-1. alpha-1 * Moved sourcecode administration from predicate to individual clauses. Purpose: better source-level debugger support, better handling of multifile predicates. * Recompiling files holding clauses for multifile predicates now works properly. The clauses of the latest loaded file will always be the last. * Removing a predicate from a file and recompiling the file now actually removes the definition from the Prolog database, even if you are not using modules. * Added prolog_frame_attribute(Frame, clause, ClauseRef) to get a reference to the currently running clause. * Added clause_property/2 to get the source information from a specific clause. * Compiled state (-c compilation) has changed a little. The system does not load old states. Version 1.9.4. Redefining system-predicates is no longer allowed. This may be overruled using :- redefine_system_predicate(+Head). Fix in Makefile (from Kayvan Sylvan): fixes shell syntax error make install. Give warning on user-files trying to load module `user' or `system' (this is why library(system) could not be loaded). Fixed whereis/1 to find locations of predicates. Fixed trace/[1,2] to avoid low-level errors on bad specifications. Specification now also accept the much more natural ?- trace(append, fail). as a shorthand for [+fail]. Added autoloader handling to ed/1, listing/1, spy/1 and trace/2. Manipulating not-yet-loaded autoload predicates will trap the autoloader. Added hook for help-system, so we provide a decent help-window when running under the XPCE graphical environment. The hook is called show_help_file/2. Fixed rename_file/2 (bug introduced in pl-1.9.2). Fixed versions Windows-specific problems. Added prolog_to_os_filename/2 to convert between internal and external names (DOS/Windows). Integrated the 1.9.4 patches for the Windows version. Fixed to compile on AIX. Fixed compilation on some Solaris version. Version 1.9.3. Fix index/1 problem introduced in 1.9.2. Fix stack-expansion problem in all versions that lack hardware support for stack-expansion. Some cleanup in pl-gc.c to make clean compilation with -Wall and -DO_DEBUG possible. Regenerated common prototype file pl-funcs.h using mkproto tool (and some editing). Version 1.9.2. Configuration is now based on GNU's autoconf. All md-*.h files have been removed from the distribution. $arch/2, $home/1 and $version/1 have been replaced by feature/2. A predicate read_link/3 has been added to read symbolic links. Installation is tested on SunOs 4.1.3, Solaris 2.3 and Linux 1.0.9 with readline 2.0.3. Version 1.9.1. Added: Windows DDE interface, Added Unix/System-V (?) interface to dlopen() and friends to access shared objects dynamically. Version 1.9.0. Incorporation of various ports: md-netbsd.h, md-mswin.h and md-msdos.h. There is a binary distribution for Windows in win-pl.tgz of the main ftp server (swi.psy.uva.nl). The DOS and Windows versions are created using the WATCOM-C/32 toolkit. ======================================================================= Version 1.8.12. Fixed tracer option `f' (fail) used on the exit port of a goal. Thanks to Thomas Hoppe. Version 1.8.8. Fix in the parser to avoid some bad syntax-error messages. Also fixed spurious crashes trying to read bad-syntax-terms of the form ?- atom,. New in the quintus.pl library: initialization/1, random/3, numbervars/3 and absolute_file_name/3. Version 1.8.7 includes the catch/throw-like control structures block(+Label, +Goal, -Rval), fail(+Label), exit(+Label, +Rval) and !(+Label). Also new is explain(+Anything) which will try to tell you a lot of what the system knows about the term you entered. Additions and suggesions are welcome. Also new: library(bim): A partial Prolog-by-BIM (tm) compatibility package by Henk Vandecasteele. Thanks. Further fixes: * Bug in detecting stack-overflow for the PC/linux version. * Handling of SWI_HOME_DIR (fixes installation problem for XPCE/SWI-Prolog). * atom_length/2: give warning (instead of crash) on invalid data-type (e.g. unbound, term). * nth_clause/3: Removed errornous warning when cut-off and fixed returning 0-reference for defined predicates without clauses. Version 1.8.6 defines phrase/[2,3] for accessing grammar rules and fixes name/2 for numbers outside the integer range (yielding a float). A predicate nth_clause/3 is added to provide access to specific clauses of predicates. xmalloc(), xrealloc() are added to fix some problems when linking with gnu-libraries. Version 1.8.5 contains a few fixes for the SunOs-4/gcc-2.5 combination. DONOT USE GCC-2.5.[123] as the optimiser appears broken. gcc-2.5.4 is ok again. Version 1.8.4 fixes =@=/2, contains a more logical form of arg/3, fixes passing empty-string arguments from the Prolog command-line and fixes some things for old non-ansi compilers. There are some extensions to the quintus.pl compatibility library. Version 1.8.3 Fixes some more readline problems having to do with running SWI-Prolog as an inferior process under EMACS. Version 1.8.2 fixes some serious problems in the tracer intoduced by more global changes in 1.8.0. Version 1.8.1 fixes load_foreign for both SunOs 4.1.3 and PC/Linux. Extensive use of the stat(2) system call is reduced with some changes to the file administration. This speeds up loading many small files by an incredible amount, notably when reading over a (slow) network. The manual is regenerated. There are not many changes, but the PostScript files in these archives are totally different as we upgrated LaTeX and dvips. Therefore the patch file **diff-1.8.0-1.8.1** does *not* include the patches to the PostScript manual. Version 1.8.0 includes a stack shifter, enabling dynamic stacks for machines that do not offer hardware support by providing suitable access to the virtual memory management. Fixed a bug in concat/3. expand_file/2 is now sensitive to fileerrors/2 while expanding $var or ~user. More bugfixes to the readline interface. Manual page contributed by Dave Sherrat. RS6000 port no longer uses -lbsd and compiles on gcc. ================================================================ Version 1.7.2 should compile on Solaris 2.2 using gcc 2.4.5. It fixes the usual couple of portability problems, the terminal interface when connected to the XPCE graphics library. It ads line_count to predicate_property to support a future graphical debugging tool. Version 1.7.1 fixes a very serious memory allocation violation in the connection to the readline library. Make sure to update from 1.7.0! Version 1.7.0 contains a version linked with the GNU readline library for bash/tcsh compatible line editing. The library readline is distributed separately and must be installed before installing prolog. The file readline-1.1.tar.gz contains the unmodified GNU sources. librl-1.1.tar.z contains the binaries for PC/Linux. ================================================================ Version 1.6.18 contains a fix to load_foreign/[2,5] for PC/Linux. [Version 1.6.17 has been reinstalled at Jun 1 23:16 with two prototype fixes and a fix to save_program/1 necessary for the RS6000.] Version 1.6.17 fixes some minor installation problems reported for 1.6.16. The online manual has been updated for trace/[1,2]. Callback of undefined Prolog-predicates from C now correctly trap the autoloader. Analysis of the PATH variable to find the Prolog executable has been fixed. Nothing serious if you have a running system! Version 1.6.16 integrates port to 386 System-V Unix made by Eric S. Raymond (esr@snark.thyrsus.com), who also ported the shell scripts to use sh rather than csh. The new predicates trace/1 and trace/2 allow for tracing individual predicates non-interactively. Version 1.6.15 eliminates some compiler limits, fixes a bug in trail-stacks management and provides a much better port for PC/Linux. Requires Linux kernel 99pl7 or later. Version 1.6.14 provides 8 bit character support. All characters in the range 128 ... 255 are treated as lowercase letters. op/3 is fixed to actually delete operators when priority 0 is specified. Version 1.6.13 implements standard order compatible to Quintus and contains a fix of the module system which broke the Quintus.pl replacement of retractall/1. Version 1.6.12 is te result of integrating ports to LINUX, OS/2 and HP/UX with the main-stream (SunOs).