further upgrades to chr

git-svn-id: https://yap.svn.sf.net/svnroot/yap/trunk@2147 b08c6af1-5177-4d33-ba66-4b1c6b8b522a
This commit is contained in:
vsc 2008-03-13 17:43:13 +00:00
parent 54ceaa1f37
commit 381a3401ac
9 changed files with 387 additions and 320 deletions

View File

@ -1,4 +1,4 @@
/* $Id: chr_compiler_utility.pl,v 1.3 2008-03-13 14:37:59 vsc Exp $
/* $Id: chr_compiler_utility.pl,v 1.4 2008-03-13 17:43:13 vsc Exp $
Part of CHR (Constraint Handling Rules)
@ -28,7 +28,6 @@
invalidate any other reasons why the executable file might be covered by
the GNU General Public License.
*/
:- if(current_prolog_flag(dialect, swi)).
:- module(chr_compiler_utility,
[ time/2
, replicate/3
@ -58,40 +57,6 @@
, tree_set_memberchk/2
, tree_set_add/3
]).
:- else.
% ugly: this is because YAP also has atomic_concat
% so we cannot export it from chr_compiler_utility.
:- module(chr_compiler_utility,
[ time/2
, replicate/3
, pair_all_with/3
, conj2list/2
, list2conj/2
, disj2list/2
, list2disj/2
, variable_replacement/3
, variable_replacement/4
, identical_rules/2
, identical_guarded_rules/2
, copy_with_variable_replacement/3
, my_term_copy/3
, my_term_copy/4
, atom_concat_list/2
, init/2
, member2/3
, select2/6
, set_elems/2
, instrument_goal/4
, sort_by_key/3
, arg1/3
, wrap_in_functor/3
, tree_set_empty/1
, tree_set_memberchk/2
, tree_set_add/3
]).
:- endif.
:- use_module(pairlist).
:- use_module(library(lists), [permutation/2]).
@ -279,12 +244,10 @@ atom_concat_list([X|Xs],A) :-
atom_concat_list(Xs,B),
atomic_concat(X,B,A).
:- if(current_prolog_flag(dialect, swi)).
atomic_concat(A,B,C) :-
make_atom(A,AA),
make_atom(B,BB),
atom_concat(AA,BB,C).
:- endif.
make_atom(A,AA) :-
(

View File

@ -1,4 +1,4 @@
/* $Id: chr_hashtable_store.pl,v 1.3 2008-03-13 14:37:59 vsc Exp $
/* $Id: chr_hashtable_store.pl,v 1.4 2008-03-13 17:43:13 vsc Exp $
Part of CHR (Constraint Handling Rules)
@ -51,18 +51,11 @@
:- use_module(hprolog).
:- use_module(library(lists)).
:- if(current_prolog_flag(dialect, swi)).
:- multifile user:goal_expansion/2.
:- dynamic user:goal_expansion/2.
user:goal_expansion(term_hash(Term,Hash),hash_term(Term,Hash)).
:- else.
:- use_module(library(terms), [term_hash/2]).
:- endif.
% term_hash(Term,Hash) :-
% hash_term(Term,Hash).
initial_capacity(89).
@ -78,6 +71,8 @@ new_ht(Capacity,HT) :-
lookup_ht(HT,Key,Values) :-
term_hash(Key,Hash),
lookup_ht1(HT,Hash,Key,Values).
/*
HT = ht(Capacity,_,Table),
Index is (Hash mod Capacity) + 1,
arg(Index,Table,Bucket),
@ -88,6 +83,23 @@ lookup_ht(HT,Key,Values) :-
;
lookup(Bucket,Key,Values)
).
*/
% :- load_foreign_library(chr_support).
/*
lookup_ht1(HT,Hash,Key,Values) :-
( lookup_ht1_(HT,Hash,Key,Values) ->
true
;
( lookup_ht1__(HT,Hash,Key,Values) ->
writeln(lookup_ht1(HT,Hash,Key,Values)),
throw(error)
;
fail
)
).
*/
lookup_ht1(HT,Hash,Key,Values) :-
HT = ht(Capacity,_,Table),

View File

@ -1,4 +1,4 @@
/* $Id: chr_swi.pl,v 1.4 2008-03-13 17:16:44 vsc Exp $
/* $Id: chr_swi.pl,v 1.5 2008-03-13 17:43:13 vsc Exp $
Part of CHR (Constraint Handling Rules)
@ -53,6 +53,10 @@
chr_leash/1 % +Ports
]).
:- if(current_prolog_flag(dialect, yap)).
:- hide(atomic_concat).
:- endif.
:- expects_dialect(swi).
:- set_prolog_flag(generate_debug_info, false).

View File

@ -1,4 +1,4 @@
/* $Id: chr_swi_bootstrap.pl,v 1.3 2008-03-13 14:38:00 vsc Exp $
/* $Id: chr_swi_bootstrap.pl,v 1.4 2008-03-13 17:43:13 vsc Exp $
Part of CHR (Constraint Handling Rules)
@ -37,6 +37,12 @@
, chr_compile/3
]).
%% SWI begin
:- if(current_prolog_flag(dialect, yap)).
:- hide(atomic_concat).
:- endif.
:- expects_dialect(swi).
:- use_module(library(listing)). % portray_clause/2
%% SWI end
:- include(chr_op).

View File

@ -4,8 +4,6 @@
:- add_to_path('.').
:- use_module(library(swi)).
:- yap_flag(unknown,error).
:- include('chr_swi_bootstrap.pl').

File diff suppressed because it is too large Load Diff

View File

@ -1,4 +1,4 @@
/* $Id: chr_translate_bootstrap.pl,v 1.6 2008-03-13 14:38:00 vsc Exp $
/* $Id: chr_translate_bootstrap.pl,v 1.7 2008-03-13 17:43:13 vsc Exp $
Part of CHR (Constraint Handling Rules)
@ -2458,8 +2458,6 @@ list2conj([G|Gs],C) :-
list2conj(Gs,R)
).
:- if(current_prolog_flag(dialect, swi)).
atom_concat_list([X],X) :- ! .
atom_concat_list([X|Xs],A) :-
atom_concat_list(Xs,B),
@ -2480,13 +2478,6 @@ make_atom(A,AA) :-
atom_codes(AA,AL)
).
:- else.
atom_concat_list(L,X) :-
atomic_concat(L, X).
:- endif.
set_elems([],_).
set_elems([X|Xs],X) :-
set_elems(Xs,X).

View File

@ -1,4 +1,4 @@
/* $Id: chr_translate_bootstrap2.chr,v 1.3 2008-03-13 14:38:01 vsc Exp $
/* $Id: chr_translate_bootstrap2.chr,v 1.4 2008-03-13 17:43:13 vsc Exp $
Part of CHR (Constraint Handling Rules)
@ -3558,8 +3558,6 @@ list2disj([G|Gs],C) :-
list2disj(Gs,R)
).
:- if(current_prolog_flag(dialect, swi)).
atom_concat_list([X],X) :- ! .
atom_concat_list([X|Xs],A) :-
atom_concat_list(Xs,B),
@ -3579,12 +3577,6 @@ make_atom(A,AA) :-
number_codes(A,AL),
atom_codes(AA,AL)
).
:- else.
atom_concat_list(L,X) :-
atomic_concat(L, X).
:- endif.
make_name(Prefix,F/A,Name) :-

View File

@ -15,7 +15,8 @@
:- use_module(library(charsio),[write_to_chars/2,read_from_chars/2]).
:- use_module(library(lists),[append/3,
:- use_module(library(lists),[append/2,
append/3,
delete/3,
member/2,
memberchk/2,
@ -64,8 +65,11 @@ swi_predicate_table(_,delete(X,Y,Z),lists,delete(X,Y,Z)).
swi_predicate_table(_,nth1(X,Y,Z),lists,nth(X,Y,Z)).
swi_predicate_table(_,memberchk(X,Y),lists,memberchk(X,Y)).
swi_predicate_table(_,member(X,Y),lists,member(X,Y)).
swi_predicate_table(_,append(X,Y),lists,append(X,Y)).
swi_predicate_table(_,append(X,Y,Z),lists,append(X,Y,Z)).
swi_predicate_table(_,select(X,Y,Z),lists,select(X,Y,Z)).
swi_predicate_table(_,hash_term(X,Y),terms,term_hash(X,Y)).
swi_predicate_table(_,term_hash(X,Y),terms,term_hash(X,Y)).
swi_predicate_table(_,term_variables(X,Y),terms,term_variables(X,Y)).
swi_predicate_table(_,term_variables(X,Y,Z),terms,term_variables(X,Y,Z)).
swi_predicate_table(_,subsumes(X,Y),terms,subsumes(X,Y)).
@ -303,8 +307,6 @@ prolog:atom_concat(A,B,C) :- atomic_concat(A,B,C).
:- hide(update_mutable).
prolog:hash_term(X,Y) :- term_hash(X,Y).
prolog:make.
prolog:source_location(File,Line) :-