sveral updates
git-svn-id: https://yap.svn.sf.net/svnroot/yap/trunk@1415 b08c6af1-5177-4d33-ba66-4b1c6b8b522a
This commit is contained in:
@@ -29,7 +29,9 @@ PROGRAMS= $(srcdir)/apply_macros.yap \
|
||||
$(srcdir)/avl.yap \
|
||||
$(srcdir)/charsio.yap \
|
||||
$(srcdir)/cleanup.yap \
|
||||
$(srcdir)/gensym.yap \
|
||||
$(srcdir)/heaps.yap \
|
||||
$(srcdir)/listing.yap \
|
||||
$(srcdir)/lists.yap \
|
||||
$(srcdir)/logtalk.yap \
|
||||
$(srcdir)/ordsets.yap \
|
||||
|
@@ -36,9 +36,14 @@
|
||||
ord_symdiff/3, % Set x Set -> Set
|
||||
ord_union/2, % Set^2 -> Set
|
||||
ord_union/3, % Set x Set -> Set
|
||||
ord_union/4 % Set x Set -> Set x Set
|
||||
ord_union/4, % Set x Set -> Set x Set,
|
||||
ord_empty/1, % -> Set
|
||||
ord_memberchk/2 % Element X Set
|
||||
]).
|
||||
|
||||
:- use_module(library(lists),
|
||||
[memberchk/2]).
|
||||
|
||||
/*
|
||||
:- mode
|
||||
list_to_ord_set(+, ?),
|
||||
@@ -347,3 +352,8 @@ ord_union_all(N,Sets0,Union,Sets) :-
|
||||
ord_union(X, Y, Union)
|
||||
).
|
||||
|
||||
ord_empty([]).
|
||||
|
||||
ord_memberchk(Element, Set) :-
|
||||
memberchk(Element, Set).
|
||||
|
||||
|
@@ -56,13 +56,13 @@
|
||||
%
|
||||
%
|
||||
wsize(32) :-
|
||||
yap_flag(max_integer,2147483647), !.
|
||||
yap_flag(max_tagged_integer,I), I >> 32 =:= 0, !.
|
||||
wsize(64).
|
||||
|
||||
ranstart :- ranstart(8'365).
|
||||
|
||||
ranstart(N) :-
|
||||
wsize(32), % bits available for int.
|
||||
wsize(Wsize), % bits available for int.
|
||||
MaxInt is \(1 << (Wsize - 1)), % all bits but sign bit are 1.
|
||||
Incr is (8'154 << (Wsize - 9)) + 1, % per Knuth, v.2 p.78
|
||||
Mult is 8'3655, % OK for 16-18 Wsize
|
||||
|
@@ -1,4 +1,10 @@
|
||||
|
||||
:- source.
|
||||
|
||||
:- style_check(all).
|
||||
|
||||
:- yap_flag(unknown,error).
|
||||
|
||||
% redefines stuff in prolog module.
|
||||
|
||||
:- module(swi, []).
|
||||
@@ -13,7 +19,8 @@
|
||||
mktime/2]).
|
||||
|
||||
:- use_module(library(terms),[term_variables/2,
|
||||
term_variables/3]).
|
||||
term_variables/3,
|
||||
term_hash/2]).
|
||||
|
||||
:- multifile
|
||||
prolog:message/3.
|
||||
@@ -111,7 +118,7 @@ prolog:b_getval(GlobalVariable,Value) :-
|
||||
|
||||
prolog:b_setval(GlobalVariable,Value) :-
|
||||
array(GlobalVariable,1),
|
||||
update_array(GlobalVariable,0,Value).
|
||||
dynamic_update_array(GlobalVariable,0,Value).
|
||||
|
||||
prolog:nb_getval(GlobalVariable,Value) :-
|
||||
array_element(GlobalVariable,0,Value).
|
||||
@@ -124,7 +131,7 @@ prolog:nb_delete(GlobalVariable) :-
|
||||
close_static_array(GlobalVariable).
|
||||
|
||||
prolog:nb_current(GlobalVariable,Val) :-
|
||||
static_array_properties(GlobalVariable,1,term),
|
||||
static_array_properties(GlobalVariable,1,nb_term),
|
||||
array_element(GlobalVariable,0,Val).
|
||||
|
||||
% SWI has a dynamic attribute scheme
|
||||
@@ -141,7 +148,7 @@ prolog:del_attr(Var, Mod) :-
|
||||
AttTerm =.. [Mod,_,_],
|
||||
attributes:del_all_module_atts(Var, AttTerm).
|
||||
|
||||
prolog:get_attrs(Var, SWIAtts) :-
|
||||
prolog:get_attrs(AttVar, SWIAtts) :-
|
||||
get_all_swi_atts(AttVar,SWIAtts).
|
||||
|
||||
prolog:put_attrs(_, []).
|
||||
@@ -164,7 +171,7 @@ prolog:append([],L,L).
|
||||
prolog:append([X|L0],L,[X|Lf]) :-
|
||||
prolog:append(L0,L,Lf).
|
||||
|
||||
prolog:member(X[X|_]).
|
||||
prolog:member(X,[X|_]).
|
||||
prolog:member(X,[_|L0]) :-
|
||||
prolog:member(X,L0).
|
||||
|
||||
@@ -188,7 +195,49 @@ prolog:get_time(Secs) :- datime(Datime), mktime(Datime, Secs).
|
||||
% Time is received as int, and converted to "..."
|
||||
prolog:convert_time(X,Y) :- swi:ctime(X,Y).
|
||||
|
||||
:- hide(atom_concat).
|
||||
|
||||
prolog:atom_concat(A,B) :- atomic_concat(A,B).
|
||||
|
||||
prolog:atom_concat(A,B,C) :- atomic_concat(A,B,C).
|
||||
|
||||
:- hide(create_mutable).
|
||||
|
||||
:- hide(get_mutable).
|
||||
|
||||
:- hide(update_mutable).
|
||||
|
||||
prolog:hash_term(X,Y) :- term_hash(X,Y).
|
||||
|
||||
:- meta_predicate prolog:maplist(:,?), prolog:maplist(:,?,?), prolog:maplist(:,?,?).
|
||||
|
||||
|
||||
prolog:maplist(_, []).
|
||||
prolog:maplist(G, [H|L]) :-
|
||||
call(G,H),
|
||||
prolog:maplist(G, L).
|
||||
|
||||
prolog:maplist(_, [], []).
|
||||
prolog:maplist(G, [H1|L1], [H2|L2]) :-
|
||||
call(G,H1,H2),
|
||||
prolog:maplist(G, L1, L2).
|
||||
|
||||
prolog:maplist(_, [], [], []).
|
||||
prolog:maplist(G, [H1|L1], [H2|L2], [H3|L3]) :-
|
||||
call(G,H1,H2,H3),
|
||||
prolog:maplist(G, L1, L2, L3).
|
||||
|
||||
prolog:make.
|
||||
|
||||
prolog:source_location(File,Line) :-
|
||||
prolog_load_context(file, File),
|
||||
prolog_load_context(term_position, '$stream_position'(_,Line,_)).
|
||||
|
||||
prolog:memberchk(Element, [Element|_]) :- !.
|
||||
prolog:memberchk(Element, [_|Rest]) :-
|
||||
prolog:memberchk(Element, Rest).
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
|
@@ -4,7 +4,7 @@
|
||||
%
|
||||
% Author: Nuno Fonseca (nunofonseca@acm.org)
|
||||
% Date: 2005-05-14
|
||||
% $Id: ypp.yap,v 1.1 2005-06-06 05:10:37 vsc Exp $
|
||||
% $Id: ypp.yap,v 1.2 2005-10-28 17:38:50 vsc Exp $
|
||||
%
|
||||
%====================================================================================
|
||||
|
||||
@@ -39,6 +39,8 @@ ypp_define(Name,Value):-
|
||||
|
||||
ypp_undefine(Name):-
|
||||
ground(Name),
|
||||
del_define(Name).
|
||||
|
||||
ypp_extcmd(Cmd):-
|
||||
ground(Cmd),!,
|
||||
eraseall('____ypp_extcmd'),
|
||||
|
Reference in New Issue
Block a user