Skip to content

Commit

Permalink
now wakes the peers resolves bug I mention in SWI-Prolog/roadmap#40 (…
Browse files Browse the repository at this point in the history
  • Loading branch information
TeamSPoon committed Jan 21, 2016
1 parent d3168c9 commit 168228c
Show file tree
Hide file tree
Showing 4 changed files with 31 additions and 25 deletions.
11 changes: 9 additions & 2 deletions boot/attvar.pl
Expand Up @@ -30,6 +30,7 @@

:- module('$attvar',
[ '$wakeup'/1, % +Wakeup list
unify/4,
freeze/2, % +Var, :Goal
frozen/2, % @Var, -Goal
call_residue_vars/2, % :Goal, -Vars
Expand Down Expand Up @@ -80,6 +81,12 @@
'$attvar_assign'(Var,Value),
call(Next).

unify(att(Module, _AttVal, Rest), Next, Var, Value):-
Module:verify_attributes(Var, Value, Goals),
unify(Rest, Next, Var, Value),
goals_with_module(Goals,Module).
unify(_, Next,Var, Value):-
call(Next).

goals_with_module([G|Gs], M):- !,
M:call(G),
Expand All @@ -91,7 +98,7 @@
system:compare_to_retcode(<,-1).
system:compare_to_retcode(==,0).
:- meta_predicate(system:wnmt(:)).
system:wnmt(G):-setup_call_cleanup(metaterm_options(W,0),G,metaterm_options(0,W)).
system:wnmt(G):-setup_call_cleanup(metaterm_options(W,0),(trace,G),metaterm_options(0,W)).
system:'$meta'('==', Var, Value, 1):-!, wnmt(Var==Value). % this one ends up calling compare/3
system:'$meta'('=@=', Var, Value, 1):-!, wnmt(Var=@=Value).
system:'$meta'(copy_term, Var, Value, 1):-!, wnmt(copy_term(Var,Value)).
Expand All @@ -108,7 +115,7 @@
system:'$meta'('$undo_unify', _, Goal, 1):- '$schedule_wakeup'(Goal).
'$undo_unify':verify_attributes(_,_,[]).
undo(GoalIn):-
metaterm_options(W,W), T is W \/ 8, % Flag to turn on trail scanning
metaterm_options(W,W), T is W \/ 0x0800, % Flag to turn on trail scanning
( T == W
-> GoalIn=Goal ;
Goal=(metaterm_options(_,W),GoalIn)),
Expand Down
1 change: 1 addition & 0 deletions src/ATOMS
Expand Up @@ -1015,6 +1015,7 @@ F tty 1
F type 1
F type_error 2
F undefinterc 4
F unify 4
F unify_determined 2
F uninstantiation_error 1
F var 1
Expand Down
30 changes: 14 additions & 16 deletions src/pl-attvar.c
Expand Up @@ -206,10 +206,10 @@ assignAttVar(Word av, Word value, int flags ARG_LD)
Discussion: https://github.com/SWI-Prolog/roadmap/issues/40#issuecomment-173002313
?- when(=(X,Y),X==Y), Y=A, X=A.
?- on_unify(X, X==Y), Y=A, X=A.
Yes.
?- when(=(X,Y),X\==Y), Y=A, X=A.
?- on_unify(X, X\==Y), Y=A, X=A.
No.
*/
Expand All @@ -228,19 +228,17 @@ assignAttVar(Word av, Word value, int flags ARG_LD)

DEBUG(MSG_WAKEUPS, Sdprintf("assignAttVar(%s)\n", vName(av)));

if ( isAttVar(*value) )
{ if ( value > av )
{ if (!(flags & ATT_NO_SWAP ))
{ Word tmp = av;
av = value;
value = tmp;
}
} else if ( av == value )
return;
}
bool other_attvar = isAttVar(*value);

if ( av == value ) return;

if( !(flags & ATT_ASSIGNONLY) )
{ registerWakeup(FUNCTOR_wakeup4, av, valPAttVar(*av), value PASS_LD);
{
if( other_attvar && (MATTS_DEFAULT & MATTS_PEER_WAKEUP) )
{ DEBUG(MSG_WAKEUPS, Sdprintf("MATTS_PEER_WAKEUP(%s)\n", vName(value)));
registerWakeup(FUNCTOR_unify4, value, valPAttVar(*value), av PASS_LD);
}
registerWakeup(FUNCTOR_wakeup4, av, valPAttVar(*av), value PASS_LD);
}

if ( (flags&ATT_WAKEBINDS) )
Expand Down Expand Up @@ -270,10 +268,10 @@ assignAttVar(Word av, Word value, int flags ARG_LD)
{ if( (flags & ATT_ASSIGNONLY) )
{ DEBUG(MSG_WAKEUPS, Sdprintf("Assigning attvar with a plain VAR ref\n"));
*av = makeRef(value); /* JW: Does this happen? */
} else
} else
{ DEBUG(MSG_WAKEUPS, Sdprintf("Putting ORIGINAL attvar into plain var\n"));
Trail(value, makeRef(av));
}
Trail(value, makeRef(av));
}
} else
*av = *value;

Expand Down
14 changes: 7 additions & 7 deletions src/pl-incl.h
Expand Up @@ -2017,17 +2017,17 @@ typedef struct
* METATERMS *
*******************************/

#define MATTS_ENABLE_VMI 0x0100 /* Hook WAM */
#define MATTS_ENABLE_CPREDS 0x0200 /* Hook CPREDS (WAM can miss a few)*/
#define MATTS_SKIP_HIDDEN 0x0400 /* dont factor $meta into attvar identity */
#define MATTS_ENABLE_UNDO 0x0800 /* check attvars for undo hooks (perfomance checking)*/
#define MATTS_DO_UNIFY 0x1000 /* debugging for a moment trying to guage if damaging do_unify()
#define MATTS_ENABLE_VMI 0x0010 /* Hook WAM */
#define MATTS_ENABLE_CPREDS 0x0020 /* Hook CPREDS (WAM can miss a few)*/
#define MATTS_SKIP_HIDDEN 0x0040 /* dont factor $meta into attvar identity */
#define MATTS_ENABLE_UNDO 0x0080 /* check attvars for undo hooks (perfomance checking)*/
#define MATTS_DO_UNIFY 0x0100 /* debugging for a moment trying to guage if damaging do_unify()
Goal, really I would like to figure out the best way to allow unification to
a between an attvar and a variable. Instead of merly placing the entire attvar self into the variable,
I want the attvar's hook to copy some attributes onto the plain variable (turning it into an attvar)
as the result of unification.

as the result of unification.
*/
#define MATTS_PEER_WAKEUP 0x0200 /* Wakeup peer attvars */
#define MATTS_DISABLED 0x8000 /* disable all options (allows the options to be saved) */
#define MATTS_DEFAULT MATTS_ENABLE_VMI|MATTS_ENABLE_CPREDS|MATTS_SKIP_HIDDEN|ATT_NO_SWAP

Expand Down

0 comments on commit 168228c

Please sign in to comment.