more meld updates.

This commit is contained in:
Vitor Santos Costa 2010-11-03 00:33:26 +00:00
parent 89ef9ac1e4
commit a90e006be0
7 changed files with 130 additions and 20 deletions

View File

@ -637,7 +637,7 @@ install_data:
$(INSTALL_DATA) $(srcdir)/LGPL/pillow/pillow.pl $(DESTDIR)$(SHAREDIR)/Yap/
@INSTALLCLP@(cd LGPL/clp ; $(MAKE) install)
(cd packages/CLPBN ; $(MAKE) install)
(cd packages/meld; $(MAKE))
(cd packages/meld; $(MAKE) install)
(cd packages/ProbLog ; $(MAKE) install)
@ENABLE_CHR@ (cd packages/chr ; $(MAKE) install)
@ENABLE_CHR@ (cd packages/clpqr ; $(MAKE) install)

View File

@ -1,3 +1,5 @@
root(a).
neighbor(a,b).

View File

@ -1,6 +1,10 @@
%:- 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 maxTemp(module, max float).

View File

@ -1,7 +1,14 @@
:- style_check(all).
:- yap_flag(unknown,error).
:- module(meld_core,
[simulate/1,
op(1200, fy, (type)),
op(1150, fy, (logical_neighbor)),
op(1150, fy, (extensional)),
op( 500, fy, (first)),
op( 500, fy, (max)),
op( 950, fy, (forall)),
@ -14,9 +21,10 @@
:- reexport(meld/meldc).
:- reexport(meld/meldtd).
simulate(G) :-
input_graph(G),
live.

View File

@ -1,7 +1,3 @@
:- style_check(all).
:- yap_flag(unknown,error).
:- module(meld_compiler,
[
mcompile/1,
@ -17,7 +13,13 @@
max/3
]).
:- use_module(meld).
:- use_module(library(meld)).
:- use_module(meldtd,
[
meld_top_down_compile/2,
meld_top_down_aggregate/3
]).
:- use_module(library(terms), [
variable_in_term/2
@ -47,6 +49,11 @@ mcompile(type(T), Program, Vars) :-
mcompile((Head :- Body), _, _Vars) :-
rule(Head, Body).
type_declaration(extensional(T), Program) :- !,
functor(T, Na, Arity),
functor(NT, Na, Arity),
assert(meld_topdown:extensional(NT, Na, Arity)),
type_declaration(T, Program).
type_declaration(logical_neighbor(T), Program) :- !,
type_declaration(T, Program).
type_declaration(T, _) :-
@ -58,8 +65,10 @@ type_declaration(T, Program) :-
check_aggregate(Args, 1, NewArgs, Aggregation, Arg),
!,
NT =.. [P|NewArgs],
meld_top_down_aggregate(T, Aggregation, Arg),
assert_type(NT, Program, aggregation(Aggregation, Arg)).
type_declaration(T, Program) :-
meld_top_down_aggregate(T, horn, _),
assert_type(T, Program, horn).
assert_type(NT, Program, Agg) :-
@ -79,7 +88,8 @@ ground_term(_, []).
rule(Head, Body) :-
bodytolist(Body, L, []),
compile_goals(L, [], Head).
compile_goals(L, [], Head),
meld_top_down_compile(Head, Body).
compile_goals([], _, _).
compile_goals([Goal|Goals], Gs, Head) :-

View File

@ -6,7 +6,9 @@
push/1,
first/2,
min/3,
max/3
max/3,
minval/3,
maxval/3
]).
@ -51,7 +53,7 @@ done.
delete(Fact) :-
nb_getval(meld_queue, Queue),
retract(meld_program:Fact),
nb_queue_enqueue(Queue, deleted(Fact)),
nb_queue_enqueue(Queue, deleted(Fact)),
live.
pop(Goal) :-
@ -61,12 +63,10 @@ pop(Goal) :-
push(Goal) :-
clause(meld_program:Goal,_,Ref),
!,
writeln(Goal+ref),
increase_reference_count(Ref),
fail.
push(Goal) :-
% format('+~w~n',[Goal]),
writeln(Goal+0),
format('+~w~n',[Goal]),
nb_getval(meld_queue, Queue), !,
assert(meld_program:Goal),
nb_queue_enqueue(Queue, Goal).
@ -124,15 +124,22 @@ deleted(Goal) :-
clause(meld_program:Goal,_,Ref),
decrease_reference_count(Ref),
!,
fail.
force_delete(Goal),
complete_delete(Goal).
deleted(Goal) :-
% format('-~w~n',[Goal]),
complete_delete(Goal).
force_delete(Goal) :-
meld_topdown:Goal, !, abolish_all_tables, fail.
force_delete(Goal) :-
abolish_all_tables.
complete_delete(Goal) :-
nb_getval(meld_queue, Queue), !,
retract(meld_program:Goal),
nb_queue_enqueue(Queue, deleted(Goal)).
%
% first, cleanup cache
%
@ -160,9 +167,11 @@ delete_from_first(VGoal,Goal) :-
delete_from_max(VGoal,Arg,Goal) :-
clause(meld_cache:Goal,_,Ref),
trace,
(
decrease_reference_count(Ref)
->
decrease_reference_count(Ref),
\+ force_delete(Goal)
;
clause(meld_program:Goal,_,CRef),
decrease_reference_count(CRef),
fail
@ -175,14 +184,14 @@ new_max(VGoal,Arg,Goal) :-
% format('-~w~n',[Goal]),
retract(meld_program:Goal),
push(deleted(Goal)),
writeln(delete_from_max(VGoal,Arg,Goal)),
maxval(Arg, meld_cache:VGoal, VGoal),
push(VGoal).
delete_from_min(VGoal,Arg,Goal) :-
clause(meld_cache:Goal,_,Ref),
(
decrease_reference_count(Ref)
decrease_reference_count(Ref),
\+ force_delete(Goal)
->
clause(meld_program:Goal,_,CRef),
decrease_reference_count(CRef),
@ -200,6 +209,8 @@ new_min(VGoal,Arg,Goal) :-
minval(Arg, meld_cache:VGoal, VGoal),
push(VGoal).
:- meta_predicate minval(+,:,-), maxval(+,:,-).
minval(_,_,_) :-
nb_setval(min, +inf),
nb_setval(min_arg, '$none'),

75
packages/meld/meldtd.yap Normal file
View File

@ -0,0 +1,75 @@
:- module(meld_topdown,
[
meld_top_down_compile/2,
meld_top_down_aggregate/3
]).
:- use_module(meldi,
[
maxval/3,
minval/3
]).
:- dynamic extensional/3, translate/2.
meld_top_down_aggregate(S0, horn, _) :-
functor(S0,Na,Arg),
table(Na/Arg).
meld_top_down_aggregate(S0, max, Arg) :-
functor(S0, Na, Arg),
functor(S, Na, Arg),
table(Na/Arg),
meld_compiler:freshen(S, Arg, VHead),
VHead =.. [Na|Args],
atom_concat([Na,'__max'], NewName),
NVHead =.. [NewName|Args],
arg(Arg, NVHead, A),
arg(Arg, S, MAX),
assert_static((S :- maxval(A, NVHead, MAX))),
assert(translate(Na,NewName)).
meld_top_down_aggregate(S0, min, Arg) :-
functor(S0, Na, Arg),
functor(S, Na, Arg),
table(Na/Arg),
meld_compiler:freshen(S, Arg, VHead),
VHead =.. [Na|Args],
atom_concat([Na,'__max'], NewName),
NVHead =.. [NewName|Args],
arg(Arg, NVHead, A),
arg(Arg, S, MIN),
assert_static((S :- minval(A, NVHead, MIN))),
assert(translate(Na,NewName)).
meld_top_down_aggregate(S0, first, _) :-
functor(S0, Na, Arg),
functor(S, Na, Arg),
table(Na/Arg),
S =.. [Na|Args],
atom_concat([Na,'__max'], NewName),
NS =.. [NewName|Args],
assert_static((S :- once(NS))),
assert(translate(Na,NewName)).
meld_top_down_compile(Head, Body) :-
compile_body(Body, NBody),
compile_aggregate(Head, NHead),
assert_static((NHead :- NBody)).
compile_body((G1,G2), (NG1, NG2)) :- !,
compile_body(G1, NG1),
compile_body(G2, NG2).
compile_body((forall G then B), (forall NG then NB)) :- !,
compile_body(G, NG),
compile_body(B, NB).
compile_body(G, meld_program:G) :-
extensional(G,_,_), !.
compile_body(G, G).
compile_aggregate(Head, NewHead) :-
Head =.. [Na|Args],
translate(Na, NewNa), !,
NewHead =.. [NewNa|Args].
compile_aggregate(Head, Head).