Did you know ... Search Documentation:
Title for pldoc(default)
Branch: stable (switch to development),
version to version

SWI-Prolog Changelog from version 6.4.1 to 6.6.0

[Nov 22 2013]

  • ADDED: Forward compatibility using ATOM_nil and ATOM_dot

[Jan 8 2013]

  • ENHANCED: Avoid that debug/3 messages from multiple threads get mixed up.

[Nov 21 2013]

  • DOC: Updated HTML readme for MacOS application
  • FIXED: Now really fixed qsave_program/2. Jos de Roo.
  • FIXED: library(pack): answered_default/1 was undefined. Nicos Angelopoulos.
  • FIXED: qsave_program('/tmp/img'). ERROR: Undefined procedure: 0/0. Jos de Roo.

[Nov 20 2013]

[Nov 19 2013]

  • PPA: Prepare making a PPA for Saucy Salamander (13.10)
  • TESTS: Fixed date test for type check of memberchk/2

[Nov 18 2013]

  • PORT: Fixed issues with _stprintf() mapping to swprintf(). This causes failure to compile under MinGW under Ubuntu 13.10, where the console opens with a title showing only "AMD," and a blank console.
  • CLEANUP: Avoid some bogus messages about uninitialised variables
  • DOC: LaTeX error

[Nov 17 2013]

  • ENHANCED: print bignums/rationals as floats using ~e without converting to GMP mpf_t types
  • BUILD: Make sure all .qlf files are gone from the tree.
  • FIXED: accounting statistics of the profiler

[Nov 16 2013]

  • DOC: Updated documentation about the profiler.
  • MODIFIED: Several details in interaction with the profiler: - profiler/2 takes new values cputime and walltime - profile/3 is replaced by profile/2, which takes an option list. - show_profile/2 is deleted. show_profile/1 now takes an option list.
  • CLEANUP: Move profile header to new pl-prof.h. Start working on different profile modes.
  • MODIFIED: Base time profiling on reported CPU time.
  • CLEANUP: Various issues and code around the execution profiler.

[Nov 15 2013]

  • FIXED: Handling break points that simply enable trace mode. Steffen Lalande.
  • FIXED: Bug#131: Loop printing errors if there is an error from initialiazing the history. Kyle Marple.
  • MODIFIED: Version and banner infrastructure: - Deleted '$welcome' predicate - Added version/0 and version/1, which is found in several Prolog implementations.
  • FIXED: Do not quote $ for shell commands in Windows.

[Nov 13 2013]

[Nov 11 2013]

  • FIXED: throw existence error if stream blob in invalid in set_stream/2

[Nov 6 2013]

  • BUILD: Ensure ./prepare also updates configure scripts if a file in ac/*.m4 has changed.

[Nov 5 2013]

  • ENHANCED: print bignums/rationals as floats without converting to GMP mpf_t types
  • PORT: Try to set JAVAPREFIX on MacOS if Oracle's Java is installed

[Nov 1 2013]

  • FIXED: clause_info/4: Be more selective in detecting swapped arguments. Patch by Matt Lilley.

[Oct 27 2013]

  • BUILD: Avoid using cpp for selecting the manual files. Now use a Prolog program.

[Oct 30 2013]

  • FIXED: mutex_statistics/0: wrong value for L_THREAD and L_MUTEX because it compensated for the wrong mutex.

[Oct 28 2013]

  • DOC: Removed docs for set_tty/2. Predicate has gone long time ago.

[Oct 31 2013]

  • WINDOWS: Added building libswipl.lib to the cross-builder
  • WINDOWS: Generate a libswipl.def

[Oct 29 2013]

  • FIXED: Make curent_functor/2 behave consistently for arity = 0 in modes (+,+) and (?,?).

[Oct 23 2013]

  • FIXED: do not include cpu_count Prolog flag in saved state
  • FIXED: Reduce risc of crashing when `hot-swapping' code in multi-threaded context. Keri Harris.

[Oct 22 2013]

  • FIXED: call/N with N>9 calling a module qualified goal. Keri Harris.

[Oct 21 2013]

[Oct 18 2013]

  • FIXED: Proper reporting and error recovery on illegal operator declarations in the module export list.
  • ADDED: string_code/3, finding a code at a given offset
  • ADDED: Support string version of "x" in arithmetic expressions.

[Oct 21 2013]

[Oct 17 2013]

  • MODIFIED: memberchk/2 reports a type error if it stumbles on a non-list. Note that it does not agressively check the list and thus memberchk(a, [a|b]) succeeds. Notably intended to capture memberchk(C, "String").
  • FIXED: Avoid instantiation error when determining locations.
  • ADDED: prolog_program_clause/2 to enumerate `interesting' clauses.

[Oct 18 2013]

  • FIXED: possible crash when removing atoms from a findall structure before it has been scanned

[Oct 17 2013]

  • FIXED: possible crash when removing atoms from a message queue before it has been scanned

[Oct 16 2013]

  • FIXED: Compensate for arg/3 atom argument in test case
  • FIXED: Avoid arg/3 on an atom (new ISO compliant exception)

[Oct 15 2013]

  • FIXED: Avoid commandline options in SICStus compatible swipl-lfr.pl
  • ADDED: list_trivial_fails/0. Based on code from Edison Mera. Included this test into check/0.
  • ADDED: prolog_walk_code/1: option clauses(+List) to process only the given clauses.
  • FIXED: clause_info/4 term-position representation for body terms of the form Var1:Var2.

[Oct 14 2013]

  • FIXED: library(arithmetic): Avoid type-error for arg/3
  • ISO: Generate a type error on arg(1, atom, X). Also small performance improvement for (non-ISO) mode arg(-,+,?).
  • MODIFIED: eos//0. I don't think this is satisfactory yet. There was something wrong with the definition, but I cannot recall the precise case.

[Oct 9 2013]

  • FIXED: Always apply canonisePath() after creating an absolute path.
  • CLEANUP: Deleted structuralEqualArg1OfRecord(). No longer used.
  • FIXED: PL_record_external(): saving wide atoms and more efficient saving of [], which is also robust against changing the notion of nil.

[Oct 8 2013]

  • FIXED: Reset suspendTrace in a new thread. This ensures that threads can be debugged, also if they are created from e.g., notrace/1. Jacco van Ossenbruggen.
  • MODIFIED: Make -f file work again if the arguments points to an existing file.
  • FIXED: Avoid using -f. Paulo Moura.

[Oct 7 2013]

  • MODIFIED: Renamed string_to_list/2 into string_codes/2. Compatibility predicate added to library(backcomp).
  • ADDED: eos//0. Also updated documentation of some predicates.
  • MODIFIED: The file_search_path/2 alias user_profile no longer includes the current working directory. Including files from the current directory is considered a security issue. The old behaviour can be restored by loading a local .plrc (Windows: pl.ini) from the global one.

    As a consequence, swipl -f file.pl no longer works. New code should use the -s flag or the new construct =swipl file.pl=.

[Oct 6 2013]

  • BUILD: Fixed makefile dependencies to avoid concurrent make errors. Roberto Bagnara.
  • FIXED: `dec10' syntax error handling for reading quasi quotations.

[Oct 5 2013]

  • FIXED: must_be(cyclic, T) and must_be(acyclic, T) used inverted error message.

[Oct 2 2013]

  • FIXED: allow Windows stand-alone applications to be called without an .exe suffix

[Sep 29 2013]

  • ENHANCED: CLP(FD): Separate parsing of reified constraints from syntax checking. This removes the declarative problem that for example both #\ 2 and #\ #\ 2 failed - it now raises a domain error in both cases, because 2 is not a Boolean value.
  • ENHANCED: CLP(FD): When clpfd_monotonic is true, ?/1 can now be omitted if a variable is already constrained to integers.

[Sep 28 2013]

  • ENHANCED: CLP(FD): Support ?(X) syntax in goal expansion.
  • ENHANCED: CLP(FD): reified tuples_in/2 now works also with clpfd_monotonic.
  • ENHANCED: CLP(FD): tuples_in/2 is now properly negated in reifications.

[Sep 26 2013]

  • ENHANCED: CLP(FD): No ?/1 wrapper for integers in residual goals.
  • ADDED: CLP(FD): New flag: clpfd_monotonic. Setting this flag to true renders CLP(FD) monotonic. ?(X) is used in CLP(FD) expressions and residual goals to denote that X is a finite domain variable, ruling out other expressions.

[Sep 16 2013]

  • FIXED: check PE module path for saved state

[Sep 13 2013]

  • ENHANCED: CLP(FD): First preparations to support monotonic constraints. Ulrich Neumerkel (i3a#313). Support X? notation which constrains X to integers in CLP(FD) expressions. A current declarative shortcoming of CLP(FD) is that it commits to interpreting variables that occur in a query as finite domain variables (= integers) instead of logical variables. For example:

    ?- X #= 3. %@ X = 3. (no further solutions)

    But X might as well stand for a different expression, for example:

    ?- X = (Y + Z), X #= 3. %@ X = Y+Z, %@ Y+Z#=3.

    Note that exchanging the goals yields a different result:

    ?- X #= 3, X = (Y + Z). %@ false.

    As another example, we have:

    ?- #\ 2. %@ false.

    because the only solution of

    ?- #\ X.

    is currently:

    %@ X = 0.

    whereas declaratively, X = (5 #= 3) is for example also a correct answer, and indeed we have:

    ?- X = (5 #= 3), #\ X. %@ X = (5#=3).

    To fix this, the (?)/1 syntax is now made available to explicitly denote finite domain variables in CLP(FD) expressions. When you add:

    :- op(5, yf, ?).

    to your programs, you can now write:

    ?- X? #= 3. %@ X = 3.

    The above example then yields:

    ?- X = (Y + Z), X? #= 3. %@ ERROR: Type error: `integer' expected, found `_G759+_G760'

    because "X?" constrains X to integers. This renders your CLP(FD) programs monotonic: adding additional goals cannot yield additional answers.

    As another example, consider again:

    ?- #\ X? . %@ X = 0.

    and contrast it with:

    ?- X = (5 #= 3), #\ X? . %@ ERROR: Type error: `integer' expected, found `5#=3'

    The convenient and declaratively problematic syntax

    ?- X #= 3. %@ X = 3.

    is currently still available. To enforce a more declarative coding style, such a query should throw an instantiation error because too little information is known about X to answer correctly. Add (?)/1 to constrain it to integers, and exclude other CLP(FD) expressions.

[Sep 7 2013]

  • ENHANCED: CLP(FD): Stronger exponentiation. Jan Burse. Example:
    ?- X^2 #= Z, X in -9.. -2.
    %@ X in -9.. -2,
    %@ X^2#=Z,
    %@ Z in 4..81.

[Sep 5 2013]

  • FIXED: expand '$source_location' clauses

[Sep 3 2013]

  • FIXED: possible crash when destroying thread message queues

[Sep 2 2013]

  • FIXED: ensure atom GC locks initialized findall mutexes

[Aug 28 2013]

  • CLEANUP: Remove unused code left from old atom-GC

[Aug 30 2013]

  • FIXED: always set argv prolog_flag
  • FIXED: calculate memory alignment of double/int64_t types
  • FIXED: Qsave for quasi_quotation_syntax property. Mike Elston.

[Aug 29 2013]

  • ENHANCED: CLP(FD): Stronger multiplication. Jan Burse. Before:
    %?- X*Y #= Z, X #>= 0, Z #>= 1.
    %@ X in 1..sup,
    %@ X*Y#=Z,
    %@ Y in inf.. -1\/1..sup,
    %@ Z in 1..sup.

    Now:

    %?- X*Y #= Z, X #>= 0, Z #>= 1. %@ X in 1..sup, %@ X*Y#=Z, %@ Y in 1..sup, %@ Z in 1..sup.

[Aug 27 2013]

  • FIXED: leave error reporting of -- long options to Prolog

[Aug 23 2013]

  • FIXED: -c command-line option (compile) to use os_argv

[Aug 22 2013]

  • ADDED: Recent file (sub)menu. Carlo Capelli.

[Aug 21 2013]

  • ENHANCED: Make list_undefined/0 call predicate_name/2 to allow for hookable messages. Paulo Moura.
  • PORT: pack_install adds -L<PrologLibDir> to LDSOFLAGS if the system is thought not to be ELF based (e.g., MacOS). Samer Abdallah.
  • PORT: Deal wit Mac OS X deployment target for wcsdup()

[Aug 20 2013]

  • DELETED: X64 and X86 submodules. These have no role since MinGW
  • DOC: Document more details of commandline processing
  • ADDED: Register .prolog as additional extension for Prolog files.
  • MODIFIED: Remove Prolog flag associate (used in the Windows version)
  • FIXED: Syntax error in WINDOWS section

[Aug 19 2013]

  • MODIFIED: No longer try to be smart about arguments in #!
  • MODIFIED: Several aspects of command line processing
  • CLEANUP: Handling of -p PathSpec and --pldoc[=port] options
  • FIXED: Updated code for new argv meaning.
  • MODIFIED: The argv Prolog flag now only contains unprocessed commandline arguments. This change is primarily for improving compatibility with other systems (e.g., YAP, SICStus). A new flag, called os_argv provides the original complete list of arguments.

    Unfortunately, some code must be updated to deal with this change. A hack to restore compatibility is to call the following before anything else in the application:

    :- current_prolog_flag(os_argv, Argv), set_prolog_flag(argv, Argv).
  • ENHANCED: CLP(FD): Give all involved constraints a propagation opportunity when a new constraint is posted and propagation is always terminating. Efficiently possible thanks to term_attvars/2. James Hogan. Example: Before:

    ?- X #> abs(X), X #> 2. %@ X in 3..sup, %@ X#>=_G6092, %@ _G6100#=abs(X), %@ _G6092 in 2..sup, %@ _G6100+1#=_G6092, %@ _G6100 in 3..sup.

    Now:

    ?- X #> abs(X), X #> 2. %@ X in 4..sup, %@ X#>=_G1033, %@ _G1041#=abs(X), %@ _G1033 in 4..sup, %@ _G1041+1#=_G1033, %@ _G1041 in 3..sup.

[Aug 18 2013]

  • ADDED: packages/swipl-win submodule

[Aug 17 2013]

  • ADDED: edit/1: allow for line-position handling.
  • ADDED: Readme file for the App.
  • FIXED: Create new thread in no-debug mode. Jan Burse.
  • ADDED: PL_thread_attach_engine(): flag PL_THREAD_NO_DEBUG to force starting the thread in nodebug mode.

[Aug 16 2013]

  • ADDED: about -> win_message_box, select_ANSI_term_colors
  • FIXED: make logic to decide on the tty_control flag platform independent
  • PORT: Add some MacOS finder integration
  • ADDED: Prolog flag apple to detect we are running on a Mac

[Aug 15 2013]

  • ADDED: PL_exit_hook() to register hooks that are called just before exit().

[Aug 14 2013]

  • DOC: Fixed and extended docs for PL_on_halt()
  • FIXED: Do not reset the stdio functions if they are set before init by the embedding system.
  • DOC: Document the flag color_term.
  • DOC: library(gensym): updated and created @see links for better alternatives

[Aug 13 2013]

[Aug 12 2013]

  • DOC: LaTeX typo
  • DOC: keysort/2
  • ENHANCED: CLP(FD): isolate global_cardinality/2 from user attributes. Before:

    %?- put_attr(A, edges, [a]), global_cardinality([A,B,C], [0-_,1-_]). %@ false.

    Now:

    %?- put_attr(A, edges, [a]), global_cardinality([A,B,C], [0-_,1-_]). %@ put_attr(A, edges, [a]), %@ A in 0..1, %@ global_cardinality([A, B, C], [0-_G4383, 1-_G4389]), %@ B in 0..1, %@ _G4383 in 0..3, %@ C in 0..1, %@ _G4389 in 0..3.

  • FIXED: Dummy empty warning if no compiler warning refers to a variable.
  • ENHANCED: CLP(FD): Better isolation from user-defined variable attributes. Example:

    :- use_module(library(clpfd)).

    distinct(Vars) :- Vars = [A,B,C,D], all_distinct(Vars), [A,B,C] ins 0..2.

    Before:

    %?- put_attr(X, edges, [x]), Vars = [X|_], distinct(Vars). %@ false.

    Now:

    %?- put_attr(X, edges, [x]), Vars = [X|_], distinct(Vars). %@ Vars = [X, _G1856, _G1859, _G1862], %@ put_attr(X, edges, [x]), %@ X in 0..2, %@ all_distinct([X, _G1856, _G1859, _G1862]), %@ _G1856 in 0..2, %@ _G1859 in 0..2.

    That is, users can freely use the "edges" attribute themselves.

  • ENHANCED: CLP(FD): Remove branch singletons.
  • FIXED: Inlined unification must revert to normal unification if occurs check is active.
  • TEST: compensate for optimization
  • FIXED: Mixup in truth of == and \== predictable warnings. Keri Harris.
  • ADDED: Move multiton detection into the compiler, so this compiles clean: == t :- (v(_A);v(_A)). ==
  • FIXED: Detection of `multitons' (broken after singleton detection extension for dealing with quasi quotations).
  • FIXED: myplus/4 in bounds.pl. Note that bounds is deprecated in favour or library(clpfd). Markus Triska.
  • ENHANCED: :- at_halt/1 is now term-expanded, such that reloading the file does not re-register the hook.

[Aug 8 2013]

  • FIXED: Apply changes that where missed due to a git conflict
  • UPDATED: Handle new PL_on_halt() interface
  • MODIFIED: Program termination: - at_halt/1 handlers can veto termination of halt/0 by calling cancel_halt/1. - PL_at_halt() handlers now have a declared return type. In the future, they will be able to cancel termination by returning a non-zero status. Now a warning is printed. - halt/1 and PL_halt() can be called from any thread.
  • FIXED: set_stream/2 issues with recent patch
  • ENHANCED: safe_goal/1, various enhancements: - Distinguish undefined predicates - Deal with library meta-predicates (security fix) - Module aware call/N support - Print context of encountered problem

[Aug 7 2013]

  • ADDED: library(sandbox): added a lot of safe primitives.
  • FIXED: safe_goal/1: Catch instantiation_error when trying to proof safety of a general goal.

[Aug 8 2013]

  • CLEANUP: Use DCG // notation for declarations
  • ENHANCED: safe_goal/1, various enhancements: - Distinguish undefined predicates - Deal with library meta-predicates (security fix) - Module aware call/N support - Print context of encountered problem
  • CLEANUP: Use DCG // notation for declarations
  • FIXED: license/1: list known licenses (found by singleton analysis)
  • ENHANCED: read_term/3: singleton detection with quasi quotations. Variables appearing only ones are searched in the quasi quotation results. If found there, they are no real singletons.
  • FIXED: license/1: list known licenses (found by singleton analysis)
  • ENHANCED: read_term/3: singleton detection with quasi quotations. Variables appearing only ones are searched in the quasi quotation results. If found there, they are no real singletons.

[Aug 7 2013]

  • ADDED: library(sandbox): added a lot of safe primitives.
  • FIXED: safe_goal/1: Catch instantiation_error when trying to proof safety of a general goal.

[Aug 8 2013]

  • MODIFIED: Make set_stream/2 behave sensibly on stream pairs. DaniĆ«l de Kok.
  • CLEANUP: Implementation of set_stream/2.
  • ADDED: Singleton checking inside \+

[Aug 7 2013]

  • DOC: var_branches style check
  • CLEANUP: Removed two useless assignments
  • FIXED: nb rbtrees (singleton)
  • MODIFIED: Setting style_check/1 and expects_dialect/1 in ~/.plrc changes the default for the session. The settings used to be scoped to the file. This scoping is now controlled by a new option scope_settings to load_files/2.
  • ADDED: style_check/1: ?- style_check(?(Style)). to return active style checks on backtracking.
  • DOC: term_expansion/4, etc.
  • DOC: Document extended singleton warnings
  • DOC: style_check/1 new no_effect option
  • DOC: user term_expansion is followed by DCG!
  • CLEANUP: Avoid new warnings in test cases. Test cases sometimes use ugly code by design ...
  • ADDED: compiler warnings for BIPS that have no effect and singleton variables in branches (semantic singletons).

[Aug 1 2013]

  • ADDED: Support for warning messages from the compiler

[Jul 30 2013]

  • ADDED: Provide prolog_load_context/2 variable_names and implemented goal/term expansion with 4 arguments to process layout information.

[Aug 7 2013]

  • FIXED: Default handling in setting (spotted by variable balance checking)
  • CLEANUP: some documentation glitches
  • ADDED: New style-check options. We will include these into the stable branch to avoid warnings on code calling style_check/1.

[Aug 6 2013]

  • TEST: Fixed test code for timeout handling.

[Aug 1 2013]

  • CLEANUP: Removed bogus test

[Jul 31 2013]

  • FIXED: Remove meta_predicate/1 declaration for '|'/2. This is since long not a predicate anymore.
  • CLEANUP: Use '$type_error'/2.

[Jul 30 2013]

  • FIXED: Colourise [:|+] meta-declaration.
  • CLEANUP: Rename $-predicates in DCG expander. This is not needed since this code is in a module. Also removed a lot of outdated comments and added some new ones.

[Aug 3 2013]

[Aug 6 2013]

  • CLEANUP: library(clpp/bounds): singletons. Not sure whether this was intended.
  • CLEANUP: Branch singletons
  • CLEANUP: Unification against unused variable
  • CLEANUP: In DCG, \+ \+ {...} leads to useless unifications. We now use { \+ \+ G }. That remains silent. Eventually, this can (and should) be improved in the DCG compiler.
  • FIXED: Emulated shell commands for non-atom arguments.
  • FIXED: library(prolog_pack): parsing of versions with * in them.
  • FIXED: Pass thread-reference in all branches
  • FIXED: library(prolog_colour) to colour "..." terminals properly
  • PORT: Cygwin: install package shared objects in the right location. Corinna Vinschen.
  • PORT: Updated Cygwin port by Corinna Vinschen

[Aug 5 2013]

  • FIXED: make/0: avoid loading files twice. Paulo Moura.

[Aug 2 2013]

  • FIXED: PL_thread_engine_attach() did not initialise the thread locale. Carlo Capelli.

[Aug 1 2013]

  • FIXED: Make sure the config var SO_PATH is set to PATH in Windows, and not WINEPATH.
  • CLEANUP: Avoid using SO_PATH for two different purposes

[Jul 30 2013]

[Jul 29 2013]

  • FIXED: Exception term if a breakpoint cannot be set.

[Jul 26 2013]

  • DOC: Provisional documentation for break_hook/6

[Jul 23 2013]

  • ADDED: Call break_hook/6 from D_BREAK

[Jul 26 2013]

  • MAINT: Use function rather than macro to make setting breakpoints easier.
  • MAINT: Debug topic msg_vmi to print virtual machine execution
  • MAINT: Small cleanup in shift messages

[Jul 25 2013]

  • CLEANUP: Introduce CA1_FVAR for virtual machine instruction arguments that access variables as `firstvar', i.e. assume that the pointed-to location is not initialised. Can be used to generalise a bit more in GC. For now, we need it for D_BREAK GC issues.

[Jul 24 2013]

  • FIXED: Use fetchop() rather than decode() to avoid D_BREAK
  • FIXED: Bug#113: Write `Prolog' numbers under locals that have a decimal point other than ".".

[Jul 23 2013]

  • FIXED: library(prolog_colour): handling of :- meta_predicate Module:Head.
  • FIXED: Typo in warning from trace interception hook

[Jul 22 2013]

  • FIXED: Line offset of breakpoint messages.

[Jul 23 2013]

  • FIXED: Bug#113: format using ~:f using a locale where the decimal point is not ".". Eugeniy Meshcheryakov.

[Jul 22 2013]

  • FIXED: clearUninitialisedVarsFrame() if it encounters a D_BREAK
  • ADDED: library(console_input), providing completion support for the qpConsole window.
  • FIXED: New Thread in pqConsole.
  • ADDED: PL_wchars_to_term(): wide-character string --> term conversion
  • ADDED: PL_put_atom_nchars(): allow for passing len as -1.
  • MODIFIED: PL_atom_wchars() now also returns a wchar_t array for ISO latin 1 atoms.
  • ADDED: PL_new_atom_nchars() and PL_new_atom_wchars() now accept (size_t)-1 as length.
  • ADDED: Support file menus for the pqConsole.

[Jul 21 2013]

  • FIXED: Thread destruction if another threads waits for my input queue.
  • BUILD: Avoid missing documentation to remove the old docs
  • BUILD: Avoid missing documentation to remove the old docs

Package RDF

[Oct 9 2013]

  • FIXED: Incorrect handling of [] at various places

Package archive

[Aug 6 2013]

  • PORT: Deal Win64 off_t handling

Package chr

[Oct 23 2013]

  • ENHANCED: silence known benign trivial failures generated by CHR compiler

[Oct 7 2013]

[Aug 6 2013]

  • ADDED: style_check(-no_effect) to compensate for some unifications that have no effect. Suggests that is some room for optimization.
  • CLEANUP: Avoid (extended) singleton warnings.
  • FIXED: delete_first_ht/3: Not only compute load, but also update it.

Package clib

[Oct 9 2013]

  • FIXED: Avoid duplicate free whe passing non-atoms to uri_resolve/3 and family.
  • FIXED: Disallow non-text atoms for Base in uri_resolve/3, etc.
  • FIXED: Share stdout and stderr on the same pipe. Patch by Matt Lilley.

[Aug 8 2013]

  • UPDATED: Handle new PL_on_halt() interface

[Aug 6 2013]

  • PORT: Cygwin updates by Corinna Vinschen

Package cpp

[Jul 29 2013]

  • DOC: Document PREDICATE0() and NAMED_PREDICATE()
  • ADDED: PREDICATE0(name) as alternative to PREDICATE(name, 0) that avoids unused parameter warnings.
  • MODIFIED: NAMED_PREDICATE() takes a string as name.
  • FIXED: PREDICATE() macro issues
  • ADDED: Macros NAMED_PREDICATE() and NAMED_PREDICATE_NONDET() to allow defining predicates that have a name that cannot be expressed as a C identifier. This patch also casts unused variables to (void) to avoid warnings. With help from Carlo Capelli.
  • MODIFIED: Accessing PREDICATE() arguments using the macros A1..A10:
    • These macros are now defined as PL_av[n] instead of _av[n] to reduce the risc for name clashes. - These macros are now also availabl as PL_A1..PL_A10 - If the macro PL_SAFE_ARG_MACROS is defined, A1..A10 will NOT be defined. This can be used to avoid conflicts with other frameworks, such as Qt5, which also uses A1...

[Jul 22 2013]

  • ADDED: Support wchar_t* almost everywhere where char* is allowed.

Package http

[Nov 15 2013]

  • FIXED: Typo (POST --> post)
  • CLEANUP: Prepare http_open/3 for more flexible option processing.

[Nov 14 2013]

  • ADDED: Bug#132: Make http_read_json/3 also work for PUT requests. Raivo Laanemets.

[Nov 13 2013]

  • FIXED: Non-determism in handling the proxy option in http_get/3. Steffen Lalande.

[Nov 10 2013]

  • INSTALL: Avoid redefining LIBDIR which is used to specify the location of the Prolog kernel

[Nov 1 2013]

  • ADDED: http:status_page to map the third (optional) argument of an http_reply exception to a specific page. Patch by Matt Lilley.

[Oct 29 2013]

  • FIXED: More HrdExtra typos.

[Oct 19 2013]

  • FIXED: Errornous option list in test suite

[Oct 18 2013]

  • DQUOTES: Set double quotes to codes for JS parser

[Oct 17 2013]

  • DQUOTES: Various fixes
  • DQUOTES: Avoid dependency on double quotes flag

[Oct 6 2013]

  • COMPAT: Send "Authorization: Basic ..." instead of "Authorization: basic ..." to accomodate broken servers. Matt Lilley.

[Aug 21 2013]

  • FIXED: Race condition if two threads try to create a new thread pool lazily.

[Aug 19 2013]

  • FIXED: Updated for new prolog flag argv

[Aug 13 2013]

  • MODIFIED: Send JSON as application/json; charset=UTF-8

[Aug 7 2013]

  • CLEANUP: More elegant implementation for computing byte-length in encoding
  • CLEANUP: Branch singletons

[Aug 6 2013]

  • CLEANUP: Another branch singleton.
  • FIXED: Singleton in interactive_httpd->authorise causes poor error message.
  • CLEANUP: Removed detection of unused OpenID NS
  • INSTALL: Avoid double installation of shared objects. Corinna Vinschen.

[Aug 5 2013]

  • DOC: Improved documentation of cookie handling

Package jpl

[Nov 5 2013]

  • PORT: Be more flexibl for finding the header files from JAVAPREFIX

[Oct 18 2013]

  • FIXED: Bug#128: Include hidden classes into jpl.jar. With patch from Andrew Santosa.
  • DQUOTES: Avoid use of character codes. Some small cleanup.

[Aug 12 2013]

Package ltx2htm

[Oct 24 2013]

  • DQUOTES: Support strings.
  • FIXED: Avoid pldoc.pl confusion due to changing the library search path

[Aug 19 2013]

  • FIXED: Updated for new prolog flag argv

Package nlp

[Aug 21 2013]

  • PORT: Deal wit Mac OS X deployment target for wcsdup()

Package pldoc

[Nov 19 2013]

[Oct 17 2013]

  • DQUOTES: Various fixes

[Oct 8 2013]

  • ENHANCED: doc_server/1: use default HTTP settings. Note that using only a single worker can lead to waiting for keep-alive timeouts.

[Aug 19 2013]

  • FIXED: Updated for new prolog flag argv
  • ADDED: Allow for a variable type in a mode declaration. Samer Abdallah.

[Aug 5 2013]

  • CLEANUP: Avoid semantic singleton message

Package plunit

[Aug 12 2013]

  • FIXED: Only share variables between options and body to maintain first-var and singleton properties.

[Aug 7 2013]

  • CLEANUP: Singletons

Package protobufs

[Oct 22 2013]

  • DQUOTES: Avoid more dependency issues

[Oct 9 2013]

  • PORT: Avoid dependency on backquoted syntax.

Package semweb

[Nov 18 2013]

  • FIXED: Possibly uninitialised variable
  • ENHANCED: Scheduling of additional literal indexing threads
  • PORT: Avoid dependency of random(), which behaves poorly on MacOS 10.9.

[Nov 10 2013]

  • INSTALL: Avoid redefining LIBDIR which is used to specify the location of the Prolog kernel

[Oct 18 2013]

  • DQUOTES: Simple fix

[Oct 9 2013]

  • FIXED: Incorrect handling of base_uri([]).

[Oct 7 2013]

[Aug 21 2013]

  • PORT: Deal wit Mac OS X deployment target for wcsdup()

[Aug 14 2013]

  • FIXED: rdf(_,_, literal(prefix(_), _)). Jacco van Ossenbruggen.

[Aug 13 2013]

[Aug 12 2013]

  • FIXED: Avoid unlocking the RDF store directory twice.

[Aug 7 2013]

  • FIXED: rdfe_undo (bug found by balanced var check)

[Aug 6 2013]

  • FIXED: Loading Turtle from a stream did not reset the stream encoding.
  • FIXED: Detecting subjects for turtle writer.

Package sgml

[Nov 17 2013]

  • ADDED: Allow for nested expressions in xpath/3. Michael Hendricks.

[Oct 17 2013]

  • DQUOTES: Various fixes

[Aug 19 2013]

  • ADDED: role attribute

Package ssl

[Oct 22 2013]

  • CLEANUP: Use standard naming for test files.
  • DQUOTES: Do not rely on flag

Package windows

[Aug 19 2013]

  • FIXED: Updated for new prolog flag argv

[Aug 6 2013]

  • CLEANUP: Do not ignore return values and delete dead code.

Package xpce

[Nov 17 2013]

  • ADDED: thread monitor: collect CPU or wall time profile.

[Nov 16 2013]

  • UPDATED: Deal with old and new profile hook.
  • UPDATED: profile frontend for changed interface.

[Nov 15 2013]

  • MODIFIED: Deleted pce_welcome/0. Remove hooking into Prolog's banner message since xpce is no longer a dominant part of SWI-Prolog.

[Oct 18 2013]

  • DQUOTES: Fixed c_mode for string handling

[Oct 17 2013]

  • DQUOTES: Handle "doc":: regardless of the double_quotes setting and various fixes.

[Oct 11 2013]

  • MODIFIED: Using string(atom) now creates an XPCE string without printf translation. This is no longer necessary since Prolog atoms do this part of the translation. Should affect little because e.g., string('\n') is still a newline.
  • SECURITY: Avoid buffer overrun by using snprintf()
  • PORT: Compatibility with SWI-Prolog V7

[Aug 20 2013]

  • FIXED: swipl-win.rc to deal with new argv

[Aug 19 2013]

  • FIXED: Updated for new prolog flag argv

[Aug 17 2013]

  • ADDED: Allow for emacs(File:Line:LinePos)

[Aug 12 2013]

  • FIXED: Locking issue that causes long delays on halt if xpce is running in separate thread.
  • FIXED: Two new singleton warnings (one was a bug).

[Aug 8 2013]

  • FIXED: Priority issue in GUI term pretty printer
  • UPDATED: Handle new PL_on_halt() interface
  • ENHANCED: Allow cancelling halt

[Aug 7 2013]

  • CLEANUP: Variable style issues.

[Aug 6 2013]

  • PORT: Rename installation helper xpce-install into xpce-copy to prevent Windows from trying to run this program as admin. Corinna Vinshen.
  • FIXED: Start xpce from a background thread.
  • PORT: update of the Cygwin port by Corinna Vinschen

[Aug 5 2013]

  • CLEANUP: Avoid more semantic singletons
  • FIXED: Semantic singletons. One fixes a bug in the class prolog_predicate.

Package zlib

[Oct 22 2013]

  • DQUOTES: Make tests independent from flag