Logtalk 2.30.7 files.

git-svn-id: https://yap.svn.sf.net/svnroot/yap/trunk@1974 b08c6af1-5177-4d33-ba66-4b1c6b8b522a
This commit is contained in:
pmoura 2007-11-06 01:58:56 +00:00
parent 42aabce1bb
commit 025dd6214f
26 changed files with 1485 additions and 0 deletions

View File

@ -0,0 +1,14 @@
================================================================
Logtalk - Open source object-oriented logic programming language
Release 2.30.7
Copyright (c) 1998-2007 Paulo Moura. All Rights Reserved.
================================================================
This folder contains a preliminary framework for defining and running
unit tests in Logtalk.
The unit tests framework is inspired on the works of Joachim Schimpf
(ECLiPSe library "test_util") and Jan Wielemaker (SWI-Prolog "plunit"
package).

View File

@ -0,0 +1,15 @@
================================================================
Logtalk - Open source object-oriented logic programming language
Release 2.30.7
Copyright (c) 1998-2007 Paulo Moura. All Rights Reserved.
================================================================
% start by loading the example:
| ?- logtalk_load(testing(loader)).
...
% take a look at the "results.txt" file in the example directory

View File

@ -0,0 +1,4 @@
:- initialization((
logtalk_load(library(lgtunit), [reload(skip)]), % allow for static binding
logtalk_load(testing))).

View File

@ -0,0 +1,134 @@
:- object(ctx_call_tests,
extends(lgtunit)).
:- info([
version is 1.0,
author is 'Paulo Moura',
date is 2007/04/17,
comment is 'Tests <</2 built-in control construct.']).
% :- initialization(::run).
% :- initialization(::run('bios_tests.txt', write)).
:- initialization(::run('results.txt', write)).
throws(ctx1, _ << goal, error(instantiation_error, _, _)).
throws(ctx2, object << _, error(instantiation_error, _, _)).
throws(ctx3, 3 << goal, error(type_error(object_identifier, 3), _, _)).
throws(ctx4, object << 3, error(type_error(callable, 3), _, _)).
throws(ctx5, ctx_call_tests << goal, error(existence_error(procedure, goal/0), _)).
throws(ctx6, xpto << goal, error(existence_error(object, xpto), _, _)).
succeeds(ctx7, user << true).
fails(ctx8, user << fail).
:- end_object.
:- object(bios_tests,
extends(lgtunit)).
:- info([
version is 1.0,
author is 'Paulo Moura',
date is 2007/04/17,
comment is 'Tests built-in objects.']).
% :- initialization(::run).
% :- initialization(::run('bios_tests.txt', write)).
:- initialization(::run('results.txt', append)).
succeeds(all, (setof(Obj, (current_object(Obj), object_property(Obj, built_in)), Objs), Objs == [debugger,logtalk,user])).
succeeds(user0, current_object(user)).
succeeds(user1, object_property(user, built_in)).
succeeds(user2, object_property(user, static)).
succeeds(debugger0, current_object(debugger)).
succeeds(debugger1, object_property(debugger, built_in)).
succeeds(debugger2, object_property(debugger, static)).
succeeds(logtalk0, current_object(logtalk)).
succeeds(logtalk1, object_property(logtalk, built_in)).
succeeds(logtalk2, object_property(logtalk, static)).
throws(co0, current_object(1), error(type_error(object_identifier, 1), _)).
:- end_object.
:- object(list_tests,
extends(lgtunit)).
:- info([
version is 1.0,
author is 'Paulo Moura',
date is 2007/04/17,
comment is 'Tests for the library object "list".']).
% :- initialization(::run).
% :- initialization(::run('list_tests.txt', write)).
:- initialization(::run('results.txt', append)).
setup :-
current_logtalk_flag(report, Value),
set_logtalk_flag(report, off),
logtalk_load(library(types_loader), [reload(skip)]),
set_logtalk_flag(report, Value),
^^setup.
fails(member0, list << member(_, [])).
succeeds(member1, list << member(1, [1,2,3])).
succeeds(member2, (findall(X, list << member(X, [1,2,3]), L), L == [1,2,3])).
succeeds(length, (list << length([1,2,3], Length), Length =:= 3)).
:- end_object.
:- object(dyn_tests,
extends(lgtunit)).
:- info([
version is 1.1,
author is 'Paulo Moura',
date is 2007/09/15,
comment is 'Tests dynamic objects and dynamic predicates.']).
% :- initialization(::run).
% :- initialization(::run('dyn_tests.txt', write)).
:- initialization(::run('results.txt', append)).
setup :-
create_object(dyn_test, [], [], []).
succeeds(dyn, This << goal) :-
this(This).
goal :-
\+ dyn_test::current_predicate(_),
dyn_test::asserta(a(1)),
dyn_test::current_predicate(a/1),
dyn_test::predicate_property(a(_), public),
dyn_test::predicate_property(a(_), dynamic),
dyn_test::predicate_property(a(_), declared_in(dyn_test)),
dyn_test::predicate_property(a(_), defined_in(dyn_test)),
dyn_test::assertz(a(2)),
dyn_test::retractall(a(_)),
\+ dyn_test::a(_),
dyn_test::predicate_property(a(_), defined_in(dyn_test)), % closed-world assumption
dyn_test::current_predicate(a/1),
dyn_test::abolish(a/1),
\+ dyn_test::predicate_property(a(_), declared_in(dyn_test)),
\+ dyn_test::predicate_property(a(_), defined_in(dyn_test)),
\+ dyn_test::current_predicate(_).
cleanup :-
abolish_object(dyn_test).
:- end_object.

View File

@ -0,0 +1,11 @@
================================================================
Logtalk - Open source object-oriented logic programming language
Release 2.30.7
Copyright (c) 1998-2007 Paulo Moura. All Rights Reserved.
================================================================
To load this example and for sample queries, please see the SCRIPT file.
This folder contains examples of multi-threading barrier synchronization.

View File

@ -0,0 +1,22 @@
================================================================
Logtalk - Open source object-oriented logic programming language
Release 2.30.7
Copyright (c) 1998-2007 Paulo Moura. All Rights Reserved.
================================================================
% start by loading the loading the example:
| ?- logtalk_load(barriers(loader)).
...
% run example:
| ?- beatles::sing_along.
hello(1)hello(4)hello(2)hello(3)
goodbye(2)goodbye(1)goodbye(3)goodbye(4)
Yes

View File

@ -0,0 +1,36 @@
:- object(beatles).
:- info([
version is 1.0,
author is 'Paulo Moura',
date is 2007/10/23,
comment is 'Simple example of using a barrier to synchronize a set of threads.']).
:- threaded.
:- public(sing_along/0).
:- mode(sing_along, one).
:- info(sing_along/0, [
comment is 'Wait for all threads to say "hello" and then proceed with the threads saying "goodbye".']).
:- uses(random, [random/3]).
sing(Thread) :-
random(1, 3, BusyHello), thread_sleep(BusyHello), % spend some time before saying hello
write(hello(Thread)), flush_output,
threaded_notify(ready(Thread)), % notify barrier that you have arrived
threaded_wait(go(Thread)), % wait for green light to cross the barrier
random(1, 3, BusyGoodbye), thread_sleep(BusyGoodbye), % spend some time before saying goodbye
write(goodbye(Thread)), flush_output.
sing_along :-
threaded_ignore(sing(1)), % start the threads
threaded_ignore(sing(2)),
threaded_ignore(sing(3)),
threaded_ignore(sing(4)),
threaded_wait([ready(1), ready(2), ready(3), ready(4)]), % wait for all threads to reach the barrier
nl, write('Enough of hellos! Time for goodbyes!'), nl,
threaded_notify([go(1), go(2), go(3), go(4)]). % give green light to all threads to cross the barrier
:- end_object.

View File

@ -0,0 +1,4 @@
:- initialization((
logtalk_load(library(random_loader), [reload(skip)]),
logtalk_load(beatles))).

View File

@ -0,0 +1,13 @@
================================================================
Logtalk - Open source object-oriented logic programming language
Release 2.30.7
Copyright (c) 1998-2007 Paulo Moura. All Rights Reserved.
================================================================
To load this example and for sample queries, please see the SCRIPT file.
This folder contains single-threaded and multi-threaded implementations
of the Takeuchi function (recursive arithmetic). The multi-threaded version
uses three threads per recursive call.

View File

@ -0,0 +1,54 @@
================================================================
Logtalk - Open source object-oriented logic programming language
Release 2.30.7
Copyright (c) 1998-2007 Paulo Moura. All Rights Reserved.
================================================================
% load the example:
| ?- logtalk_load(tak(loader)).
...
% single-threaded version:
| ?- time(tak::tak_st(18, 12, 6, R)).
% 254,474 inferences, 1.44 CPU in 1.47 seconds (98% CPU, 176718 Lips)
R = 7
Yes
% multi-threaded version:
| ?- time(tak::tak_mt(18, 12, 6, R)).
% 202 inferences, 1.45 CPU in 0.77 seconds (188% CPU, 139 Lips)
R = 7
Yes
% single-threaded version:
| ?- time(tak::tak_st(21, 14, 7, R)).
% 1,583,066 inferences, 12.40 CPU in 12.53 seconds (99% CPU, 127667 Lips)
R = 14
Yes
% multi-threaded version:
| ?- time(tak::tak_mt(21, 14, 7, R)).
% 122 inferences, 11.98 CPU in 7.74 seconds (155% CPU, 10 Lips)
R = 14
Yes

View File

@ -0,0 +1,3 @@
:- initialization(
logtalk_load(tak)).

View File

@ -0,0 +1,52 @@
:- object(tak).
:- info([
version is 1.0,
author is 'Paulo Moura',
date is 2007/07/15,
comment is 'Takeuchi function (recursive arithmetic).']).
:- threaded.
:- public(tak_st/4).
:- mode(tak_st(+integer, +integer, +integer, -integer), one).
:- info(tak_st/4, [
comment is 'Single-threaded version of Takeuchi function.',
argnames is ['X', 'Y', 'Z', 'R']]).
:- public(tak_mt/4).
:- mode(tak_mt(+integer, +integer, +integer, -integer), one).
:- info(tak_mt/4, [
comment is 'Multi-threaded version of Takeuchi function.',
argnames is ['X', 'Y', 'Z', 'R']]).
tak_st(X, Y, Z, A):-
X =< Y,
Z = A.
tak_st(X, Y, Z, A):-
X > Y,
X1 is X - 1,
tak_st(X1, Y, Z, A1),
Y1 is Y - 1,
tak_st(Y1, Z, X, A2),
Z1 is Z - 1,
tak_st(Z1, X, Y, A3),
tak_st(A1, A2, A3, A).
tak_mt(X, Y, Z, A):-
X =< Y,
Z = A.
tak_mt(X, Y, Z, A):-
X > Y,
X1 is X - 1,
Y1 is Y - 1,
Z1 is Z - 1,
threaded((
tak_st(X1, Y, Z, A1),
tak_st(Y1, Z, X, A2),
tak_st(Z1, X, Y, A3)
)),
tak_mt(A1, A2, A3, A).
:- end_object.

View File

@ -0,0 +1,71 @@
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Logtalk - Open source object-oriented logic programming language
% Release 2.30.7
%
% Copyright (c) 1998-2007 Paulo Moura. All Rights Reserved.
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
:- import stat_set_flag/2 from machine. % workaround for compiling/loading source files
:- stat_set_flag(79, 1). % when more than one thread is active
:- compiler_options([xpp_on]).
#include ../compiler/logtalk.pl
% tables of defined events and monitors
:- thread_shared('$lgt_before_'(_, _, _, _, _)).
:- thread_shared('$lgt_after_'(_, _, _, _, _)).
% tables of loaded entities and respective relationships
:- thread_shared('$lgt_current_protocol_'(_, _, _)).
:- thread_shared('$lgt_current_category_'(_, _, _, _)).
:- thread_shared('$lgt_current_object_'(_, _, _, _, _, _, _, _)).
:- thread_shared('$lgt_implements_protocol_'(_, _, _)).
:- thread_shared('$lgt_imports_category_'(_, _, _)).
:- thread_shared('$lgt_instantiates_class_'(_, _, _)).
:- thread_shared('$lgt_specializes_class_'(_, _, _)).
:- thread_shared('$lgt_extends_protocol_'(_, _, _)).
:- thread_shared('$lgt_extends_object_'(_, _, _)).
% table of loaded files
:- thread_shared('$lgt_loaded_file_'(_, _)).
% debugger status and tables
:- thread_shared('$lgt_debugging_'(_)).
:- thread_shared('$lgt_dbg_debugging_').
:- thread_shared('$lgt_dbg_tracing_').
:- thread_shared('$lgt_dbg_skipping_').
:- thread_shared('$lgt_dbg_spying_'(_, _)).
:- thread_shared('$lgt_dbg_spying_'(_, _, _, _)).
:- thread_shared('$lgt_dbg_leashing_'(_)).
% runtime flags
:- thread_shared('$lgt_current_flag_'(_, _)).
% static binding caches
:- thread_shared('$lgt_static_binding_entity_'(_)).
:- thread_shared('$lgt_obj_static_binding_cache_'(_, _, _, _)).
:- thread_shared('$lgt_ctg_static_binding_cache_'(_, _, _, _, _, _)).
% lookup caches for messages to an object, messages to self, and super calls
:- thread_shared('$lgt_obj_lookup_cache_'(_, _, _, _)).
:- thread_shared('$lgt_self_lookup_cache_'(_, _, _, _)).
:- thread_shared('$lgt_super_lookup_cache_'(_, _, _, _, _)).
% lookup cache for asserting and retracting dynamic facts
:- thread_shared('$lgt_db_lookup_cache_'(_, _, _, _, _)).
% table of library paths
:- thread_shared(logtalk_library_path(_, _)).
% compiler hook goal:
:- thread_shared('$lgt_hook_goal_'(_, _)).
% multi-threading tags
:- thread_shared('$lgt_threaded_tag_counter'(_)).

View File

@ -0,0 +1,19 @@
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Logtalk - Open source object-oriented logic programming language
% Release 2.30.7
%
% Copyright (c) 1998-2007 Paulo Moura. All Rights Reserved.
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
:- os(system('ln -sf $LOGTALKUSER/configs/qu.config $LOGTALKUSER/configs/qu.pl')),
fcompile('$LOGTALKUSER/configs/qu.pl', [assemble_only(true)]),
load('$LOGTALKUSER/configs/qu.qo'),
os(system('ln -sf $LOGTALKHOME/compiler/logtalk.pl $LOGTALKUSER/.logtalk.pl')),
fcompile('$LOGTALKUSER/.logtalk.pl', [assemble_only(true), object_file('$LOGTALKUSER/.logtalk.qo'), string_table(256)]),
load('$LOGTALKUSER/.logtalk.qo'),
fcompile('$LOGTALKUSER/libpaths/libpaths.pl', [assemble_only(true)]),
load('$LOGTALKUSER/libpaths/libpaths.qo').

View File

@ -0,0 +1,16 @@
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% Logtalk - Open source object-oriented logic programming language
% Release 2.30.7
%
% Copyright (c) 1998-2007 Paulo Moura. All Rights Reserved.
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
:- import expand_atom/2 from standard.
:- expand_atom('$LOGTALKUSER/configs/xsb.config', Config), reconsult(Config).
:- expand_atom('$LOGTALKHOME/integration/logtalk_comp_xsbmt.pl', Compiler), reconsult(Compiler).
:- expand_atom('$LOGTALKUSER/libpaths/libpaths.pl', Libpaths), reconsult(Libpaths).

60
Logtalk/integration/qplgt.sh Executable file
View File

@ -0,0 +1,60 @@
#/bin/sh
## ================================================================
## Logtalk - Open source object-oriented logic programming language
## Release 2.30.7
##
## Copyright (c) 1998-2007 Paulo Moura. All Rights Reserved.
## ================================================================
if ! [ "$LOGTALKHOME" ]; then
echo "The environment variable LOGTALKHOME should be defined first, pointing"
echo "to your Logtalk installation directory!"
echo "Trying the default locations for the Logtalk installation..."
if [ -d "/usr/local/share/logtalk" ]; then
LOGTALKHOME=/usr/local/share/logtalk
echo "... using Logtalk installation found at /usr/local/share/logtalk"
elif [ -d "/usr/share/logtalk" ]; then
LOGTALKHOME=/usr/share/logtalk
echo "... using Logtalk installation found at /usr/share/logtalk"
elif [ -d "/opt/local/share/logtalk" ]; then
LOGTALKHOME=/opt/local/share/logtalk
echo "... using Logtalk installation found at /opt/local/share/logtalk"
elif [ -d "/opt/share/logtalk" ]; then
LOGTALKHOME=/opt/share/logtalk
echo "... using Logtalk installation found at /opt/share/logtalk"
else
echo "... unable to locate Logtalk installation directory!"
echo
exit 1
fi
echo
elif ! [ -d "$LOGTALKHOME" ]; then
echo "The environment variable LOGTALKHOME points to a non-existing directory!"
echo "Its current value is: $LOGTALKHOME"
echo "The variable must be set to your Logtalk installation directory!"
echo
exit 1
fi
export LOGTALKHOME
if ! [ "$LOGTALKUSER" ]; then
echo "The environment variable LOGTALKUSER should be defined first, pointing"
echo "to your Logtalk user directory!"
echo "Trying the default location for the Logtalk user directory..."
export LOGTALKUSER=$HOME/logtalk
if [ -d "$LOGTALKUSER" ]; then
echo "... using Logtalk user directory found at $LOGTALKUSER"
else
echo "... Logtalk user directory not found at default location. Creating a"
echo "new Logtalk user directory by running the \"cplgtdirs\" shell script:"
cplgtdirs
fi
elif ! [ -d "$LOGTALKUSER" ]; then
echo "Cannot find \$LOGTALKUSER directory! Creating a new Logtalk user directory"
echo "by running the \"cplgtdirs\" shell script:"
cplgtdirs
fi
echo
exec qp -s 3072 -d 1024 -h 2048 -g "['$LOGTALKHOME/integration/logtalk_qp.pl']." "$@"

60
Logtalk/integration/xsbmtlgt.sh Executable file
View File

@ -0,0 +1,60 @@
#/bin/sh
## ================================================================
## Logtalk - Open source object-oriented logic programming language
## Release 2.30.7
##
## Copyright (c) 1998-2007 Paulo Moura. All Rights Reserved.
## ================================================================
if ! [ "$LOGTALKHOME" ]; then
echo "The environment variable LOGTALKHOME should be defined first, pointing"
echo "to your Logtalk installation directory!"
echo "Trying the default locations for the Logtalk installation..."
if [ -d "/usr/local/share/logtalk" ]; then
LOGTALKHOME=/usr/local/share/logtalk
echo "... using Logtalk installation found at /usr/local/share/logtalk"
elif [ -d "/usr/share/logtalk" ]; then
LOGTALKHOME=/usr/share/logtalk
echo "... using Logtalk installation found at /usr/share/logtalk"
elif [ -d "/opt/local/share/logtalk" ]; then
LOGTALKHOME=/opt/local/share/logtalk
echo "... using Logtalk installation found at /opt/local/share/logtalk"
elif [ -d "/opt/share/logtalk" ]; then
LOGTALKHOME=/opt/share/logtalk
echo "... using Logtalk installation found at /opt/share/logtalk"
else
echo "... unable to locate Logtalk installation directory!"
echo
exit 1
fi
echo
elif ! [ -d "$LOGTALKHOME" ]; then
echo "The environment variable LOGTALKHOME points to a non-existing directory!"
echo "Its current value is: $LOGTALKHOME"
echo "The variable must be set to your Logtalk installation directory!"
echo
exit 1
fi
export LOGTALKHOME
if ! [ "$LOGTALKUSER" ]; then
echo "The environment variable LOGTALKUSER should be defined first, pointing"
echo "to your Logtalk user directory!"
echo "Trying the default location for the Logtalk user directory..."
export LOGTALKUSER=$HOME/logtalk
if [ -d "$LOGTALKUSER" ]; then
echo "... using Logtalk user directory found at $LOGTALKUSER"
else
echo "... Logtalk user directory not found at default location. Creating a"
echo "new Logtalk user directory by running the \"cplgtdirs\" shell script:"
cplgtdirs
fi
elif ! [ -d "$LOGTALKUSER" ]; then
echo "Cannot find \$LOGTALKUSER directory! Creating a new Logtalk user directory"
echo "by running the \"cplgtdirs\" shell script:"
cplgtdirs
fi
echo
exec xsb-mt --shared_predicates -l -e "['$LOGTALKHOME/integration/logtalk_xsbmt.pl']." "$@"

140
Logtalk/library/lgtunit.lgt Normal file
View File

@ -0,0 +1,140 @@
:- object(lgtunit).
:- info([
version is 0.2,
author is 'Paulo Moura',
date is 2007/08/27,
comment is 'Logtalk unit test framework.']).
:- public(succeeds/2).
:- mode(succeeds(+atom, @callable), zero_or_more).
:- info(succeeds/2, [
comment is 'Defines a test goal which is expected to succeed.',
argnames is ['Test', 'Goal']]).
:- public(fails/2).
:- mode(fails(+atom, @callable), zero_or_more).
:- info(fails/2, [
comment is 'Defines a test goal which is expected to fail.',
argnames is ['Test', 'Goal']]).
:- public(throws/3).
:- mode(throws(+atom, @callable, @nonvar), zero_or_more).
:- info(throws/3, [
comment is 'Defines a test goal which is expected to throw an error.',
argnames is ['Test', 'Goal', 'Error']]).
:- public(run/2).
:- mode(run(+atom, +atom), zero_or_one).
:- info(run/2, [
comment is 'Runs the unit tests, writing the results to the specified file. Mode can be either "write" (to create a new file) or "append" (to add results to an existing file).',
argnames is ['File', 'Mode']]).
:- public(run/0).
:- mode(run, zero_or_one).
:- info(run/0, [
comment is 'Runs the unit tests, writing the results to the current output stream.']).
:- protected(setup/0).
:- mode(setup, zero_or_one).
:- info(setup/0, [
comment is 'Setup environment before running the test. Defaults to the goal true.']).
:- protected(test/0).
:- mode(test, zero_or_one).
:- info(test/0, [
comment is 'Executes the tests. By default, starts with the "succeeds" tests, followed by the "fails" tests, and than the "throws" tests.']).
:- protected(cleanup/0).
:- mode(cleanup, zero_or_one).
:- info(cleanup/0, [
comment is 'Cleanup environment after running the test. Defaults to the goal true.']).
% by default, no test setup is needed:
setup.
% by default, run all "succeeds", "fails", and "throws" tests:
test :-
test_succeeds,
test_fails,
test_throws.
test_succeeds :-
forall(::succeeds(Test, Goal), test_succeeds(Test, Goal)).
test_succeeds(Test, Goal) :-
( catch({Goal}, _, fail) ->
passed_test(Test, Goal)
; failed_test(Test, Goal)
).
test_fails :-
forall(::fails(Test, Goal), test_fail(Test, Goal)).
test_fail(Test, Goal) :-
( catch(\+ {Goal}, _, fail) ->
passed_test(Test, Goal)
; failed_test(Test, Goal)
).
test_throws :-
forall(::throws(Test, Goal, Error), test_throws(Test, Goal, Error)).
test_throws(Test, Goal, Error) :-
( catch({Goal}, Ball, ((Ball = Error -> passed_test(Test, Goal); failed_test(Test, Goal)), Flag = error)) ->
( var(Flag) ->
failed_test(Test, Goal)
; true
)
; failed_test(Test, Goal)
).
passed_test(Test, _Goal) :-
self(Self),
write('= passed test '), writeq(Test), write(' in object '), writeq(Self), nl.
failed_test(Test, _Goal) :-
self(Self),
write('= failed test '), writeq(Test), write(' in object '), writeq(Self), nl.
% by default, no test cleanup is needed:
cleanup.
run(File, Mode) :-
open(File, Mode, Stream),
current_output(Output),
set_output(Stream),
::run,
set_output(Output),
close(Stream).
run :-
self(Self),
write('% running tests from object '), writeq(Self), nl,
( catch(::setup, Error, (broken(setup, Error), fail)) ->
( catch(::test, Error, (broken(test, Error), Flag = error)) ->
do_cleanup,
( var(Flag) ->
write('% completed tests from object '), writeq(Self), nl
; write('% test run failed'), nl
)
; do_cleanup,
write('! test run failed for object '), writeq(Self), nl,
write('% test run failed'), nl
)
; write('! test setup failed for object '), writeq(Self), nl
).
do_cleanup :-
self(Self),
( catch(::cleanup, Error, (broken(cleanup, Error), fail)) ->
true
; write('! test cleanup failed for object '), writeq(Self), nl
).
broken(Step, Error) :-
self(Self),
write('! broken '), write(Step), write(' for object '), writeq(Self), write(': '), write(Error), nl.
:- end_object.

View File

@ -0,0 +1,15 @@
================================================================
Logtalk - Open source object-oriented logic programming language
Release 2.30.7
Copyright (c) 1998-2007 Paulo Moura. All Rights Reserved.
================================================================
The "lgtunit.lgt" file contains a preliminary framework for defining
and running unit tests in Logtalk.
The unit tests framework is inspired on the works of Joachim Schimpf
(ECLiPSe library "test_util") and Jan Wielemaker (SWI-Prolog "plunit"
package).

View File

@ -0,0 +1,75 @@
<?xml version="1.0" encoding="utf-8"?>
<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.1//EN"
"http://www.w3.org/TR/xhtml11/DTD/xhtml11.dtd">
<html xmlns="http://www.w3.org/1999/xhtml" xml:lang="en">
<head>
<meta http-equiv="content-type" content="application/xml+xhtml; charset=utf-8" />
<title>Logtalk built-in predicate: threaded_call/1-2</title>
<link rel="stylesheet" href="../../screen.css" type="text/css" media="screen"/>
<link rel="stylesheet" href="../../print.css" type="text/css" media="print"/>
</head>
<body>
<div class="top-left">Logtalk reference manual</div>
<div class="top-right">Built-in predicate: threaded_call/1-2</div>
<div class="bottom-left"><span class="page"/></div>
<div class="bottom-right"><span class="page"/></div>
<div class="navtop"><a href="../../index.html">contents</a> &gt; <a href="../index.html">reference manual</a> &gt; <a href="../index.html#builtins">built-in predicates</a></div>
<h2 id="builtins_threaded_call1_2" class="codenp">threaded_call/1-2</h2>
<h4>Description</h4>
<pre>threaded_call(Goal)
threaded_call(Goal, Tag)</pre>
<p>
Proves <code>Goal</code> asynchronously using a new thread. The argument can be a message sending goal. Calls to this predicate always succeeds and return immediately. The results (success, failure, or exception) are sent back to the message queue of the object containing the call (<em>this</em>); they can be retrieved by calling the <a title="Consult reference manual" href="threaded_exit1_2.html"><code>threaded_exit/1</code></a> predicate.
</p>
<p>
The variant <code>threaded_call/2</code> returns a threaded call identifier tag that can be used with the <a title="Consult reference manual" href="threaded_exit1_2.html"><code>threaded_exit/2</code></a> predicate. Tags shall be considered as an opaque term; users shall not rely on its type.
</p>
<h4>Template and modes</h4>
<pre>threaded_call(@callable)
threaded_call(@callable, -nonvar)</pre>
<h4>Errors</h4>
<dl>
<dt>Goal is a variable:</dt>
<dd><code>instantiation_error</code></dd>
<dt>Goal is neither a variable nor a callable term:</dt>
<dd><code>type_error(callable, Goal)</code></dd>
<dt>Tag is not a variable:</dt>
<dd><code>type_error(variable, Goal)</code></dd>
</dl>
<h4>Examples</h4>
<dl>
<dt>Prove <code>Goal</code> asynchronously in a new thread:</dt>
<dd><code>threaded_call(Goal)</code></dd>
<dt>Prove <code>::Message</code> asynchronously in a new thread:</dt>
<dd><code>threaded_call(::Message)</code></dd>
<dt>Prove <code>Object::Message</code> asynchronously in a new thread:</dt>
<dd><code>threaded_call(Object::Message)</code></dd>
</dl>
<div class="footer">
<div class="copyright">
<span>Copyright &copy; <a href="mailto:pmoura@logtalk.org">Paulo Moura</a> &mdash; <a href="http://logtalk.org">Logtalk.org</a></span><br/>
<span>Last updated on: September 15, 2007</span>
</div>
<div class="navbottom">
<span><a href="../index.html#builtins">previous</a> | <a href="../../glossary.html">glossary</a> | <a href="threaded_once1_2.html">next</a></span><br/>
<span><a href="http://validator.w3.org/check/referer">XHTML</a> + <a href="http://jigsaw.w3.org/css-validator/check/referer">CSS</a></span>
</div>
</div>
</body>
</html>

View File

@ -0,0 +1,80 @@
<?xml version="1.0" encoding="utf-8"?>
<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.1//EN"
"http://www.w3.org/TR/xhtml11/DTD/xhtml11.dtd">
<html xmlns="http://www.w3.org/1999/xhtml" xml:lang="en">
<head>
<meta http-equiv="content-type" content="application/xml+xhtml; charset=utf-8" />
<title>Logtalk built-in predicate: threaded_exit/1-2</title>
<link rel="stylesheet" href="../../screen.css" type="text/css" media="screen"/>
<link rel="stylesheet" href="../../print.css" type="text/css" media="print"/>
</head>
<body>
<div class="top-left">Logtalk reference manual</div>
<div class="top-right">Built-in predicate: threaded_exit/1-2</div>
<div class="bottom-left"><span class="page"/></div>
<div class="bottom-right"><span class="page"/></div>
<div class="navtop"><a href="../../index.html">contents</a> &gt; <a href="../index.html">reference manual</a> &gt; <a href="../index.html#builtins">built-in predicates</a></div>
<h2 id="builtins_threaded_exit1_2" class="codenp">threaded_exit/1-2</h2>
<h4>Description</h4>
<pre>threaded_exit(Goal)
threaded_exit(Goal, Tag)</pre>
<p>
Retrieves the result of proving <code>Goal</code> in a new thread. This predicate blocks execution until the reply is sent to the <em>this</em> message queue by the thread executing the goal. When there is no thread proving the goal, the predicate generates an exception. This predicate is non-deterministic, providing access to any alternative solutions of its argument.
</p>
<p>
The argument of this predicate should be a <em>variant</em> of the argument of the corresponding <a href="threaded_call1_2.html">threaded_call/1</a> call. When the predicate argument is subsumed by the <a href="threaded_call1_2.html">threaded_call/1</a> call argument, the <code>threaded_exit/1</code> call will succeed iff its argument is a solution of the (more general) goal.
</p>
<p>
The variant <code>threaded_exit/2</code> accepts a threaded call identifier tag generated by the calls to the <a title="Consult reference manual" href="threaded_call1_2.html"><code>threaded_call/2</code></a> and <a title="Consult reference manual" href="threaded_once1_2.html"><code>threaded_once/2</code></a> predicates. Tags shall be considered as an opaque term; users shall not rely on its type.
</p>
<h4>Template and modes</h4>
<pre>threaded_exit(+callable)
threaded_exit(+callable, +nonvar)</pre>
<h4>Errors</h4>
<dl>
<dt>Goal is a variable:</dt>
<dd><code>instantiation_error</code></dd>
<dt>Goal is neither a variable nor a callable term:</dt>
<dd><code>type_error(callable, Goal)</code></dd>
<dt>no thread is running for proving Goal:</dt>
<dd><code>existence_error(goal_thread, Goal)</code></dd>
<dt>Tag is a variable:</dt>
<dd><code>instantiation_error</code></dd>
</dl>
<h4>Examples</h4>
<dl>
<dt>To retrieve an asynchronous goal proof result:</dt>
<dd><code>threaded_exit(Goal)</code></dd>
<dt>To retrieve an asynchronous message to <em>self</em> result:</dt>
<dd><code>threaded_exit(::Goal)</code></dd>
<dt>To retrieve an asynchronous message result:</dt>
<dd><code>threaded_exit(Object::Goal)</code></dd>
</dl>
<div class="footer">
<div class="copyright">
<span>Copyright &copy; <a href="mailto:pmoura@logtalk.org">Paulo Moura</a> &mdash; <a href="http://logtalk.org">Logtalk.org</a></span><br/>
<span>Last updated on: September 15, 2007</span>
</div>
<div class="navbottom">
<span><a href="threaded_ignore1.html">previous</a> | <a href="../../glossary.html">glossary</a> | <a href="threaded_peek1_2.html">next</a></span><br/>
<span><a href="http://validator.w3.org/check/referer">XHTML</a> + <a href="http://jigsaw.w3.org/css-validator/check/referer">CSS</a></span>
</div>
</div>
</body>
</html>

View File

@ -0,0 +1,75 @@
<?xml version="1.0" encoding="utf-8"?>
<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.1//EN"
"http://www.w3.org/TR/xhtml11/DTD/xhtml11.dtd">
<html xmlns="http://www.w3.org/1999/xhtml" xml:lang="en">
<head>
<meta http-equiv="content-type" content="application/xml+xhtml; charset=utf-8" />
<title>Logtalk built-in predicate: threaded_once/1-2</title>
<link rel="stylesheet" href="../../screen.css" type="text/css" media="screen"/>
<link rel="stylesheet" href="../../print.css" type="text/css" media="print"/>
</head>
<body>
<div class="top-left">Logtalk reference manual</div>
<div class="top-right">Built-in predicate: threaded_once/1-2</div>
<div class="bottom-left"><span class="page"/></div>
<div class="bottom-right"><span class="page"/></div>
<div class="navtop"><a href="../../index.html">contents</a> &gt; <a href="../index.html">reference manual</a> &gt; <a href="../index.html#builtins">built-in predicates</a></div>
<h2 id="builtins_threaded_once1_2" class="codenp">threaded_once/1-2</h2>
<h4>Description</h4>
<pre>threaded_once(Goal)
threaded_once(Goal, Tag)</pre>
<p>
Proves <code>Goal</code> asynchronously using a new thread. Only the first goal solution is found. The argument can be a message sending goal. This call always succeeds. The result (success, failure, or exception) is sent back to the message queue of the object containing the call (<em>this</em>).
</p>
<p>
The variant <code>threaded_once/2</code> returns a threaded call identifier tag that can be used with the <a title="Consult reference manual" href="threaded_exit1_2.html"><code>threaded_exit/2</code></a> predicate. Tags shall be considered as an opaque term; users shall not rely on its type.
</p>
<h4>Template and modes</h4>
<pre>threaded_once(@callable)
threaded_once(@callable, -nonvar)</pre>
<h4>Errors</h4>
<dl>
<dt>Goal is a variable:</dt>
<dd><code>instantiation_error</code></dd>
<dt>Goal is neither a variable nor a callable term:</dt>
<dd><code>type_error(callable, Goal)</code></dd>
<dt>Tag is not a variable:</dt>
<dd><code>type_error(variable, Goal)</code></dd>
</dl>
<h4>Examples</h4>
<dl>
<dt>Prove <code>Goal</code> asynchronously in a new thread:</dt>
<dd><code>threaded_once(Goal)</code></dd>
<dt>Prove <code>::Message</code> asynchronously in a new thread:</dt>
<dd><code>threaded_once(::Message)</code></dd>
<dt>Prove <code>Object::Message</code> asynchronously in a new thread:</dt>
<dd><code>threaded_once(Object::Message)</code></dd>
</dl>
<div class="footer">
<div class="copyright">
<span>Copyright &copy; <a href="mailto:pmoura@logtalk.org">Paulo Moura</a> &mdash; <a href="http://logtalk.org">Logtalk.org</a></span><br/>
<span>Last updated on: September 15, 2007</span>
</div>
<div class="navbottom">
<span><a href="threaded_call1_2.html">previous</a> | <a href="../../glossary.html">glossary</a> | <a href="threaded_ignore1.html">next</a></span><br/>
<span><a href="http://validator.w3.org/check/referer">XHTML</a> + <a href="http://jigsaw.w3.org/css-validator/check/referer">CSS</a></span>
</div>
</div>
</body>
</html>

View File

@ -0,0 +1,78 @@
<?xml version="1.0" encoding="utf-8"?>
<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.1//EN"
"http://www.w3.org/TR/xhtml11/DTD/xhtml11.dtd">
<html xmlns="http://www.w3.org/1999/xhtml" xml:lang="en">
<head>
<meta http-equiv="content-type" content="application/xml+xhtml; charset=utf-8" />
<title>Logtalk built-in predicate: threaded_peek/1-2</title>
<link rel="stylesheet" href="../../screen.css" type="text/css" media="screen"/>
<link rel="stylesheet" href="../../print.css" type="text/css" media="print"/>
</head>
<body>
<div class="top-left">Logtalk reference manual</div>
<div class="top-right">Built-in predicate: threaded_peek/1-2</div>
<div class="bottom-left"><span class="page"/></div>
<div class="bottom-right"><span class="page"/></div>
<div class="navtop"><a href="../../index.html">contents</a> &gt; <a href="../index.html">reference manual</a> &gt; <a href="../index.html#builtins">built-in predicates</a></div>
<h2 id="builtins_threaded_peek1_2" class="codenp">threaded_peek/1-2</h2>
<h4>Description</h4>
<pre>threaded_peek(Goal)
threaded_peek(Goal, Tag)</pre>
<p>
Checks if the result of proving <code>Goal</code> in a new thread is already available. This call succeeds or fails without blocking execution waiting for a reply to be available.
</p>
<p>
The argument of this predicate should be a <em>variant</em> of the argument of the corresponding <a href="threaded_call1_2.html">threaded_call/1</a> call. When the predicate argument is subsumed by the <a href="threaded_call1_2.html">threaded_call/1</a> call argument, the <code>threaded_peek/1</code> call will succeed iff its argument unifies with an already available solution of the (more general) goal.
</p>
<p>
The variant <code>threaded_peek/2</code> accepts a threaded call identifier tag generated by the calls to the <a title="Consult reference manual" href="threaded_call1_2.html"><code>threaded_call/2</code></a> and <a title="Consult reference manual" href="threaded_once1_2.html"><code>threaded_once/2</code></a> predicates. Tags shall be considered as an opaque term; users shall not rely on its type.
</p>
<h4>Template and modes</h4>
<pre>threaded_peek(+callable)
threaded_peek(+callable, +nonvar)</pre>
<h4>Errors</h4>
<dl>
<dt>Goal is a variable:</dt>
<dd><code>instantiation_error</code></dd>
<dt>Goal is neither a variable nor a callable term:</dt>
<dd><code>type_error(callable, Goal)</code></dd>
<dt>Tag is a variable:</dt>
<dd><code>instantiation_error</code></dd>
</dl>
<h4>Examples</h4>
<dl>
<dt>To check for an asynchronous goal proof result:</dt>
<dd><code>threaded_peek(Goal)</code></dd>
<dt>To check for an asynchronous message to <em>self</em> result:</dt>
<dd><code>threaded_peek(::Goal)</code></dd>
<dt>To check for an asynchronous message result:</dt>
<dd><code>threaded_peek(Object::Goal)</code></dd>
</dl>
<div class="footer">
<div class="copyright">
<span>Copyright &copy; <a href="mailto:pmoura@logtalk.org">Paulo Moura</a> &mdash; <a href="http://logtalk.org">Logtalk.org</a></span><br/>
<span>Last updated on: September 15, 2007</span>
</div>
<div class="navbottom">
<span><a href="threaded_exit1_2.html">previous</a> | <a href="../../glossary.html">glossary</a> | <a href="threaded_wait1.html">next</a></span><br/>
<span><a href="http://validator.w3.org/check/referer">XHTML</a> + <a href="http://jigsaw.w3.org/css-validator/check/referer">CSS</a></span>
</div>
</div>
</body>
</html>

View File

@ -0,0 +1,73 @@
# $Id: Portfile 26918 2007-07-11 15:28:15Z gwright@macports.org $
PortSystem 1.0
name logtalk
version 2.30.7
categories lang
maintainers pmoura@logtalk.org
platforms darwin freebsd linux
description Logtalk - Open source object-oriented logic programming language
long_description \
Logtalk is an open source object-oriented logic programming language \
that can use most Prolog implementations as a back-end compiler. \
As a multi-paradigm language, Logtalk includes support for both \
prototypes and classes, protocols, component-based programming \
through category-based composition, event-driven programming, and \
multi-threading programming.
homepage http://logtalk.org/
master_sites ${homepage}/files/
checksums md5 0653f6e2e10219111deed4b2096e6394
distname lgt2307
extract.suffix .tar.bz2
use_bzip2 yes
configure {}
build {}
destroot {
cd ${workpath}/${worksrcdir}/scripts
system "./install.sh ${destroot}/${prefix}"
}
post-pkg {
set resources ${workpath}/${name}-${version}.pkg/Contents/Resources/
file copy -force -- ${workpath}/${worksrcdir}/scripts/macosx/License.html ${resources}
file copy -force -- ${workpath}/${worksrcdir}/scripts/macosx/ReadMe.html ${resources}
file copy -force -- ${workpath}/${worksrcdir}/scripts/macosx/Welcome.html ${resources}
file copy -force -- ${workpath}/${worksrcdir}/scripts/macosx/postflight ${resources}
}
post-activate {
ui_msg "****************************************************************************"
ui_msg "* Integration scripts have been created for running Logtalk with selected"
ui_msg "* back-end Prolog compilers (which must be properly installed for running"
ui_msg "* the scripts!):"
ui_msg "*"
ui_msg "* B-Prolog: bplgt (first run must use sudo)"
ui_msg "* CIAO: ciaolgt (first run must use sudo)"
ui_msg "* CxProlog: cxlgt"
ui_msg "* ECLiPSe: eclipselgt"
ui_msg "* GNU Prolog: gplgt"
ui_msg "* K-Prolog: plclgt"
ui_msg "* Qu-Prolog: qplgt"
ui_msg "* SICStus Prolog: sicstuslgt"
ui_msg "* SWI-Prolog: swilgt"
ui_msg "* XSB: xsblgt (first run must use sudo)"
ui_msg "* XSB (MT): xsbmtlgt (first run must use sudo)"
ui_msg "* YAP: yaplgt"
ui_msg "*"
ui_msg "* Remember to set the environment variable LOGTALKHOME to the path to"
ui_msg "* the Logtalk distribution: ${prefix}/share/logtalk"
ui_msg "* and the environment variable LOGTALKUSER to your local configuration"
ui_msg "* directory (usually ~/logtalk), which you can create by running the"
ui_msg "* command cplgtdirs. See the file \$LOGTALKHOME/CUSTOMIZE.txt for details"
ui_msg "* on how to customize your working environment."
ui_msg "****************************************************************************"
}

View File

@ -0,0 +1,26 @@
================================================================
Logtalk - Open source object-oriented logic programming language
Release 2.30.7
Copyright (c) 1998-2007 Paulo Moura. All Rights Reserved.
================================================================
This directory contains files that provide syntax highlighting for
GtkSourceView 2.x, which is a text widget used in text editors and
IDEs such as recent versions of Gnome's Gedit and MonoDevelop:
http://gtksourceview.sourceforge.net/
To install, copy the file "logtalk.lang" to the following system-wide
directory:
${prefix}/share/gtksourceview-2.0/language-specs/
The ${prefix} can be e.g. "/usr", "/usr/local", or "/opt", depending
on your system configuration.
Alternatively, you can copy the "logtalk.lang" file to the following
location on your home directory:
~./gnome2/gtksourceview-2.0/language-specs/

View File

@ -0,0 +1,335 @@
<?xml version="1.0" encoding="UTF-8"?>
<!--
Author: Paulo Moura <pmoura@logtalk.org>
Copyright (C) 2007 Paulo Moura <pmoura@logtalk.org>
This library is free software; you can redistribute it and/or
modify it under the terms of the GNU Library General Public
License as published by the Free Software Foundation; either
version 2 of the License, or (at your option) any later version.
This library is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
Library General Public License for more details.
You should have received a copy of the GNU Library General Public
License along with this library; if not, write to the
Free Software Foundation, Inc., 59 Temple Place - Suite 330,
Boston, MA 02111-1307, USA.
-->
<language id="logtalk" _name="Logtalk" version="2.0" _section="Sources">
<metadata>
<property name="mimetypes">text/x-logtalk</property>
<property name="globs">*.lgt</property>
<property name="line-comment-start">%</property>
<property name="block-comment-start">/*</property>
<property name="block-comment-end">*/</property>
</metadata>
<styles>
<style id="comment" _name="Comment" map-to="def:comment"/>
<style id="operator" _name="Operator" map-to="def:operator"/>
<style id="error" _name="Error" map-to="def:error"/>
<style id="string" _name="String" map-to="def:string"/>
<style id="entity" _name="Data type" map-to="def:type"/>
<style id="directive" _name="Preprocessor directive" map-to="def:preprocessor"/>
<style id="number" _name="Number" map-to="def:decimal"/>
<style id="built-in" _name="Keyword" map-to="def:keyword"/>
<style id="variable" _name="Variable" map-to="def:identifier"/>
</styles>
<definitions>
<context id="string" style-ref="string" end-at-line-end="true">
<start>"</start>
<end>"</end>
</context>
<context id="quoted-atom" style-ref="string" end-at-line-end="true">
<start>'</start>
<end>'</end>
</context>
<context id="line-comment" style-ref="comment" end-at-line-end="true">
<start>%</start>
<include>
<context ref="def:in-line-comment"/>
</include>
</context>
<context id="block-comment" style-ref="comment">
<start>/\*</start>
<end>\*/</end>
<include>
<context ref="def:in-comment"/>
</include>
</context>
<context id="close-comment-outside-comment" style-ref="error">
<match>\*/(?!\*)</match>
</context>
<context id="entity-directives" style-ref="entity">
<prefix>^\s*:-\s</prefix>
<keyword>(object)(?=[(])</keyword>
<keyword>(protocol)(?=[(])</keyword>
<keyword>(category)(?=[(])</keyword>
<keyword>(end_(object|protocol|category))(?=[.])</keyword>
</context>
<context id="entity-relations" style-ref="entity">
<keyword>(specializes)(?=[(])</keyword>
<keyword>(extends)(?=[(])</keyword>
<keyword>(i(mp(orts|lements)|nstantiates))(?=[(])</keyword>
</context>
<context id="predicate-directives" style-ref="directive">
<prefix>^\s*:-\s</prefix>
<!-- Scope directives -->
<keyword>(p(ublic|r(otected|ivate)))(?=[(])</keyword>
<!-- Multi-threading directives -->
<keyword>(synchronized)(?=[(])</keyword>
<keyword>(synchronized)(?=[.])</keyword>
<keyword>(threaded)(?=[.])</keyword>
<!-- Other directives -->
<keyword>(alias)(?=[(])</keyword>
<keyword>(e(ncoding|xport))(?=[(])</keyword>
<keyword>(in(itialization|fo))(?=[(])</keyword>
<keyword>(mod(e|ule))(?=[(])</keyword>
<keyword>(dynamic)(?=[(])</keyword>
<keyword>(dynamic)(?=[.])</keyword>
<keyword>(discontiguous)(?=[(])</keyword>
<keyword>(m(eta_predicate|ultifile))(?=[(])</keyword>
<keyword>(op)(?=[(])</keyword>
<keyword>(calls)(?=[(])</keyword>
<keyword>(use(s|_module))(?=[(])</keyword>
</context>
<context id="built-in-methods" style-ref="built-in">
<!-- Method execution context -->
<keyword>(parameter)(?=[(])</keyword>
<keyword>(se(lf|nder))(?=[(])</keyword>
<keyword>(this)(?=[(])</keyword>
<!-- Reflection -->
<keyword>(current_predicate)(?=[(])</keyword>
<keyword>(predicate_property)(?=[(])</keyword>
<!-- Database -->
<keyword>(a(bolish|ssert(a|z)))(?=[(])</keyword>
<keyword>(clause)(?=[(])</keyword>
<keyword>(retract(all)?)(?=[(])</keyword>
<!-- All solutions -->
<keyword>((bag|set)of)(?=[(])</keyword>
<keyword>(f(ind|or)all)(?=[(])</keyword>
<!-- Event handlers -->
<keyword>(before)(?=[(])</keyword>
<keyword>(after)(?=[(])</keyword>
<!-- DCGs -->
<keyword>(expand_term)(?=[(])</keyword>
<keyword>(term_expansion)(?=[(])</keyword>
<keyword>(phrase)(?=[(])</keyword>
</context>
<context id="built-in-predicates" style-ref="built-in">
<!-- Entity -->
<keyword>((abolish|c(reate|urrent))_(object|protocol|category))(?=[(])</keyword>
<keyword>((object|protocol|category)_property)(?=[(])</keyword>
<!-- Entity relations -->
<keyword>(extends_(object|protocol))(?=[(])</keyword>
<keyword>(imp(lements_protocol|orts_category))(?=[(])</keyword>
<keyword>((instantiat|specializ)es_class)(?=[(])</keyword>
<!-- Events -->
<keyword>(current_event)(?=[(])</keyword>
<keyword>((abolish|define)_events)(?=[(])</keyword>
<!-- Flags -->
<keyword>((se|curren)t_logtalk_flag)(?=[(])</keyword>
<!-- Compiling, loading, and library paths -->
<keyword>(logtalk_(compile|l(ibrary_path|oad)))(?=[(])</keyword>
<!-- Multi-threading meta-predicates -->
<keyword>(threaded(_(call|once|ignore|exit|peek|wait|notify))?)(?=[(])</keyword>
<!-- All solutions -->
<keyword>(forall)(?=[(])</keyword>
</context>
<context id="other-built-in-predicates" style-ref="built-in">
<!-- Term unification -->
<keyword>(unify_with_occurs_check)(?=[(])</keyword>
<!-- Term testing -->
<keyword>(atom(ic)?)(?=[(])</keyword>
<keyword>(integer)(?=[(])</keyword>
<keyword>(float)(?=[(])</keyword>
<keyword>(compound)(?=[(])</keyword>
<keyword>((non)?var)(?=[(])</keyword>
<keyword>(number)(?=[(])</keyword>
<!-- Term creation and decomposition -->
<keyword>(functor)(?=[(])</keyword>
<keyword>(arg)(?=[(])</keyword>
<keyword>(copy_term)(?=[(])</keyword>
<!-- Arithemtic evaluation -->
<keyword>is</keyword>
<!-- Evaluable functors -->
<keyword>(rem)(?=[(])</keyword>
<keyword>rem</keyword>
<keyword>(mod)(?=[(])</keyword>
<keyword>mod</keyword>
<keyword>(abs)(?=[(])</keyword>
<keyword>(sign)(?=[(])</keyword>
<keyword>(float(_(integer|fractional)_part)?)(?=[(])</keyword>
<keyword>(floor)(?=[(])</keyword>
<keyword>(truncate)(?=[(])</keyword>
<keyword>(round)(?=[(])</keyword>
<keyword>(ceiling)(?=[(])</keyword>
<!-- Other arithemtic functors -->
<keyword>(sin)(?=[(])</keyword>
<keyword>(cos)(?=[(])</keyword>
<keyword>(atan)(?=[(])</keyword>
<keyword>(exp)(?=[(])</keyword>
<keyword>(log)(?=[(])</keyword>
<keyword>(sqrt)(?=[(])</keyword>
<!-- Stream selection and control -->
<keyword>((current|set)_(in|out)put)(?=[(])</keyword>
<keyword>(open)(?=[(])</keyword>
<keyword>(close)(?=[(])</keyword>
<keyword>(flush_output)(?=[(])</keyword>
<keyword>flush_output</keyword>
<keyword>(stream_property)(?=[(])</keyword>
<keyword>(at_end_of_stream)(?=[(])</keyword>
<keyword>at_end_of_stream</keyword>
<keyword>(set_stream_position)(?=[(])</keyword>
<!-- Character input/output -->
<keyword>((get|p(eek|ut))_c(har|ode))(?=[(])</keyword>
<keyword>(nl)(?=[(])</keyword>
<keyword>nl</keyword>
<!-- Byte input/output -->
<keyword>((get|peek|put)_byte)(?=[(])</keyword>
<!-- Term input/output -->
<keyword>(read(_term)?)(?=[(])</keyword>
<keyword>(write(q|_(canonical|term))?)(?=[(])</keyword>
<keyword>((current_)?op)(?=[(])</keyword>
<keyword>((current_)?char_conversion)(?=[(])</keyword>
<!-- Logic and control -->
<keyword>(once)(?=[(])</keyword>
<keyword>(true|fail|repeat)(?![-!(^~])</keyword>
<!-- Atomic term processing -->
<keyword>(atom_(length|c(hars|o(ncat|des))))(?=[(])</keyword>
<keyword>(sub_atom)(?=[(])</keyword>
<keyword>(char_code)(?=[(])</keyword>
<keyword>(number_c(hars|odes))(?=[(])</keyword>
<!-- Implementation defined hooks functions -->
<keyword>((set|current)_prolog_flag)(?=[(])</keyword>
<keyword>(halt)(?=[(])</keyword>
<keyword>halt</keyword>
</context>
<context id="built-in-operators" style-ref="built-in">
<prefix></prefix>
<suffix></suffix>
<!-- Term unification -->
<keyword>=</keyword>
<keyword>\\=</keyword>
<!-- Term comparison -->
<keyword>==</keyword>
<keyword>\\==</keyword>
<keyword>@&lt;</keyword>
<keyword>@=&lt;</keyword>
<keyword>@&gt;=</keyword>
<keyword>@&gt;</keyword>
<!-- Term creation and decomposition -->
<keyword>=\.\.</keyword>
<!-- Arithemtic comparison -->
<keyword>=:=</keyword>
<keyword>=\\=</keyword>
<keyword>&lt;</keyword>
<keyword>=&lt;</keyword>
<keyword>&gt;</keyword>
<keyword>&gt;=</keyword>
<!-- Evaluable functors -->
<keyword>\+(?![,a-z])</keyword>
<keyword>(?&lt;!:)(-)(?![,a-z])</keyword>
<keyword>\*</keyword>
<keyword>//</keyword>
<keyword>/</keyword>
<!-- Other arithemtic functors -->
<keyword>\*\*</keyword>
<!-- Bitwise functors -->
<keyword>&gt;&gt;</keyword>
<keyword>&lt;&lt;</keyword>
<keyword>/\\</keyword>
<keyword>\\/</keyword>
<keyword>\\</keyword>
<!-- Logic and control -->
<keyword>(\\\+|!)</keyword>
</context>
<context id="number" style-ref="number">
<match extended="true">
\b(0'.|0b[0-1]+|0o[0-7]+|0x[0-9a-fA-F]+|\d+(\.\d+)?([eE]([-+])?\d+)?)
</match>
</context>
<context id="variable" style-ref="variable">
<match extended="true">
\b[A-Z_][a-zA-Z0-9_]*
</match>
</context>
<context id="message-sending-operators" style-ref="built-in">
<prefix></prefix>
<suffix></suffix>
<keyword>::</keyword>
<keyword>\^\^</keyword>
</context>
<context id="category-predicate-direct-call" style-ref="built-in">
<prefix></prefix>
<suffix></suffix>
<keyword>:</keyword>
</context>
<context id="external-call-operator" style-ref="built-in">
<prefix></prefix>
<suffix></suffix>
<keyword>\{</keyword>
<keyword>\}</keyword>
</context>
<!--
<context id="mode-operators" style-ref="built-in">
<prefix></prefix>
<suffix></suffix>
<keyword>\+</keyword>
<keyword>-</keyword>
<keyword>\?</keyword>
<keyword>@</keyword>
</context>
-->
<context id="logtalk">
<include>
<context ref="string"/>
<context ref="quoted-atom"/>
<context ref="line-comment"/>
<context ref="block-comment"/>
<context ref="close-comment-outside-comment"/>
<context ref="entity-directives"/>
<context ref="entity-relations"/>
<context ref="predicate-directives"/>
<context ref="built-in-methods"/>
<context ref="built-in-predicates"/>
<context ref="other-built-in-predicates"/>
<context ref="built-in-operators"/>
<context ref="number"/>
<context ref="variable"/>
<context ref="message-sending-operators"/>
<context ref="category-predicate-direct-call"/>
<context ref="external-call-operator"/>
<!--
<context ref="mode-operators"/>
-->
</include>
</context>
</definitions>
</language>