XSB-Prolog: Current Items/All Items

news, browse, commit_browser.
Should you find a bug in XSB, please report it using our bug tracking system at
 
	http://sourceforge.net/bugs/?group_id=1176
 
and also to  xsb-development@lists.sourceforge.net
svn checkout svn://svn.code.sf.net/p/xsb/src/trunk xsb-src

Syntax issues, number_chars/2, DTC2

At revision 8750.
3.7
At revision 8635.
At revision 8555.
60: *
Some improvements to writing round brackets are here. Probably I am using too much ISO built-ins instead of the internal ones.
At revision 8473
At revision 8466.
59: * Missing instantiation errors
| ?- O = alias(_), /**/ catch(open(f,write,_,[O]),error(E,_),true).

O = alias(_h189)
E = _h325

yes
| ?- O = alias(1), /**/ catch(open(f,write,_,[O]),error(E,_),true).

O = alias(1)
E = permission_error(open,source_sink,alias(1))

yes
Expected: instantiation_error and domain_error(stream_option,alias(1))
58: * integer division by zero
#229
At revision 8416.
At revision 8413.
57: * debug message
(#228)
| ?- writeq('\
').
next after back-nl: 39
''
yes
Expected: no debug message.
At revision 8406.
Updated to revision 8370.
Updated to revision 8284.
Updated to revision 8274.
56: * Regressions
Updated to revision 8273.
Updated to revision 8268.
55: * (is)/2 error
| ?- catch((T=a,X is _),error(E,_),true).
 
T = a
X = _h207
E = type_error(evaluable,_h405);
Expected: E = instantiation_error and T = _h1232
54: * error handling error
| ?- catch((Xs=[a|Xs],X is _),error(E,_),true), var(Xs).
 
no
Expected: Succeeds with E = instantiation_error
53: * replacing errors by semantically better replacements
Sometimes it is desirable to replace type errors by silent failure ; and instantiation errors by some constraints. To make this approach compatible with ISO, IF/Prolog has a list in the second argument of error/2 with terms like:
    [ valid_type = evaluable,
      culprit = _164,
      goal = ...
    ]
(See more about it in the manuals, specifically Chapter 8 Contexts, exception/2, context/2)

This term is normally not copied upon error. But first, a fitting catcher is searched. If it is catch/3, only then the error-term is copied. But if the catcher is exception_handler/3, the replacing goal is executed in the very place of the built-in that produced the error.

[user] ?- exception_handler(X > Y, error(instantiation_error, P), writeq((X>Y->P))).
_164 > _165 -> _309 ::
       [_278 :: (valid_type = evaluable) |_287 :: [
                culprit = _164,
                goal = system : exception_handler(_164 > _165,
                                     error(instantiation_error,_309),
                                     writeq((_164 > _165 -> _309))) @ user]]
or simplified:
_164 > _165 -> _309 ::
      [ valid_type = evaluable,
           culprit = _164,
              goal = system : exception_handler(_164 > _165,
                                       error(instantiation_error,_309),
                                       writeq((_164 > _165 -> _309))) @ user]
Note the sharing of _309 which makes this an infinite term. Also note that the original goal and the corresponding variables (_164 and _165) are all shared. When using catch, the term is copied:
[user] ?- catch(X > Y, error(instantiation_error, P), writeq((X>Y->P))). 
_164 > _165 -> [ valid_type = evaluable,
                 culprit = _273,
                 goal = system : catch(_273 > _291,error(instantiation_error,_294),writeq((_273 > _291 -> _294))) @ user]
In this manner it is also possible to convey the information whether or not a prticular built-in can be "restarted". It might not be possible to restart it at all, since trailing information is no longer present etc.

IF's way to print infinite terms: Only infinite termins are printed using ::.

[user] ?- current_op(50,xfx,::).
 
[user] ?- X = s(X), writeq(X),nl,fail.
_165 :: s(_165)
 
[user] ?- blam(L), X = s(L,X).
...
L     = [[[[]],[]],[[]],[]]
X     = _168 :: s([_228 :: [_230 :: [[]]|_230]|_228],_168) ;

L     = [[[[[]],[]],[[]],[]],[[[]],[]],[[]],[]]
X     = _168 :: s([_228 :: [_230 :: [_232 :: [[]]|_232]|_230]|_228],_168)
52: * Float extensions
I recommend reading a bit William Kahan's views. In particular on Java. Essentially one of his ideas is that the information whether or not some exceptional value/situation occured should be easily accessible to the programmer. In the classical "Java model" it is practically inaccessible. Only remaining values could be tested, but there is no way to know if some intermediary calculation was problematic or not. The ISO (base) model to produce Prolog-errors everywhere fits into this (as a very crude base). Further extensions are possible, but so far there has not been much interest. It seems everyone makes another extension, all of them incompatible with each other and not capable to maintain the desireable properties of IEEE floats. The ultimate answer are indeed unums, until we understand them entirely...
51: * float extension: syntax invalid
The syntax of floats does not conform to 5.5 extensions.
| ?- X is 1/0, Y is X* -1, write_canonical(f(X,Y)).
f(inf.0,-inf.0)
| ?- X is inf.0.
++Error[XSB/Runtime/P]: [Syntax] () X is inf  <--- HERE? ************ 
The text inf.0 are 3 valid tokens [inf,.,0] that could form valid Prolog syntax by adding appropriate operators. That is, either infix . or prefix inf and prefix dot. So far, every systems makes its own incompatible extension. Ideally, there is full support of the base model offered in ISO and appropriate extensions.
50: * writeq/1 and write_canonical/1 inconsistent
both should write the same for floats.
| ?- write_canonical(10.0e100).
9.9999999999999998e+100
yes
| ?- writeq(10.0e100).
99999999999999997704951326524533662844684271992415000612999597473199345218078991130326129448151154688.0000
yes
49: * superfluous message
| ?- writeq('\
').
next after back-nl: 39
''
yes
48: * too many round brackets
| ?- writeq(f(:-)+[:-]).
f((:-)) + [(:-)]
yes
| ?- writeq(:-).
(:-)
yes
expected: no brackets around :-.

There is never a reason to put round brackets around an atom that is an argument in functional notation, an element or rest of a list, or at the top. In fact, some 10+ cases could be removed by avoiding extra brackets.

47: * missing errors
| ?- X is 2^ -1.

X = 0;

no
Expected: type_error(float,2).
46: * number_chars/2
| ?- number_chars(1,[[]|_]).

no
Expected: type_error(character,[])
Updated to revision 8235.
Updated to revision 8054.
45: * loop in subsumes_term/2
| ?- X = s(X), subsumes_term(X,s(X)).
This cannot be interrupted. It would make sense to make this succeed. After all it holds that, X = s(X), X == s(X).
44: * looping unification
| ?- X = s(X), unify_with_occurs_check(X,Y).
  C-c C-c[ Break (level 1) ]
While this is perfect w.r.t. the standard ; there, this case is undefined, it would help much more to make this case succeed.
43: * manual (leftover of #39)
42: * Syntax issues
6 improvements, 2 regressions.
41: * minor issue
During compilation I now get:
While compiling XSB/lib:
++Warning[XSB]: [Compiler] format : Unused symbol C/3
Updated to revision 8041.
Updated to revision 7998.
Updated to revision 7997.
40: * manual
  1. atan/2 is not ISO. atan2/2 is ISO.
  2. subsumes_term/2 still states that variables should not be shared. But all of this has been clarified!
At revision 7993.
At revision 7980.
39: * manual (dated 2013-07-04) (local copy)
  1. p.31: and many more: s/compatab/compatib/ as in compatibility etc.
    
    ulrich@p0:/opt/gupu/src/xsb-src/XSB/docs/userman$ grep -ic compatab *.tex|grep -v :0
    builtin.tex:8
    exceptions.tex:2
    incr_tabling.tex:2
    manual1.tex:1
    rbltin.tex:1
    state.tex:5
    system.tex:6
    tables.tex:2
    
  2. p.157: the characters for and, or, leftshift, rightshift look odd.
  3. p.159: e/0: is not ISO. Use exp(1) instead.
  4. p.159: Functions from math.h: many of these are ISO.
  5. p.160: false/0: ISO missing
  6. p.165: (=)/2, (==)/2: ISO missing
  7. p.165: (?=)/2: Should read ?=(A,B) :- (A==B ; A\=B), !. (The ! is superfluous for a specification: there are no terms that are both identical and not unifiable).
  8. p.166: (@<)/2, ... (@>=)/2, compare/3, ground/1: ISO missing.
  9. p.167: subsumes_term/2: ".. Term1 and Term2 should not share any variables". This case is well-defined in ISO (and particularly useful for certain loop-checks).
  10. p.169: sort/2, keysort/2: ISO missing (the errors also lack type_error(list,nonlist)). instantiation_error happens only when the argument is a partial list.
  11. p.174: callable/1: ISO missing
  12. p.183: 6.8.1: "... while unification with an occurs check is exponential..." This is not true. Unification with occurs check is practically linear in the size of the larger term (actually there is the inverse of an Ackermann-function involved), whereas without occurs check it is linear in the size of the smaller term. So for the common case of unifying a variable with a term, it is constant instead of linear. There might be some quadratic overhead due to reference chains but that overhead exists regardless of the occurs check. Only Robinson's original algorithm was exponential.
  13. p.184: (after copy_term/2): term_variables/2 missing.
  14. p.205: call_cleanup/2 is not ISO. If it would, then it would be rather setup_call_cleanup/3.
  15. p.232: assert/1 is not ISO. (But your dependence on a particular index scheme does make sense. Already DEC10 did not specify a position for assert/1.)
  16. p.233: retractall/1: ISO missing
  17. p.335: 11.2: p(X) -> q(X). should read -->
  18. p.336: Push-back lists: Are now called semicontext.
  19. p.339: tphrase/1: "is succeeds"
  20. p.342, p.343: -> should read --> 3 times.
  21. p.345-347: Sometimes it is error/3, sometimes error/2. I hope indeed that only error/2 will be issued...
  22. p.350: "Each of the error/2 terms below can also be represented as error/3 terms, ..." That is not an ISO error.
  23. p.350: replace ".Msg" by ",Msg" 3 times.
At revision 7945.
38: *
| ?- catch(_=..[1|_],Pat,true).

Pat = error(type_error(atomic,1),in arg 2 of predicate =../2,[]);
Expected: instantiation_error.

A type error is never correct here, because _=..[1] is an instance of above goal and does succeed.

37: * floats and writeq
| ?-  X is 1/3,writeq(X).
0.3333
X = 0.3333
 
yes
| ?- X is 1/3,write_canonical(X).
0.333333333333333
X = 0.3333
 
yes
Expected: Same result as write_canonical/1.
36: * Cor.2
uninstantiation_error, op/3 errors, term_variables/2 errors, compare/3 errors, sort/2 errors, keysort/2 errors.
35: * read cannot read what writeq wrote
The following term cannot be read back. Please note that this is independent of actual ISO Prolog conformance.
| ?- V = v(-(1),-((a,b)),-(-),(-)-(-)), writeq(V).

v(-1,-(a  ','  b),--,- - -)
Ideally, this term is written as (please note the spaces):
v(- (1),- (a,b),- (-),(-)-(-))
Further case:
| ?- V = v(- (a;b)).

V = v(-(a  ';'  b))
34: * memory violation
ulrich@gupu2:~/iso-prolog$ /opt/gupu/src/xsb-cvs/XSB/bin/xsb
[xsb_configuration loaded]
[sysinitrc loaded]

XSB Version 3.3.1 (Pignoletto) of April 12, 2011
[i686-pc-linux-gnu; mode: optimal; engine: slg-wam; scheduling: local; word size: 32]
[build date: Sat Apr 30 00:51:30 CEST 2011]

| ?- catch(call(.(_,_),_,_,_),_,true).

yes
| ?- catch(call(.(H,_),_,_,_),_,true).

H = Partial Forward Continuation...
... l_write/3
... l_write/3
... file_write/2
... print_answer/1
... call/1
... catch/3
... interpreter/0
... ll_code_call/3
... call/1
... catch/3

++Memory violation occurred during evaluation.
++Please report this problem using the XSB bug tracking system accessible from
++	 http://sourceforge.net/projects/xsb
++Please supply the steps necessary to reproduce the bug.

Exiting XSB abnormally...
33: * remove is_cylic/1 and is_acyclic/1
There is acyclic_term/1 for this.
| ?- is_acyclic(X).
 
X = _h164
 
yes
| ?- is_cyclic(X).
 
no
32: * incorrect toplevel
| ?- X = f(_h192,_).
 
X = f(_h178,_h192)
31: * !->! loops
| ?- call((write(hic),!,write(hoc)->true)).
hic^C loops
Expected: Success.
| ?- call(( ( (!-> C =cond ; false) ; X = Alt ) )).
^C loops
Expected: C = cond ; X = Alt
30: * writeq syntax
Here are is some very important syntax issues: #33, #139, #181. XSB is the only different system here. And not quoting , and | when they are printed as infix operators should really go into DTC3!.
3.3.6
29: * strange update
ulrich@gupu2:/opt/gupu/src/xsb-cvs$ cvs -Q update
? nunc
? XSB/bin
? XSB/emu/extensions_xsb.h
cvs update: nonmergeable file needs merge
cvs update: revision 1.42 from repository is now in XSB/cmplib/cp_opt.xwam
cvs update: file from working directory is now in .#cp_opt.xwam.1.41
cvs update: nonmergeable file needs merge
cvs update: revision 1.124 from repository is now in XSB/cmplib/parse.xwam
cvs update: file from working directory is now in .#parse.xwam.1.123
cvs update: move away `XSB/emu/extensions_xsb.h'; it is in the way

ulrich@gupu2:/opt/gupu/src/xsb-cvs$ date
Mon Mar  5 17:42:33 CET 2012
I have never seen such a message.
28: *
| ?- catch(X =.. [],error(E,_,_),true).
 
X = _h164
E = type_error(list,[]);
Expected: domain_error(non_empty_list,[])
27: * make problems
ulrich@gupu2:/opt/gupu/src/xsb-cvs/XSB/build$ ./makexsb clean
 
make -f ../config/i686-pc-linux-gnu/topMakefile   clean
 
Cleaning up /opt/gupu/src/xsb-cvs/XSB/config/i686-pc-linux-gnu/lib
Cleaning up /opt/gupu/src/xsb-cvs/XSB/config/i686-pc-linux-gnu/saved.o
Cleaning up /opt/gupu/src/xsb-cvs/XSB/emu
Cleaning up packages
make[1]: Entering directory `/opt/gupu/src/xsb-cvs/XSB/packages'
/bin/rm -f core *.xwam *.O *~ .*~ *.bak .#*
...
make[1]: Entering directory `/opt/gupu/src/xsb-cvs/XSB/packages/xmc'
Removing all C object files...
rm -f parse *.o
Removing all Prolog bytecode files...
rm -f *.xwam *.O
Removing all libraries!
rm -f libxlp.a xlparse.so
Removing intermediate C files...
rm -f xl.tab.c xl.tab.h lex.yy.c
Removing junk...
rm -f *~ .*~ *.so
make[1]: Leaving directory `/opt/gupu/src/xsb-cvs/XSB/packages/xmc'
Cleaning up /opt/gupu/src/xsb-cvs/XSB/packages/xpath
make[1]: Entering directory `/opt/gupu/src/xsb-cvs/XSB/packages/xpath'
make[1]: *** No rule to make target `clean'.  Stop.
make[1]: Leaving directory `/opt/gupu/src/xsb-cvs/XSB/packages/xpath'
Cleaning up /opt/gupu/src/xsb-cvs/XSB/packages/xref
make[1]: Entering directory `/opt/gupu/src/xsb-cvs/XSB/packages/xref'
/bin/rm -f *.xwam *.O *~ .*~ *.bak
make[1]: Leaving directory `/opt/gupu/src/xsb-cvs/XSB/packages/xref'
Cleaning up /opt/gupu/src/xsb-cvs/XSB/packages/xsbdoc
make[1]: Entering directory `/opt/gupu/src/xsb-cvs/XSB/packages/xsbdoc'
/bin/rm -f *.xwam *.O *~ .*~ *.bak
make[1]: Leaving directory `/opt/gupu/src/xsb-cvs/XSB/packages/xsbdoc'
Cleaning up /opt/gupu/src/xsb-cvs/XSB/lib
make[1]: Entering directory `/opt/gupu/src/xsb-cvs/XSB/lib'
/bin/rm -f *.xwam *.O core *~ *.bak .#*
make[1]: Leaving directory `/opt/gupu/src/xsb-cvs/XSB/lib'
Cleaning up /opt/gupu/src/xsb-cvs/XSB/syslib
make[1]: Entering directory `/opt/gupu/src/xsb-cvs/XSB/syslib'
rm -f core *~ *.bak .#*
rm -f objfiles.saved/*
make[1]: Leaving directory `/opt/gupu/src/xsb-cvs/XSB/syslib'
Cleaning up /opt/gupu/src/xsb-cvs/XSB/cmplib
make[1]: Entering directory `/opt/gupu/src/xsb-cvs/XSB/cmplib'
rm -f core *~ *.bak .#*
rm -f objfiles.saved/*
make[1]: Leaving directory `/opt/gupu/src/xsb-cvs/XSB/cmplib'
ulrich@gupu2:/opt/gupu/src/xsb-cvs/XSB/build$ ./makexsb
 
make -f ../config/i686-pc-linux-gnu/topMakefile   devel
 
 
Preparing...
 
Making emulator...
make[1]: Entering directory `/opt/gupu/src/xsb-cvs/XSB/emu'
make[1]: Leaving directory `/opt/gupu/src/xsb-cvs/XSB/emu'
*** Warning: The command 'makedepend' is not installed. Install it to speed up compilation of XSB.
make[1]: Entering directory `/opt/gupu/src/xsb-cvs/XSB/emu'
-e 
Compiling XSB with gcc using -O3 -fno-strict-aliasing  -Wall -pipe 
 
-e .	[gcc] main_xsb.c
-e 	[gcc] auxlry.c
-e 	[gcc] biassert.c
In file included from biassert.c:40:
cell_xsb.h:115:1: warning: "GENERAL_TAGGING" redefined
In file included from box_defines.h:27,
                 from cell_xsb.h:77,
                 from biassert.c:40:
/opt/gupu/src/xsb-cvs/XSB/config/i686-pc-linux-gnu/xsb_config.h:60:1: warning: this is the location of the previous definition
In file included from export.h:28,
                 from error_xsb.h:27,
                 from biassert.c:42:
/opt/gupu/src/xsb-cvs/XSB/config/i686-pc-linux-gnu/xsb_config.h:60:1: warning: "GENERAL_TAGGING" redefined
In file included from biassert.c:40:
cell_xsb.h:115:1: warning: this is the location of the previous definition
26: *
There is no 'digit atom' type. It should be rather character.
25: * number_chars/2
There are now many cases, where a success or failure is expected, but an error occurs. Flagged with ???. But just to be sure: You need only to look into Section 2 for the moment.
24: * memory violation
| ?- number_chars(1,[[]|_])=X,catch(X,error(E,_,_),true).

X = number_chars(1,[[]|Partial Forward Continuation...
... l_write/5
... l_write/5
... l_write/5
... l_writearg/6
... l_write/3
... file_write/2
... print_answer/1
... call/1
... catch/3
... interpreter/0
... ll_code_call/3
... call/1
... catch/3

++Memory violation occurred during evaluation.
++Please report this problem using the XSB bug tracking system accessible from
++	 http://sourceforge.net/projects/xsb
++Please supply the steps necessary to reproduce the bug.
23: * number_chars/2
| ?- catch(number_chars(1,[' ',[]]),error(E,_,_),true), writeq(E).
type_error('digit atom',[' ',[]])
Expected: type_error(character,[]). So there are two differnces (apart from error/3): the type should be character. And the culprit should be [].
22: * banner not in sync
On the recently built version I get:
ulrich@gupu2:~/iso-prolog$ /opt/gupu/xsb-cvs/3.3.5/bin/xsb 
[xsb_configuration]
[sysinitrc]

XSB Version 3.3.1 (Pignoletto) of April 12, 2011
[i686-pc-linux-gnu; mode: optimal; engine: slg-wam; scheduling: local; word size: 32]
[build date: Sat Apr 30 00:51:30 CEST 2011]

| ?- X is xor(2,3).

X = 1
21: * resource error
| ?- catch((length(K,L),fail),Pat,true).
UNRECOVERABLE ERROR: Ran our of tagged address space!

Exiting XSB abnormally...
20: * (div)/2
Evaluable functor + operator declaration, for flooring division (towards minus infinity).
?- -1 =:= 2 div -3.
true.

Present in : B, ECLiPSe, GNU, IF, SWI, YAP.

19: * (^)/2
Evaluable functor, giving both integer and float.

Present in : ECLiPSe, GNU, IF, SWI, YAP.

18: * xor/2
Evaluable functor.

Present in : B, ECLiPSe, GNU, Jekejeke, SWI, YAP.

17: * subsumes_term/2
missing.

Present in: B, GNU, SWI, YAP.

16: * acyclic_term/1
| ?- is_acyclic(a+b).
++Error[XSB/Runtime/P]: [Miscellaneous]  Builtin #227 is not implemented
Expected: acyclic_term/1 is the name for it!

Present in B, GNU, (SICStus), SWI, YAP

15: * aw man
ulrich@gupu2:~/iso-prolog$ /opt/gupu/src/xsb-cvs/XSB/bin/xsb
[xsb_configuration loaded]
[sysinitrc loaded]

XSB Version 3.3.1 (Pignoletto) of April 12, 2011
[i686-pc-linux-gnu; mode: optimal; engine: slg-wam; scheduling: local; word size: 32]
[build date: Sat Apr 30 00:51:30 CEST 2011]

| ?- use_module(basics,length/2).

yes
| ?- catch(length(K,K),Pat,true).
UNRECOVERABLE ERROR: Ran our of tagged address space -- aw man!

Exiting XSB abnormally...
14: * import problem
ulrich@gupu2:~/iso-prolog$ /opt/gupu/xsb-cvs/3.2/bin/xsb
[xsb_configuration loaded]
[sysinitrc loaded]

XSB Version 3.2 (Kopi Lewak) of March 15, 2009
[i686-pc-linux-gnu; mode: optimal; engine: slg-wam; scheduling: local; word size: 32]

| ?- use_module(basics,length/2).

yes
| ?- length(Xs,2).

Xs = [_h203,_h205]

yes
| ?- call(length(Xs),2).

Xs = [_h219,_h221]

yes
| ?- use_module(inex,length/1).

yes
| ?- length(Xs,2).

Xs = [_h203,_h205]

yes
| ?- call(length(Xs),2).
++Error[XSB/Runtime/P]: [Existence (No module inex exists)]  in arg 1 of predicate load
Forward Continuation...
... machine:xsb_backtrace/1
... loader:load/1
... loader:load_pred1/1
... loader:load_pred0/1
... loader:load_pred/1
... x_interp:_$call/1
... x_interp:call_query/1
... standard:call_expose/1
... standard:catch/3
... x_interp:interpreter/0
... loader:ll_code_call/3
... standard:call_expose/1
... standard:catch/3
13: * buffer overflow
| ?- X is 10.0** -308, write_canonical(X), X == 0.
*** buffer overflow detected ***: /opt/gupu/xsb-cvs/3.2/config/i686-pc-linux-gnu/bin/xsb terminated
======= Backtrace: =========
12: * memory violation
| ?- call(inex(1),2).
Partial Forward Continuation...
... load_pred1/1
... load_pred1/1
... load_pred0/1
... load_pred/1
... _$call/1
... call_query/1
... call_expose/1
... catch/3
... interpreter/0
... ll_code_call/3
... call_expose/1
... catch/3
 
++Memory violation occurred during evaluation.
++Please report this problem using the XSB bug tracking system accessible from
++	 http://sourceforge.net/projects/xsb
++Please supply the steps necessary to reproduce the bug.
11: *
| ?- length(Xs,I),X is acos(0.9 ** I), number_chars(X,Chrs), number_chars(Y,Chrs), X \== Y.

Xs = [_h461]
I = 1
X = 0.4510
Chrs = [4,.,5,1,0,2,6,8,e,-,0,1]
Y = 0.4510
Expected: Infinite loop.
10: * error/3
The error term should contain 2 and not 3 arguments:
| ?- catch(_=.._,Pat,true), functor(Pat,F,A).
 
Pat = error(instantiation_error, in arg 2 of predicate =../2,[[137566488,137544056,137822312,137821928,137566488,137466064,137794952,137472752,137566488,137466064]])
F = error
A = 3
9: * number_chars/2
| ?- number_chars(N,['0','1']).
 
N = 1;
 
no
| ?- number_chars(1, ['0','1']).
no
Expected: Success. More details
8: * toplevel printing
| ?- X = '1'.
 
X = 1
Expected X = '1'. writeq/1.
7: * (**)/2
| ?- catch(X is-1**1.5,error(E,_),true).

X = nan
E = _h175;
Expected: E = evaluation_error(undefined)
6: * atom_chars/2
| ?- Xs=[a|Xs],atom_chars(A,Xs).
Partial Forward Continuation...
... _$call/1
... call_query/1
... call_c/1
... call_expose/1
... catch/3
... interpreter/0
... ll_code_call/3
... call_expose/1
... catch/3

++Memory violation occurred during evaluation.
++Please report this problem using the XSB bug tracking system accessible from
++	 http://sourceforge.net/projects/xsb
++Please supply the steps necessary to reproduce the bug.

Exiting XSB abnormally...
Expected: type_error(list,[a| ...])
5: * (**)/2 incorrect
** should result in a float value. Integer values are ideally produced via ^ (as an extension). (Maybe there will be some discussion on this) It is now part of DTC2
| ?- X is 2**3.

X = 8;
4: * call_cleanup/2 cut and exceptions
g3:/opt/gupu/src/XSB/build> /opt/gupu/XSB/3.2/bin/xsb
[xsb_configuration loaded]
[sysinitrc loaded]
 
XSB Version 3.2 (Kopi Lewak) of March 15, 2009
[x86_64-unknown-linux-gnu; mode: optimal; engine: slg-wam; scheduling: local; word size: 64]
 
| ?- call_cleanup((X=1;X=2),(write(cleanup(X,Y)),nl)),Y=bound,!,throw(x).
cleanup(1,bound)
Partial Forward Continuation...
  Local Stack clobbered, no backtrace available (h:0x2aaaab31cdb0,e:0x2aaaab31cde0)
 
++Memory violation occurred during evaluation.
++Please report this problem using the XSB bug tracking system accessible from
++       http://sourceforge.net/projects/xsb
++Please supply the steps necessary to reproduce the bug.
 
Exiting XSB abnormally...
Now:
| ?- call_cleanup((X=1;X=2),(write(cleanup(X,Y)),nl)),Y=bound,!,throw(x).
cleanup(1,bound)
 
++Error[XSB]: [Runtime/C] no heap space in xsb_throw_internal
++Error[XSB]: [Runtime/C] Exiting XSB abnormally...
3: setup_call_cleanup/3 needed
setup_call_cleanup(Setup, Call, Cleanup) :-
   once(Setup),
   call_cleanup(Call, Cleanup).
The difference to call_cleanup/2 is that setup_call_cleanup/3 is able to provide provisions for handling interrupts/timeouts and other asynchronous signals during Setup in a more robust fashion. Consider:
file_term(File, Term) :-
   setup_call_cleanup(
      open(File, read, Stream),
      ( repeat, read(Stream, Term), ( Term == end_of_file -> ! ; true ) ),
      close(Stream)).
The idea is to read the file term-by-term. At the end, or when the caller is satisfied, the stream is closed. But what happens, if there is an interrupt immediately after the goal open/3? The cleanup handler might not be installed at that very moment - and the Stream is never closed thereby using system resources.

Most uses of call_cleanup/2 are better handled by setup_call_cleanup/3. In many applications it is not a big problem, if something leaves some files open in case of errors, but in some like servers it is a big problem.

2: call_cleanup/2: priorities for multiple exceptions
| ?- call_cleanup(throw(goal_exception),throw(cleanup_exception)).
++Error[XSB/Runtime] Unhandled Exception: cleanup_exception
Expected:
| ?- call_cleanup(throw(goal_exception),throw(cleanup_exception)).
++Error[XSB/Runtime] Unhandled Exception: goal_exception
1: call_cleanup/2: Lost cleanup
g3:/opt/gupu/src/XSB/build> /opt/gupu/XSB/3.2/bin/xsb
[xsb_configuration loaded]
[sysinitrc loaded]
 
XSB Version 3.2 (Kopi Lewak) of March 15, 2009
[x86_64-unknown-linux-gnu; mode: optimal; engine: slg-wam; scheduling: local; word size: 64]
 
| ?- call_cleanup((X=1;X=2),(write(cleanup(X,Y)),nl)),Y=bound,throw(x).
++Error[XSB/Runtime] Unhandled Exception: x
Expected:
| ?- call_cleanup((X=1;X=2),(write(cleanup(X,Y)),nl)),Y=bound,throw(x).
cleanup(_h124,_h222)
++Error[XSB/Runtime] Unhandled Exception: x
| ?-
[ICO]NameLast modifiedSizeDescription

[DIR]Parent Directory  -  
[TXT]Item.html15-Jul-2016 01:06 18K 
[TXT]XSB-HEADER.html30-Oct-2016 15:32 34K 
[DIR]item60/21-Sep-2015 11:59 -  
[   ]manual1.pdf04-Jul-2013 11:07 2.5M 

Apache/2.2.22 (Debian) DAV/2 mod_fcgid/2.3.6 PHP/5.4.36-0+deb7u3 mod_python/3.3.1 Python/2.7.3 mod_ssl/2.2.22 OpenSSL/1.0.1e mod_perl/2.0.7 Perl/v5.14.2 Server at www.complang.tuwien.ac.at Port 80