first attemp at deletion.

This commit is contained in:
Vítor Santos Costa 2010-11-03 16:16:40 +00:00
parent cca1461747
commit 2f525cb2f3
4 changed files with 119 additions and 94 deletions

View File

@ -1,10 +1,4 @@
%:- ensure_loaded(l
type extensional root(module).
type extensional neighbor(module, module).
type extensional temperature(module, float).
type logical_neighbor parent(module, first module). type logical_neighbor parent(module, first module).
type maxTemp(module, max float). type maxTemp(module, max float).
@ -29,6 +23,7 @@ globalMax(B, T) :-
globalMax(A, T). globalMax(A, T).
type localMax(module). type localMax(module).
localMax(A) :- localMax(A) :-
temperature(A,T), temperature(A,T),
forall forall

View File

@ -21,8 +21,6 @@
:- reexport(meld/meldc). :- reexport(meld/meldc).
:- reexport(meld/meldtd).
simulate(G) :- simulate(G) :-
input_graph(G), input_graph(G),
live. live.

View File

@ -15,12 +15,6 @@
:- use_module(library(meld)). :- use_module(library(meld)).
:- use_module(meldtd,
[
meld_top_down_compile/2,
meld_top_down_aggregate/3
]).
:- use_module(library(terms), [ :- use_module(library(terms), [
variable_in_term/2 variable_in_term/2
]). ]).
@ -65,10 +59,8 @@ type_declaration(T, Program) :-
check_aggregate(Args, 1, NewArgs, Aggregation, Arg), check_aggregate(Args, 1, NewArgs, Aggregation, Arg),
!, !,
NT =.. [P|NewArgs], NT =.. [P|NewArgs],
meld_top_down_aggregate(T, Aggregation, Arg),
assert_type(NT, Program, aggregation(Aggregation, Arg)). assert_type(NT, Program, aggregation(Aggregation, Arg)).
type_declaration(T, Program) :- type_declaration(T, Program) :-
meld_top_down_aggregate(T, horn, _),
assert_type(T, Program, horn). assert_type(T, Program, horn).
assert_type(NT, Program, Agg) :- assert_type(NT, Program, Agg) :-
@ -88,8 +80,7 @@ ground_term(_, []).
rule(Head, Body) :- rule(Head, Body) :-
bodytolist(Body, L, []), bodytolist(Body, L, []),
compile_goals(L, [], Head), compile_goals(L, [], Head).
meld_top_down_compile(Head, Body).
compile_goals([], _, _). compile_goals([], _, _).
compile_goals([Goal|Goals], Gs, Head) :- compile_goals([Goal|Goals], Gs, Head) :-
@ -160,26 +151,32 @@ extra_head(Head) -->
{ type(Head, _, _, horn) }, { type(Head, _, _, horn) },
[push(Head)]. [push(Head)].
extra_head(Head) --> extra_head(Head) -->
{ type(Head, _, _, aggregation(first, Arg)), freshen(Head, Arg, VHead) }, { type(Head, _, _, aggregation(first, Arg)),
freshen(Head, Arg, VHead) },
[ meld_interpreter:first(VHead, Head)]. [ meld_interpreter:first(VHead, Head)].
extra_head(Head) --> extra_head(Head) -->
{ type(Head, _, _, aggregation(max, Arg)), freshen(Head, Arg, VHead) }, { type(Head, _, _, aggregation(max, Arg)),
freshen(Head, Arg, VHead) },
[ meld_interpreter:max(VHead, Arg, Head)]. [ meld_interpreter:max(VHead, Arg, Head)].
extra_head(Head) --> extra_head(Head) -->
{ type(Head, _, _, aggregation(min, Arg)), freshen(Head, Arg, VHead) }, { type(Head, _, _, aggregation(min, Arg)),
freshen(Head, Arg, VHead) },
[ meld_interpreter:min(VHead, Arg, Head)]. [ meld_interpreter:min(VHead, Arg, Head)].
extra_delete(Head) --> extra_delete(Head) -->
{ type(Head, _, _, horn) }, { type(Head, _, _, horn) },
[meld_interpreter:deleted(Head)]. [meld_interpreter:deleted(Head)].
extra_delete(Head) --> extra_delete(Head) -->
{ type(Head, _, _, aggregation(first, Arg)), freshen(Head, Arg, VHead) }, { type(Head, _, _, aggregation(first, Arg)),
freshen(Head, Arg, VHead) },
[ meld_interpreter:delete_from_first(VHead, Head)]. [ meld_interpreter:delete_from_first(VHead, Head)].
extra_delete(Head) --> extra_delete(Head) -->
{ type(Head, _, _, aggregation(max, Arg)), freshen(Head, Arg, VHead) }, { type(Head, _, _, aggregation(max, Arg)),
freshen(Head, Arg, VHead) },
[ meld_interpreter:delete_from_max(VHead, Arg, Head)]. [ meld_interpreter:delete_from_max(VHead, Arg, Head)].
extra_delete(Head) --> extra_delete(Head) -->
{ type(Head, _, _, aggregation(min, Arg)), freshen(Head, Arg, VHead) }, { type(Head, _, _, aggregation(min, Arg)),
freshen(Head, Arg, VHead) },
[ meld_interpreter:delete_from_min(VHead, Arg, Head)]. [ meld_interpreter:delete_from_min(VHead, Arg, Head)].
freshen(Head, Arg, VHead) :- freshen(Head, Arg, VHead) :-

View File

@ -29,6 +29,8 @@
:- initialization :- initialization
init_meld_queue. init_meld_queue.
:- dynamic speculative_delete/3.
live :- live :-
repeat, repeat,
( pop(Goal) -> ( pop(Goal) ->
@ -40,6 +42,10 @@ live :-
done done
). ).
done :-
speculative_delete(_, _, _), !,
push_residuals,
live.
done :- done :-
current_predicate(meld_program:P), current_predicate(meld_program:P),
P \= run/1, P \= run/1,
@ -110,8 +116,6 @@ clean(Skel) :-
% format('D~w~n',[Skel]), % format('D~w~n',[Skel]),
retractall(meld_program:Skel). retractall(meld_program:Skel).
cache(Goal) :-
writeln(cache(Goal)),fail.
cache(Goal) :- cache(Goal) :-
clause(meld_cache:Goal,_,Ref), clause(meld_cache:Goal,_,Ref),
!, !,
@ -124,108 +128,137 @@ deleted(Goal) :-
clause(meld_program:Goal,_,Ref), clause(meld_program:Goal,_,Ref),
decrease_reference_count(Ref), decrease_reference_count(Ref),
!, !,
force_delete(Goal), force_delete(Goal, Ref),
complete_delete(Goal). complete_delete(Goal).
deleted(Goal) :-
retract(speculative_delete(Goal, Ref, Count)), !,
NCount is Count-1,
(
NCount > 0
->
assert(speculative_delete(Goal, Ref, Count))
;
true
).
deleted(Goal) :- deleted(Goal) :-
% format('-~w~n',[Goal]), % format('-~w~n',[Goal]),
complete_delete(Goal). complete_delete(Goal).
force_delete(Goal) :-
meld_topdown:Goal, !, abolish_all_tables, fail.
force_delete(Goal) :-
abolish_all_tables.
complete_delete(Goal) :- complete_delete(Goal) :-
nb_getval(meld_queue, Queue), !, nb_getval(meld_queue, Queue), !,
retract(meld_program:Goal), retract(meld_program:Goal),
nb_queue_enqueue(Queue, deleted(Goal)). nb_queue_enqueue(Queue, deleted(Goal)).
force_delete(Goal, Ref) :-
current_reference_count(Ref, Count),
assert(speculative_delete(Goal, Ref, Count)).
push_residuals :-
retract(speculative_delete(Goal, _, _)),
push(Goal),
fail.
push_residuals.
% %
% first, cleanup cache % first, cleanup cache
% %
delete_from_first(_,Goal) :- delete_from_first(_,Goal) :-
clause(meld_cache:Goal,_,Ref), clause(meld_program:Goal,_,Ref), !,
( (
decrease_reference_count(Ref) decrease_reference_count(Ref)
-> ->
fail true
; ;
erase(Ref), force_delete(Goal, Ref)
fail ),
). erase(Ref),
delete_from_first(_,Goal) :- retract(meld_cache:Goal),
clause(meld_program:Goal,_,Ref),
decrease_reference_count(Ref),
!,
fail.
delete_from_first(VGoal,Goal) :-
retract(meld_program:Goal), retract(meld_program:Goal),
push(deleted(Goal)), push(deleted(Goal)),
once(meld_cache:VGoal), once(meld_cache:VGoal),
push(VGoal). push(VGoal).
delete_from_first(Goal) :-
retract(speculative_delete(Goal, Ref, Count)), !,
NCount is Count-1,
(
NCount > 0
->
assert(speculative_delete(Goal, Ref, Count))
;
true
).
delete_from_first(Goal) :-
retract(meld_cache:Goal),
push(deleted(Goal)).
delete_from_max(VGoal,Arg,Goal) :- delete_from_max(VGoal,Arg,Goal) :-
clause(meld_cache:Goal,_,Ref), clause(meld_program:Goal,_,Ref), !,
trace,
( (
decrease_reference_count(Ref), decrease_reference_count(Ref)
\+ force_delete(Goal) ->
; true
clause(meld_program:Goal,_,CRef), ;
decrease_reference_count(CRef), force_delete(Goal, Ref)
fail ),
; erase(Ref),
erase(Ref), retract(meld_cache:Goal),
new_max(VGoal, Arg, Goal)
).
new_max(VGoal,Arg,Goal) :-
% format('-~w~n',[Goal]),
retract(meld_program:Goal),
push(deleted(Goal)), push(deleted(Goal)),
maxval(Arg, meld_cache:VGoal, VGoal), new_max(VGoal, Arg).
delete_from_max(Goal) :-
retract(speculative_delete(Goal, Ref, Count)), !,
NCount is Count-1,
(
NCount > 0
->
assert(speculative_delete(Goal, Ref, Count))
;
true
).
delete_from_max(Goal) :-
retract(meld_cache:Goal),
push(deleted(Goal)).
new_max(VGoal,Arg) :-
arg(Arg, VGoal, A),
maxval(A, meld_cache:VGoal, VGoal),
push(VGoal). push(VGoal).
delete_from_min(VGoal,Arg,Goal) :- delete_from_min(VGoal,Arg,Goal) :-
clause(meld_cache:Goal,_,Ref), clause(meld_program:Goal,_,Ref), !,
( (
decrease_reference_count(Ref), decrease_reference_count(Ref)
\+ force_delete(Goal)
-> ->
clause(meld_program:Goal,_,CRef), true
decrease_reference_count(CRef), ;
fail force_delete(Goal, Ref)
; ),
erase(Ref), erase(Ref),
new_min(VGoal, Arg, Goal) retract(meld_cache:Goal),
).
new_min(VGoal,Arg,Goal) :-
% format('-~w~n',[Goal]),
retract(meld_program:Goal),
push(deleted(Goal)), push(deleted(Goal)),
writeln(delete_from_min(VGoal,Arg,Goal)), new_min(VGoal, Arg).
minval(Arg, meld_cache:VGoal, VGoal), delete_from_min(Goal) :- !,
retract(speculative_delete(Goal, Ref, Count)),
NCount is Count-1,
(
NCount > 0
->
assert(speculative_delete(Goal, Ref, Count))
;
true
).
delete_from_min(Goal) :-
retract(meld_cache:Goal),
push(deleted(Goal)).
new_min(VGoal,Arg) :-
arg(Arg, VGoal, A),
minval(A, meld_cache:VGoal, VGoal),
push(VGoal). push(VGoal).
:- meta_predicate minval(+,:,-), maxval(+,:,-). :- meta_predicate minval(+,:,-), maxval(+,:,-).
minval(_,_,_) :-
nb_setval(min, +inf),
nb_setval(min_arg, '$none'),
fail.
minval(V,G,GMax) :-
call(G),
nb_getval(min, V0),
V < V0,
nb_setval(min, V),
nb_setval(min_arg, V.GMax),
fail.
minval(V,_,GMax) :-
nb_getval(min_arg, V.GMax).
maxval(V,G,GMax) :- maxval(V,G,GMax) :-
Memory = f(-inf,[]), Memory = f(-inf,[]),
( (
@ -233,7 +266,8 @@ maxval(V,G,GMax) :-
arg(1, Memory, V0), arg(1, Memory, V0),
V > V0, V > V0,
nb_setarg(1, Memory, V), nb_setarg(1, Memory, V),
nb_setarg(2, Memory, V.GMax) nb_setarg(2, Memory, V.GMax),
fail
; ;
arg(2, Memory, V.GMax) arg(2, Memory, V.GMax)
). ).
@ -245,7 +279,8 @@ minval(V,G,GMin) :-
arg(1, Memory, V0), arg(1, Memory, V0),
V < V0, V < V0,
nb_setarg(1, Memory, V), nb_setarg(1, Memory, V),
nb_setarg(2, Memory, V.GMin) nb_setarg(2, Memory, V.GMin),
fail
; ;
arg(2, Memory, V.GMin) arg(2, Memory, V.GMin)
). ).