Merge branch 'master' of ../yap-6.2

This commit is contained in:
Vítor Santos Costa 2011-02-08 21:05:12 +00:00
commit 54507703fe
19 changed files with 78 additions and 30 deletions

View File

@ -569,6 +569,13 @@ p_put_atts(void) {
} }
/* we may have a stack shift meanwhile!! */ /* we may have a stack shift meanwhile!! */
tatts = Deref(ARG2); tatts = Deref(ARG2);
if (IsVarTerm(tatts)) {
Yap_Error(INSTANTIATION_ERROR,tatts,"second argument of put_att/2");
return FALSE;
} else if (!IsApplTerm(tatts)) {
Yap_Error(TYPE_ERROR_COMPOUND,tatts,"second argument of put_att/2");
return FALSE;
}
if (IsVarTerm(otatts = SearchAttsForModule(attv->Atts,mfun))) { if (IsVarTerm(otatts = SearchAttsForModule(attv->Atts,mfun))) {
AddNewModule(attv,tatts,new,FALSE); AddNewModule(attv,tatts,new,FALSE);
} else { } else {

View File

@ -1258,6 +1258,8 @@ cleanup_dangling_indices(yamop *ipc, yamop *beg, yamop *end, yamop *suspend_code
case _switch_on_cons: case _switch_on_cons:
case _if_cons: case _if_cons:
case _go_on_cons: case _go_on_cons:
/* make sure we don't leave dangling references to memory that is going to be removed */
ipc->u.sssl.l = NULL;
ipc = NEXTOP(ipc,sssl); ipc = NEXTOP(ipc,sssl);
break; break;
case _op_fail: case _op_fail:
@ -1272,12 +1274,6 @@ cleanup_dangling_indices(yamop *ipc, yamop *beg, yamop *end, yamop *suspend_code
} }
} }
void
Yap_cleanup_dangling_indices(yamop *ipc, yamop *beg, yamop *end, yamop *sc)
{
cleanup_dangling_indices(ipc, beg, end, sc);
}
static void static void
decrease_log_indices(LogUpdIndex *c, yamop *suspend_code) decrease_log_indices(LogUpdIndex *c, yamop *suspend_code)
{ {

View File

@ -372,6 +372,16 @@ static Int p_start_low_level_trace(void)
return(TRUE); return(TRUE);
} }
static Int p_total_choicepoints(void)
{
return Yap_unify(MkIntegerTerm(Yap_total_choicepoints),ARG1);
}
static Int p_reset_total_choicepoints(void)
{
Yap_total_choicepoints = 0;
}
static Int p_show_low_level_trace(void) static Int p_show_low_level_trace(void)
{ {
fprintf(stderr,"Call counter=%lld\n",vsc_count); fprintf(stderr,"Call counter=%lld\n",vsc_count);
@ -414,6 +424,8 @@ Yap_InitLowLevelTrace(void)
#endif #endif
Yap_InitCPred("stop_low_level_trace", 0, p_stop_low_level_trace, SafePredFlag); Yap_InitCPred("stop_low_level_trace", 0, p_stop_low_level_trace, SafePredFlag);
Yap_InitCPred("show_low_level_trace", 0, p_show_low_level_trace, SafePredFlag); Yap_InitCPred("show_low_level_trace", 0, p_show_low_level_trace, SafePredFlag);
Yap_InitCPred("total_choicepoints", 1, p_total_choicepoints, SafePredFlag);
Yap_InitCPred("reset_total_choicepoints", 0, p_reset_total_choicepoints, SafePredFlag);
Yap_InitCPred("vsc_wait", 0, p_vsc_wait, SafePredFlag); Yap_InitCPred("vsc_wait", 0, p_vsc_wait, SafePredFlag);
} }

View File

@ -36,6 +36,7 @@ int
Yap_rational_tree_loop(CELL *pt0, CELL *pt0_end, CELL **to_visit, CELL **to_visit_max) Yap_rational_tree_loop(CELL *pt0, CELL *pt0_end, CELL **to_visit, CELL **to_visit_max)
{ {
CELL ** base = to_visit;
rtree_loop: rtree_loop:
while (pt0 < pt0_end) { while (pt0 < pt0_end) {
register CELL *ptd0; register CELL *ptd0;
@ -56,7 +57,7 @@ rtree_loop:
} }
to_visit[0] = pt0; to_visit[0] = pt0;
to_visit[1] = pt0_end; to_visit[1] = pt0_end;
to_visit[2] = (CELL *)d0; to_visit[2] = (CELL *)*pt0;
*pt0 = TermFoundVar; *pt0 = TermFoundVar;
pt0_end = (pt0 = RepPair(d0) - 1) + 2; pt0_end = (pt0 = RepPair(d0) - 1) + 2;
continue; continue;
@ -78,7 +79,7 @@ rtree_loop:
} }
to_visit[0] = pt0; to_visit[0] = pt0;
to_visit[1] = pt0_end; to_visit[1] = pt0_end;
to_visit[2] = (CELL *)d0; to_visit[2] = (CELL *)*pt0;
*pt0 = TermFoundVar; *pt0 = TermFoundVar;
d0 = ArityOfFunctor(f); d0 = ArityOfFunctor(f);
pt0 = ap2; pt0 = ap2;
@ -91,7 +92,7 @@ rtree_loop:
derefa_body(d0, ptd0, rtree_loop_unk, rtree_loop_nvar); derefa_body(d0, ptd0, rtree_loop_unk, rtree_loop_nvar);
} }
/* Do we still have compound terms to visit */ /* Do we still have compound terms to visit */
if (to_visit < (CELL **)to_visit_base) { if (to_visit < base) {
pt0 = to_visit[0]; pt0 = to_visit[0];
pt0_end = to_visit[1]; pt0_end = to_visit[1];
*pt0 = (CELL)to_visit[2]; *pt0 = (CELL)to_visit[2];
@ -102,14 +103,13 @@ rtree_loop:
cufail: cufail:
/* we found an infinite term */ /* we found an infinite term */
while (to_visit < to_visit_max) { while (to_visit < (CELL **)base) {
CELL *pt0; CELL *pt0;
pt0 = to_visit[0]; pt0 = to_visit[0];
*pt0 = (CELL)to_visit[2]; *pt0 = (CELL)to_visit[2];
to_visit += 3; to_visit += 3;
} }
return TRUE; return TRUE;
} }
static inline int static inline int

View File

@ -731,6 +731,12 @@ Macros to check the limits of stacks
while ( pt0 > XREGS ); \ while ( pt0 > XREGS ); \
ENDP(pt0) ENDP(pt0)
#if LOW_LEVEL_TRACER
#define COUNT_CPS() Yap_total_choicepoints++
#else
#define COUNT_CPS()
#endif
/*************************************************************** /***************************************************************
* Do the bulk of work in creating a choice-point * * Do the bulk of work in creating a choice-point *
* AP: alternative pointer * * AP: alternative pointer *
@ -747,6 +753,7 @@ Macros to check the limits of stacks
#define store_yaam_regs(AP,I) \ #define store_yaam_regs(AP,I) \
{ /* Jump to CP_BASE */ \ { /* Jump to CP_BASE */ \
COUNT_CPS(); \
S_YREG = (CELL *)((choiceptr)((S_YREG)-(I))-1); \ S_YREG = (CELL *)((choiceptr)((S_YREG)-(I))-1); \
/* Save Information */ \ /* Save Information */ \
HBREG = H; \ HBREG = H; \
@ -760,6 +767,7 @@ Macros to check the limits of stacks
} }
#define store_yaam_regs_for_either(AP,d0) \ #define store_yaam_regs_for_either(AP,d0) \
COUNT_CPS(); \
pt1 --; /* Jump to CP_BASE */ \ pt1 --; /* Jump to CP_BASE */ \
/* Save Information */ \ /* Save Information */ \
HBREG = H; \ HBREG = H; \

View File

@ -205,7 +205,6 @@ void STD_PROTO(Yap_IPred,(PredEntry *, UInt, yamop *));
int STD_PROTO(Yap_addclause,(Term,yamop *,int,Term,Term*)); int STD_PROTO(Yap_addclause,(Term,yamop *,int,Term,Term*));
void STD_PROTO(Yap_add_logupd_clause,(PredEntry *,LogUpdClause *,int)); void STD_PROTO(Yap_add_logupd_clause,(PredEntry *,LogUpdClause *,int));
void STD_PROTO(Yap_kill_iblock,(ClauseUnion *,ClauseUnion *,PredEntry *)); void STD_PROTO(Yap_kill_iblock,(ClauseUnion *,ClauseUnion *,PredEntry *));
void STD_PROTO(Yap_cleanup_dangling_indices,(yamop *,yamop *,yamop *,yamop *));
void STD_PROTO(Yap_EraseStaticClause,(StaticClause *, Term)); void STD_PROTO(Yap_EraseStaticClause,(StaticClause *, Term));
ClauseUnion *STD_PROTO(Yap_find_owner_index,(yamop *, PredEntry *)); ClauseUnion *STD_PROTO(Yap_find_owner_index,(yamop *, PredEntry *));

View File

@ -95,6 +95,9 @@
#define TotGcRecovered WL->tot_gc_recovered #define TotGcRecovered WL->tot_gc_recovered
#define LastGcTime WL->last_gc_time #define LastGcTime WL->last_gc_time
#define LastSSTime WL->last_ss_time #define LastSSTime WL->last_ss_time
#if LOW_LEVEL_TRACER
#define Yap_total_choicepoints WL->total_cps
#endif
#if defined(YAPOR) || defined(THREADS) #if defined(YAPOR) || defined(THREADS)
#define SignalLock WL->signal_lock #define SignalLock WL->signal_lock

View File

@ -97,6 +97,9 @@ typedef struct worker_local {
YAP_ULONG_LONG tot_gc_recovered; YAP_ULONG_LONG tot_gc_recovered;
Int last_gc_time; Int last_gc_time;
Int last_ss_time; Int last_ss_time;
#if LOW_LEVEL_TRACER
Int total_cps;
#endif
#if defined(YAPOR) || defined(THREADS) #if defined(YAPOR) || defined(THREADS)
lockvar signal_lock; lockvar signal_lock;

View File

@ -95,6 +95,9 @@ static void InitWorker(int wid) {
FOREIGN_WL(wid)->tot_gc_recovered = 0L; FOREIGN_WL(wid)->tot_gc_recovered = 0L;
FOREIGN_WL(wid)->last_gc_time = 0L; FOREIGN_WL(wid)->last_gc_time = 0L;
FOREIGN_WL(wid)->last_ss_time = 0L; FOREIGN_WL(wid)->last_ss_time = 0L;
#if LOW_LEVEL_TRACER
FOREIGN_WL(wid)->total_cps = 0;
#endif
#if defined(YAPOR) || defined(THREADS) #if defined(YAPOR) || defined(THREADS)
INIT_LOCK(FOREIGN_WL(wid)->signal_lock); INIT_LOCK(FOREIGN_WL(wid)->signal_lock);

View File

@ -95,6 +95,9 @@ static void RestoreWorker(int wid) {
#if LOW_LEVEL_TRACER
#endif
#if defined(YAPOR) || defined(THREADS) #if defined(YAPOR) || defined(THREADS)
REINIT_LOCK(FOREIGN_WL(wid)->signal_lock); REINIT_LOCK(FOREIGN_WL(wid)->signal_lock);

View File

@ -284,6 +284,9 @@ static void
AdjustSwitchTable(op_numbers op, yamop *table, COUNT i) AdjustSwitchTable(op_numbers op, yamop *table, COUNT i)
{ {
CELL *startcode = (CELL *)table; CELL *startcode = (CELL *)table;
/* in case the table is already gone */
if (!table)
return;
switch (op) { switch (op) {
case _switch_on_func: case _switch_on_func:
{ {

View File

@ -659,7 +659,8 @@ inline EXTERN yamop *PtoOpAdjust (yamop *);
inline EXTERN yamop * inline EXTERN yamop *
PtoOpAdjust (yamop * ptr) PtoOpAdjust (yamop * ptr)
{ {
return (yamop *) (CharP (ptr) + HDiff); if (ptr)
return (yamop *) (CharP (ptr) + HDiff);
} }
inline EXTERN struct operator_entry *OpListAdjust (struct operator_entry *); inline EXTERN struct operator_entry *OpListAdjust (struct operator_entry *);

View File

@ -49,8 +49,6 @@ new_attribute(Na/Ar) :-
store_new_module(Mod,Ar,Position), store_new_module(Mod,Ar,Position),
assertz(existing_attribute(S,Mod,Ar,Position)). assertz(existing_attribute(S,Mod,Ar,Position)).
existing_attribute(delay(_),prolog,1,2).
store_new_module(Mod,Ar,ArgPosition) :- store_new_module(Mod,Ar,ArgPosition) :-
( (
retract(attributed_module(Mod,Position,_)) retract(attributed_module(Mod,Position,_))
@ -58,7 +56,7 @@ store_new_module(Mod,Ar,ArgPosition) :-
true true
; ;
retract(modules_with_attributes(Mods)), retract(modules_with_attributes(Mods)),
assert(modules_with_attributes([Mod|Mods])), Position = 1 assert(modules_with_attributes([Mod|Mods])), Position = 2
), ),
ArgPosition is Position+1, ArgPosition is Position+1,
( Ar == 0 -> NOfAtts is Position+1 ; NOfAtts is Position+Ar), ( Ar == 0 -> NOfAtts is Position+1 ; NOfAtts is Position+Ar),

View File

@ -9,8 +9,8 @@
% %
% Contributions to this file: % Contributions to this file:
% Author: Theofrastos Mantadelis % Author: Theofrastos Mantadelis
% $Date: 2011-02-01 18:36:41 +0100 (Tue, 01 Feb 2011) $ % $Date: 2011-02-04 16:04:49 +0100 (Fri, 04 Feb 2011) $
% $Revision: 7 $ % $Revision: 11 $
% Contributions: The timer implementation is inspired by Bernd Gutmann's timers % Contributions: The timer implementation is inspired by Bernd Gutmann's timers
% %
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@ -394,4 +394,4 @@ timer_pause(Name, Elapsed):-
retract('$timer'(Name, _, StartTime)), retract('$timer'(Name, _, StartTime)),
statistics(walltime, [EndTime, _]), statistics(walltime, [EndTime, _]),
Elapsed is EndTime - StartTime, Elapsed is EndTime - StartTime,
assert('$timer'(Name, paused, Elapsed)). assertz('$timer'(Name, paused, Elapsed)).

View File

@ -10,8 +10,8 @@
% Contributions to this file: % Contributions to this file:
% Author: Theofrastos Mantadelis % Author: Theofrastos Mantadelis
% Sugestions: Bernd Gutmann, Paulo Moura % Sugestions: Bernd Gutmann, Paulo Moura
% Version: 0.1 % $Date: 2011-02-04 16:06:56 +0100 (Fri, 04 Feb 2011) $
% Date: 19/11/2010 % $Revision: 12 $
% %
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% %
@ -337,26 +337,34 @@ in_interval_conj(Type, [Interval|Rest]):-
in_interval_conj(Type, Rest). in_interval_conj(Type, Rest).
in_interval_single(Type, ([Min], [Max])):- in_interval_single(Type, ([Min], [Max])):-
!, call(Type, Min), !, call(Type, Min),
call(Type, Max), call(Type, Max),
Min =< Max. Min =< Max.
in_interval_single(Type, ([Min], Max)):- in_interval_single(Type, ([Min], Max)):-
!, call(Type, Min), !, call(Type, Min),
call(Type, Max), type_or_inf(Type, Max),
Min < Max. Min < Max.
in_interval_single(Type, (Min, [Max])):- in_interval_single(Type, (Min, [Max])):-
!, call(Type, Min), !, type_or_inf(Type, Min),
call(Type, Max), call(Type, Max),
Min < Max. Min < Max.
in_interval_single(Type, (Min, Max)):- in_interval_single(Type, (Min, Max)):-
call(Type, Min), type_or_inf(Type, Min),
call(Type, Max), type_or_inf(Type, Max),
Min < Max, Min < Max,
Max - Min > 0.0. Max - Min > 0.0.
type_or_inf(Type, Value):-
nonvar(Type), nonvar(Value),
Value == (+inf), !.
type_or_inf(Type, Value):-
nonvar(Type), nonvar(Value),
Value == (-inf), !.
type_or_inf(Type, Value):- call(Type, Value).
in_interval(Type, [Interval|_Rest], Value):- in_interval(Type, [Interval|_Rest], Value):-
in_interval(Type, Interval, Value), !. in_interval(Type, Interval, Value), !.
in_interval(Type, [_Interval|Rest], Value):- in_interval(Type, [_Interval|Rest], Value):-

View File

@ -104,6 +104,10 @@ YAP_ULONG_LONG tot_gc_recovered TotGcRecovered =0L
Int last_gc_time LastGcTime =0L Int last_gc_time LastGcTime =0L
Int last_ss_time LastSSTime =0L Int last_ss_time LastSSTime =0L
#if LOW_LEVEL_TRACER
Int total_cps Yap_total_choicepoints =0
#endif
// global variables that cannot be global in a thread/or-p implementation // global variables that cannot be global in a thread/or-p implementation
#if defined(YAPOR) || defined(THREADS) #if defined(YAPOR) || defined(THREADS)
lockvar signal_lock SignalLock MkLock lockvar signal_lock SignalLock MkLock

View File

@ -213,10 +213,10 @@
reset_problog_flags/0, reset_problog_flags/0,
problog_flag/2]). problog_flag/2]).
:- use_module(gflags). :- use_module(gflags).
:- use_module(os). :- use_module(os).
:- use_module(logger). :- use_module(logger).
:- use_module(library(system), [file_exists/1, delete_file/1]).
problog_define_flag(Flag, Type, Description, DefaultValue):- problog_define_flag(Flag, Type, Description, DefaultValue):-
flag_define(Flag, Type, DefaultValue, Description). flag_define(Flag, Type, DefaultValue, Description).

@ -1 +1 @@
Subproject commit 73e4e086d06c54210100f0faaeccbea276c707eb Subproject commit 29151b2fe68f2dc727cdc07040e1fa1ad4fcca20

View File

@ -293,7 +293,7 @@ between(I,M,J) :-
( (
var(J) var(J)
-> ->
'$between'(I,M,J) I =< M, '$between'(I,M,J)
; ;
integer(J) integer(J)
-> ->