Attempt to declare a predicate as blockable, using the block/1 directive seems to put the runtime system in a broken state, so that it will no longer run predicates that have a block rule, nor predicates delayed using when/2.
If the block directive is removed, when/2 calls function normally.
This seems to apply to both sicstus and sicstus4 dialects. As far as I know, it worked fine before the sicstus4 update, but I'm not sure when that was.
Example:
When run on a fresh run of SWI, the following file content:
Welcome to SWI-Prolog (threaded, 64 bits, version 9.2.8)
SWI-Prolog comes with ABSOLUTELY NO WARRANTY. This is free software.
Please run ?- license. for legal details.
For online help and background, visit https://www.swi-prolog.org
For built-in help, use ?- help(Topic). or ?- apropos(Word).
% library(prolog_wrap) compiled into prolog_wrap 0.00 sec, 10 clauses
% sicstus/(block) compiled into block_directive 0.00 sec, 41 clauses
% library(occurs) compiled into occurs 0.00 sec, 24 clauses
% library(error) compiled into error 0.00 sec, 100 clauses
% library(arithmetic) compiled into arithmetic 0.00 sec, 130 clauses
% library(quintus) compiled into quintus 0.00 sec, 55 clauses
% library(dialect/sicstus) compiled into sicstus 0.01 sec, 66 clauses
% library(yall) compiled into yall 0.00 sec, 71 clauses
% library(apply_macros) compiled into apply_macros 0.00 sec, 70 clauses
% library(assoc) compiled into assoc 0.00 sec, 103 clauses
% library(pairs) compiled into pairs 0.00 sec, 21 clauses
% library(clpfd) compiled into clpfd 0.08 sec, 1,283 clauses
% /Users/geraintwiggins/Library/Mobile Documents/com~apple~CloudDocs/Temp/Temp.pl compiled 0.09 sec, 8 clauses
?- mytest(a).
ERROR: Unknown procedure: prolog_wrap:'$block_helper$mytest'/1
ERROR: In:
ERROR: [13] prolog_wrap:'$block_helper$mytest'(a)
ERROR: [12] '$wrap$mytest'(a)1-st clause of '$wrap$mytest'/1
ERROR: [11] toplevel_call(user:user: ...) at /Applications/SWI-Prolog.app/Contents/swipl/boot/toplevel.pl:1317
?- when( ground(X), mytest(X)).
when(ground(X), mytest(X)).
?- when( ground(X), mytest(X)),X=a.
ERROR: Unknown procedure: prolog_wrap:'$block_helper$mytest'/1
ERROR: In:
ERROR: [20] prolog_wrap:'$block_helper$mytest'(a)
ERROR: [19] '$wrap$mytest'(a)1-st clause of '$wrap$mytest'/1
ERROR: [18] when:trigger_ground(a,user:mytest(a)) at /Applications/SWI-Prolog.app/Contents/swipl/library/when.pl:139
ERROR: [17] when:attr_unify_hook(call(when: ...),a) at /Applications/SWI-Prolog.app/Contents/swipl/library/when.pl:202
ERROR: [16] uhook(when,call(when: ...),a) at /Applications/SWI-Prolog.app/Contents/swipl/boot/attvar.pl:86
ERROR: [15] call_all_attr_uhooks(att(when,call(...),[]),a) at /Applications/SWI-Prolog.app/Contents/swipl/boot/attvar.pl:63
ERROR: [14] '$wakeup'(wakeup(att(when,...,[]),a,[])) at /Applications/SWI-Prolog.app/Contents/swipl/boot/attvar.pl:58
ERROR: [13] a=a
ERROR: [11] toplevel_call(user:user: ...) at /Applications/SWI-Prolog.app/Contents/swipl/boot/toplevel.pl:1317
ERROR:
ERROR: Note: some frames are missing due to last-call optimization.
ERROR: Re-run your program in debug mode (:- debug.) to get more detail.
^ Exception: (4) setup_call_cleanup('$toplevel':notrace(call_repl_loop_hook(begin, 0)), '$toplevel':'$query_loop'(0), '$toplevel':notrace(call_repl_loop_hook(end, 0))) ?
=======================
When the block directive is removed, the when command, above, works correctly:
Welcome to SWI-Prolog (threaded, 64 bits, version 9.2.8)
SWI-Prolog comes with ABSOLUTELY NO WARRANTY. This is free software.
Please run ?- license. for legal details.
For online help and background, visit https://www.swi-prolog.org
For built-in help, use ?- help(Topic). or ?- apropos(Word).
% library(prolog_wrap) compiled into prolog_wrap 0.00 sec, 10 clauses
% sicstus/(block) compiled into block_directive 0.00 sec, 41 clauses
% library(occurs) compiled into occurs 0.00 sec, 24 clauses
% library(error) compiled into error 0.00 sec, 100 clauses
% library(arithmetic) compiled into arithmetic 0.00 sec, 130 clauses
% library(quintus) compiled into quintus 0.00 sec, 55 clauses
% library(dialect/sicstus) compiled into sicstus 0.01 sec, 66 clauses
% library(yall) compiled into yall 0.00 sec, 71 clauses
% library(apply_macros) compiled into apply_macros 0.00 sec, 70 clauses
% library(assoc) compiled into assoc 0.00 sec, 103 clauses
% library(pairs) compiled into pairs 0.00 sec, 21 clauses
% library(clpfd) compiled into clpfd 0.08 sec, 1,283 clauses
% /Users/geraintwiggins/Library/Mobile Documents/com~apple~CloudDocs/Temp/Temp.pl compiled 0.10 sec, 4 clauses
?- when( ground(X), mytest(X)),X=a.
X = a.
?-
====================
Of course, block directives can be simulated using when/2, so this doesn't stop us using advanced prolog, but the behaviour does not match the manual, so that's why I raise it here.
Using SWI-Prolog 9.2.8 on MacOS.
Attempt to declare a predicate as blockable, using the block/1 directive seems to put the runtime system in a broken state, so that it will no longer run predicates that have a block rule, nor predicates delayed using when/2.
If the block directive is removed, when/2 calls function normally.
This seems to apply to both sicstus and sicstus4 dialects. As far as I know, it worked fine before the sicstus4 update, but I'm not sure when that was.
Example:
When run on a fresh run of SWI, the following file content:
*** produces the following output:
Welcome to SWI-Prolog (threaded, 64 bits, version 9.2.8) SWI-Prolog comes with ABSOLUTELY NO WARRANTY. This is free software. Please run ?- license. for legal details.
For online help and background, visit https://www.swi-prolog.org For built-in help, use ?- help(Topic). or ?- apropos(Word).
% library(prolog_wrap) compiled into prolog_wrap 0.00 sec, 10 clauses % sicstus/(block) compiled into block_directive 0.00 sec, 41 clauses % library(occurs) compiled into occurs 0.00 sec, 24 clauses % library(error) compiled into error 0.00 sec, 100 clauses % library(arithmetic) compiled into arithmetic 0.00 sec, 130 clauses % library(quintus) compiled into quintus 0.00 sec, 55 clauses % library(dialect/sicstus) compiled into sicstus 0.01 sec, 66 clauses % library(yall) compiled into yall 0.00 sec, 71 clauses % library(apply_macros) compiled into apply_macros 0.00 sec, 70 clauses % library(assoc) compiled into assoc 0.00 sec, 103 clauses % library(pairs) compiled into pairs 0.00 sec, 21 clauses % library(clpfd) compiled into clpfd 0.08 sec, 1,283 clauses % /Users/geraintwiggins/Library/Mobile Documents/com~apple~CloudDocs/Temp/Temp.pl compiled 0.09 sec, 8 clauses ?- mytest(a). ERROR: Unknown procedure: prolog_wrap:'$block_helper$mytest'/1 ERROR: In: ERROR: [13] prolog_wrap:'$block_helper$mytest'(a) ERROR: [12] '$wrap$mytest'(a)1-st clause of '$wrap$mytest'/1
ERROR: [11] toplevel_call(user:user: ...) at /Applications/SWI-Prolog.app/Contents/swipl/boot/toplevel.pl:1317
?- when( ground(X), mytest(X)).
when(ground(X), mytest(X)).
?- when( ground(X), mytest(X)),X=a. ERROR: Unknown procedure: prolog_wrap:'$block_helper$mytest'/1 ERROR: In: ERROR: [20] prolog_wrap:'$block_helper$mytest'(a) ERROR: [19] '$wrap$mytest'(a)1-st clause of '$wrap$mytest'/1
ERROR: [18] when:trigger_ground(a,user:mytest(a)) at /Applications/SWI-Prolog.app/Contents/swipl/library/when.pl:139
ERROR: [17] when:attr_unify_hook(call(when: ...),a) at /Applications/SWI-Prolog.app/Contents/swipl/library/when.pl:202
ERROR: [16] uhook(when,call(when: ...),a) at /Applications/SWI-Prolog.app/Contents/swipl/boot/attvar.pl:86
ERROR: [15] call_all_attr_uhooks(att(when,call(...),[]),a) at /Applications/SWI-Prolog.app/Contents/swipl/boot/attvar.pl:63
ERROR: [14] '$wakeup'(wakeup(att(when,...,[]),a,[])) at /Applications/SWI-Prolog.app/Contents/swipl/boot/attvar.pl:58
ERROR: [13] a=a
ERROR: [11] toplevel_call(user:user: ...) at /Applications/SWI-Prolog.app/Contents/swipl/boot/toplevel.pl:1317
ERROR:
ERROR: Note: some frames are missing due to last-call optimization.
ERROR: Re-run your program in debug mode (:- debug.) to get more detail.
^ Exception: (4) setup_call_cleanup('$toplevel':notrace(call_repl_loop_hook(begin, 0)), '$toplevel':'$query_loop'(0), '$toplevel':notrace(call_repl_loop_hook(end, 0))) ?
=======================
When the block directive is removed, the when command, above, works correctly:
Welcome to SWI-Prolog (threaded, 64 bits, version 9.2.8) SWI-Prolog comes with ABSOLUTELY NO WARRANTY. This is free software. Please run ?- license. for legal details.
For online help and background, visit https://www.swi-prolog.org For built-in help, use ?- help(Topic). or ?- apropos(Word).
% library(prolog_wrap) compiled into prolog_wrap 0.00 sec, 10 clauses % sicstus/(block) compiled into block_directive 0.00 sec, 41 clauses % library(occurs) compiled into occurs 0.00 sec, 24 clauses % library(error) compiled into error 0.00 sec, 100 clauses % library(arithmetic) compiled into arithmetic 0.00 sec, 130 clauses % library(quintus) compiled into quintus 0.00 sec, 55 clauses % library(dialect/sicstus) compiled into sicstus 0.01 sec, 66 clauses % library(yall) compiled into yall 0.00 sec, 71 clauses % library(apply_macros) compiled into apply_macros 0.00 sec, 70 clauses % library(assoc) compiled into assoc 0.00 sec, 103 clauses % library(pairs) compiled into pairs 0.00 sec, 21 clauses % library(clpfd) compiled into clpfd 0.08 sec, 1,283 clauses % /Users/geraintwiggins/Library/Mobile Documents/com~apple~CloudDocs/Temp/Temp.pl compiled 0.10 sec, 4 clauses ?- when( ground(X), mytest(X)),X=a. X = a.
?-
====================
Of course, block directives can be simulated using when/2, so this doesn't stop us using advanced prolog, but the behaviour does not match the manual, so that's why I raise it here.
Hope this helps.
Geraint