improve meld emulation to compile pagerank example.
This commit is contained in:
parent
bf6033082d
commit
77407bc14e
@ -24,6 +24,8 @@ INSTALL_PROGRAM=@INSTALL_PROGRAM@
|
|||||||
srcdir=@srcdir@
|
srcdir=@srcdir@
|
||||||
YAP_EXTRAS=@YAP_EXTRAS@
|
YAP_EXTRAS=@YAP_EXTRAS@
|
||||||
|
|
||||||
|
EXDIR=$(srcdir)/examples
|
||||||
|
|
||||||
MELD_PROGRAMS= \
|
MELD_PROGRAMS= \
|
||||||
$(srcdir)/meldtd.yap \
|
$(srcdir)/meldtd.yap \
|
||||||
$(srcdir)/meldc.yap \
|
$(srcdir)/meldc.yap \
|
||||||
@ -31,11 +33,12 @@ MELD_PROGRAMS= \
|
|||||||
$(srcdir)/meldp.yap
|
$(srcdir)/meldp.yap
|
||||||
|
|
||||||
MELD_EXAMPLES= \
|
MELD_EXAMPLES= \
|
||||||
$(srcdir)/maxtemp.meld \
|
$(EXDIR)/temperature/maxtemp.meld \
|
||||||
$(srcdir)/graph0.meld \
|
$(EXDIR)/temperature/graph0.meld \
|
||||||
$(srcdir)/graph1.meld \
|
$(EXDIR)/temperature/graph1.meld \
|
||||||
$(srcdir)/graph2.meld \
|
$(EXDIR)/temperature/graph2.meld \
|
||||||
$(srcdir)/graph3.meld
|
$(EXDIR)/temperature/graph3.meld \
|
||||||
|
$(EXDIR)/pagerank/pagerank.meld \
|
||||||
|
|
||||||
PROGRAMS= \
|
PROGRAMS= \
|
||||||
$(srcdir)/meld.yap \
|
$(srcdir)/meld.yap \
|
||||||
|
@ -17,8 +17,8 @@ Supported:
|
|||||||
- basic semantics
|
- basic semantics
|
||||||
- aggregates
|
- aggregates
|
||||||
- updates
|
- updates
|
||||||
|
- delete
|
||||||
|
|
||||||
Unsupported:
|
Unsupported:
|
||||||
- delete
|
|
||||||
- distributed execution :)
|
- distributed execution :)
|
||||||
|
|
||||||
|
13
packages/meld/examples/pagerank/README
Normal file
13
packages/meld/examples/pagerank/README
Normal file
@ -0,0 +1,13 @@
|
|||||||
|
Pagerank Algorithm in Meld
|
||||||
|
Example of Iteration and Arithmetic Builtins
|
||||||
|
|
||||||
|
Use as follows:
|
||||||
|
|
||||||
|
bash> yap
|
||||||
|
|
||||||
|
:- use_module(library(meld)).
|
||||||
|
|
||||||
|
:- mcompile(pagerank).
|
||||||
|
|
||||||
|
:- simulate(g10).
|
||||||
|
|
30
packages/meld/examples/pagerank/g10.meld
Normal file
30
packages/meld/examples/pagerank/g10.meld
Normal file
@ -0,0 +1,30 @@
|
|||||||
|
edge(0, 9).
|
||||||
|
edge(0, 6).
|
||||||
|
edge(1, 6).
|
||||||
|
edge(2, 9).
|
||||||
|
edge(2, 3).
|
||||||
|
edge(2, 6).
|
||||||
|
edge(2, 8).
|
||||||
|
edge(3, 4).
|
||||||
|
edge(4, 2).
|
||||||
|
edge(4, 1).
|
||||||
|
edge(5, 4).
|
||||||
|
edge(5, 3).
|
||||||
|
edge(5, 8).
|
||||||
|
edge(5, 9).
|
||||||
|
edge(5, 2).
|
||||||
|
edge(6, 2).
|
||||||
|
edge(6, 8).
|
||||||
|
edge(6, 7).
|
||||||
|
edge(6, 3).
|
||||||
|
edge(6, 1).
|
||||||
|
edge(7, 6).
|
||||||
|
edge(7, 2).
|
||||||
|
edge(7, 4).
|
||||||
|
edge(7, 9).
|
||||||
|
edge(7, 5).
|
||||||
|
edge(8, 4).
|
||||||
|
edge(8, 9).
|
||||||
|
edge(8, 0).
|
||||||
|
edge(8, 3).
|
||||||
|
edge(9, 7).
|
3030
packages/meld/examples/pagerank/g100.meld
Normal file
3030
packages/meld/examples/pagerank/g100.meld
Normal file
File diff suppressed because it is too large
Load Diff
34
packages/meld/examples/pagerank/pagerank.meld
Normal file
34
packages/meld/examples/pagerank/pagerank.meld
Normal file
@ -0,0 +1,34 @@
|
|||||||
|
|
||||||
|
type rank(node, int, float).
|
||||||
|
type calcRank(node, int, sum float).
|
||||||
|
type persistent numPages(node, int).
|
||||||
|
type numLinks(node, sum int).
|
||||||
|
|
||||||
|
const damping = 0.85.
|
||||||
|
const num_iterations = 4.
|
||||||
|
% extern float to_float(int).
|
||||||
|
% extern float float_abs(float).
|
||||||
|
|
||||||
|
rank(A, 0, 1.0 / to_float(T)) :- numPages(A, T).
|
||||||
|
rank(A, I, V) :-
|
||||||
|
calcRank(A, I, T),
|
||||||
|
Before = I - 1,
|
||||||
|
rank(A, Before, VOld),
|
||||||
|
V = damping + (1.0 - damping) * T,
|
||||||
|
I =< num_iterations.
|
||||||
|
|
||||||
|
% //float_abs((damping + (1.0 - damping) * T) - VOld) > 0.001.
|
||||||
|
|
||||||
|
calcRank(A, I + 1, O / to_float(C)) :-
|
||||||
|
edge(B, A),
|
||||||
|
rank(B, I, O),
|
||||||
|
numLinks(B, C).
|
||||||
|
|
||||||
|
numLinks(A, 1) :-
|
||||||
|
edge(A,B).
|
||||||
|
|
||||||
|
numPages(A, 1) :-
|
||||||
|
edge(B,A).
|
||||||
|
|
||||||
|
|
||||||
|
|
@ -8,9 +8,13 @@
|
|||||||
[simulate/1,
|
[simulate/1,
|
||||||
op(1200, fy, (type)),
|
op(1200, fy, (type)),
|
||||||
op(1150, fy, (logical_neighbor)),
|
op(1150, fy, (logical_neighbor)),
|
||||||
|
op(1150, fy, (const)),
|
||||||
op(1150, fy, (extensional)),
|
op(1150, fy, (extensional)),
|
||||||
|
op(1150, fy, (persistent)),
|
||||||
|
op(1150, fy, (extern)),
|
||||||
op( 500, fy, (first)),
|
op( 500, fy, (first)),
|
||||||
op( 500, fy, (max)),
|
op( 500, fy, (max)),
|
||||||
|
op( 500, fy, (sum)),
|
||||||
op( 950, fy, (forall)),
|
op( 950, fy, (forall)),
|
||||||
op( 900, xfy, (then))
|
op( 900, xfy, (then))
|
||||||
]).
|
]).
|
||||||
|
@ -1,3 +1,8 @@
|
|||||||
|
%
|
||||||
|
% A compiler for Meld programs
|
||||||
|
% can understand aggregates.
|
||||||
|
%
|
||||||
|
|
||||||
:- module(meld_compiler,
|
:- module(meld_compiler,
|
||||||
[
|
[
|
||||||
mcompile/1,
|
mcompile/1,
|
||||||
@ -10,7 +15,8 @@
|
|||||||
push/1,
|
push/1,
|
||||||
first/2,
|
first/2,
|
||||||
min/3,
|
min/3,
|
||||||
max/3
|
max/3,
|
||||||
|
sum/3
|
||||||
]).
|
]).
|
||||||
|
|
||||||
:- use_module(library(meld)).
|
:- use_module(library(meld)).
|
||||||
@ -19,6 +25,13 @@
|
|||||||
variable_in_term/2
|
variable_in_term/2
|
||||||
]).
|
]).
|
||||||
|
|
||||||
|
:- use_module(library(ordsets), [
|
||||||
|
ord_subset/2,
|
||||||
|
ord_union/3
|
||||||
|
]).
|
||||||
|
|
||||||
|
:- dynamic meld_constants:const/2.
|
||||||
|
|
||||||
mcompile(Program) :-
|
mcompile(Program) :-
|
||||||
open(Program, read, P),
|
open(Program, read, P),
|
||||||
init_mcompile(Program),
|
init_mcompile(Program),
|
||||||
@ -40,6 +53,9 @@ init_mcompile(Program) :-
|
|||||||
mcompile(type(T), Program, Vars) :-
|
mcompile(type(T), Program, Vars) :-
|
||||||
ground_term(T, Vars),
|
ground_term(T, Vars),
|
||||||
type_declaration(T, Program), !.
|
type_declaration(T, Program), !.
|
||||||
|
mcompile(const(T=V), _Program, Vars) :-
|
||||||
|
ground_term(T, Vars),
|
||||||
|
const_declaration(T, V), !.
|
||||||
mcompile((Head :- Body), _, _Vars) :-
|
mcompile((Head :- Body), _, _Vars) :-
|
||||||
rule(Head, Body).
|
rule(Head, Body).
|
||||||
|
|
||||||
@ -50,6 +66,10 @@ type_declaration(extensional(T), Program) :- !,
|
|||||||
type_declaration(T, Program).
|
type_declaration(T, Program).
|
||||||
type_declaration(logical_neighbor(T), Program) :- !,
|
type_declaration(logical_neighbor(T), Program) :- !,
|
||||||
type_declaration(T, Program).
|
type_declaration(T, Program).
|
||||||
|
type_declaration(persistent(T), Program) :- !,
|
||||||
|
type_declaration(T, Program).
|
||||||
|
type_declaration(extern(T), Program) :- !,
|
||||||
|
type_declaration(T, Program).
|
||||||
type_declaration(T, _) :-
|
type_declaration(T, _) :-
|
||||||
functor(T, N, A),
|
functor(T, N, A),
|
||||||
dynamic(meld_program:N/A),
|
dynamic(meld_program:N/A),
|
||||||
@ -68,9 +88,15 @@ assert_type(NT, Program, Agg) :-
|
|||||||
functor(Spec, Na, Ar),
|
functor(Spec, Na, Ar),
|
||||||
assert(type(Spec, NT, Program, Agg)).
|
assert(type(Spec, NT, Program, Agg)).
|
||||||
|
|
||||||
|
const_declaration(C,V) :- !,
|
||||||
|
( atom(C) -> true ; throw(type_error(atom,C),const(C=V))),
|
||||||
|
( number(V) -> true ; throw(type_error(number,V),const(C=V))),
|
||||||
|
assert(meld_constants:const(C, V)).
|
||||||
|
|
||||||
check_aggregate([first(Type)|Args], I, [Type|Args], first, I) :- !.
|
check_aggregate([first(Type)|Args], I, [Type|Args], first, I) :- !.
|
||||||
check_aggregate([max(Type)|Args], I, [Type|Args], max, I) :- !.
|
check_aggregate([max(Type)|Args], I, [Type|Args], max, I) :- !.
|
||||||
check_aggregate([min(Type)|Args], I, [Type|Args], min, I) :- !.
|
check_aggregate([min(Type)|Args], I, [Type|Args], min, I) :- !.
|
||||||
|
check_aggregate([sum(Type)|Args], I, [Type|Args], sum, I) :- !.
|
||||||
check_aggregate([Type|Args], I, [Type|NewArgs], Agg, Arg) :-
|
check_aggregate([Type|Args], I, [Type|NewArgs], Agg, Arg) :-
|
||||||
atom(Type),
|
atom(Type),
|
||||||
I1 is I+1,
|
I1 is I+1,
|
||||||
@ -78,15 +104,68 @@ check_aggregate([Type|Args], I, [Type|NewArgs], Agg, Arg) :-
|
|||||||
|
|
||||||
ground_term(_, []).
|
ground_term(_, []).
|
||||||
|
|
||||||
|
%
|
||||||
|
% Rule compiler
|
||||||
|
%
|
||||||
rule(Head, Body) :-
|
rule(Head, Body) :-
|
||||||
bodytolist(Body, L, []),
|
bodytolist(Body, L0, []),
|
||||||
compile_goals(L, [], Head).
|
builtins(L0, L, R),
|
||||||
|
builtins([Head], RLH, []),
|
||||||
|
join(RLH, NHead, R, []),
|
||||||
|
compile_goals(L, [], NHead).
|
||||||
|
|
||||||
|
builtins([]) --> [].
|
||||||
|
builtins(G.Gs) -->
|
||||||
|
builtin(G), !,
|
||||||
|
builtins(Gs).
|
||||||
|
|
||||||
|
builtin(Res = Op) --> !,
|
||||||
|
process_constants(Op, Res).
|
||||||
|
builtin(Goal) -->
|
||||||
|
process_constants(Goal, NGoal),
|
||||||
|
[ NGoal ].
|
||||||
|
|
||||||
|
process_constants(G, G) -->
|
||||||
|
{ var(G) }, !.
|
||||||
|
process_constants(C, V) -->
|
||||||
|
{ meld_constants:const(C,V) }, !.
|
||||||
|
process_constants(G, G) -->
|
||||||
|
{ atomic(G) }, !.
|
||||||
|
process_constants(to_float(Arg1), NArg1) --> !,
|
||||||
|
process_constants(Arg1, NArg1).
|
||||||
|
process_constants(A, NA) -->
|
||||||
|
{ arithmetic(A, Op, Arg1, Arg2) }, !,
|
||||||
|
process_constants(Arg1, NArg1),
|
||||||
|
process_constants(Arg2, NArg2),
|
||||||
|
{ arithmetic(NExp, Op, NArg1, NArg2) },
|
||||||
|
[ NA is NExp ].
|
||||||
|
process_constants(A, NA) -->
|
||||||
|
{ arithmetic(A, Op, Arg1) }, !,
|
||||||
|
process_constants(Arg1, NArg1),
|
||||||
|
{ arithmetic(NExp, Op, NArg1) },
|
||||||
|
[ NA is NExp ].
|
||||||
|
process_constants(G, NG) -->
|
||||||
|
{ G =.. [A|Args] },
|
||||||
|
process_args(Args, NArgs),
|
||||||
|
{ NG =.. [A|NArgs] }.
|
||||||
|
|
||||||
|
process_args([], []) --> [].
|
||||||
|
process_args(A.Args, NA.NArgs) -->
|
||||||
|
process_constants(A, NA),
|
||||||
|
process_args(Args, NArgs).
|
||||||
|
|
||||||
|
join([H0], H0) --> !.
|
||||||
|
join([H|T], H0) -->
|
||||||
|
[H],
|
||||||
|
join(T, H0).
|
||||||
|
|
||||||
compile_goals([], _, _).
|
compile_goals([], _, _).
|
||||||
compile_goals([Goal|Goals], Gs, Head) :-
|
compile_goals([Goal|Goals], Gs, Head) :-
|
||||||
compile_goal(Goal, Goals, Gs, Head),
|
compile_goal(Goal, Goals, Gs, Head),
|
||||||
compile_goals(Goals, [Goal|Gs], Head).
|
compile_goals(Goals, [Goal|Gs], Head).
|
||||||
|
|
||||||
|
compile_goal(BIP, _Goals, _Gs, _Head) :-
|
||||||
|
meld_builtin(BIP, _, _), !.
|
||||||
compile_goal((forall G then Do), Goals, Gs, Head) :- !,
|
compile_goal((forall G then Do), Goals, Gs, Head) :- !,
|
||||||
% make sure quantified variables are not seen outside
|
% make sure quantified variables are not seen outside
|
||||||
quantified_vars(G,Gs+Goals,NG),
|
quantified_vars(G,Gs+Goals,NG),
|
||||||
@ -100,9 +179,12 @@ compile_goal((forall G then Do), Goals, Gs, Head) :- !,
|
|||||||
extra_head(Head, BL1, []),
|
extra_head(Head, BL1, []),
|
||||||
% add the delete operation
|
% add the delete operation
|
||||||
extra_delete(Head, DelBL1, []),
|
extra_delete(Head, DelBL1, []),
|
||||||
|
% reorder builtins
|
||||||
|
reorder_builtins(NG, BLF, BLF2),
|
||||||
|
reorder_builtins(DelNG, DelBLF, DelBLF2),
|
||||||
% create the body as a conjunction
|
% create the body as a conjunction
|
||||||
listtobody(BLF, Body),
|
listtobody(BLF2, Body),
|
||||||
listtobody(DelBLF, DelBody),
|
listtobody(DelBLF2, DelBody),
|
||||||
% done
|
% done
|
||||||
assert(meld_program:(run(NG) :- Body)),
|
assert(meld_program:(run(NG) :- Body)),
|
||||||
assert(meld_program:(run(delete(DelNG)) :- DelBody)).
|
assert(meld_program:(run(delete(DelNG)) :- DelBody)).
|
||||||
@ -111,10 +193,13 @@ compile_goal(Goal, Goals, Gs, Head) :-
|
|||||||
copy_term(h(Head,BLF,BL1,Goal), h(Head,DelBLF,DelBL1,DelGoal)),
|
copy_term(h(Head,BLF,BL1,Goal), h(Head,DelBLF,DelBL1,DelGoal)),
|
||||||
extra_head(Head, BL1, []),
|
extra_head(Head, BL1, []),
|
||||||
extra_delete(Head, DelBL1, []),
|
extra_delete(Head, DelBL1, []),
|
||||||
listtobody(BLF, Body),
|
% reorder builtins
|
||||||
listtobody(DelBLF, DelBody),
|
reorder_builtins(Goal, BLF, BLF2),
|
||||||
assert(meld_program:(run(Goal) :- Body)),
|
reorder_builtins(DelGoal, DelBLF, DelBLF2),
|
||||||
assert(meld_program:(run(deleted(DelGoal)) :- DelBody)).
|
listtobody(BLF2, Body),
|
||||||
|
listtobody(DelBLF2, DelBody),
|
||||||
|
once((assert(meld_program:(run(Goal) :- Body)),
|
||||||
|
assert(meld_program:(run(deleted(DelGoal)) :- DelBody)))).
|
||||||
|
|
||||||
% quantified variables should not leave the scope of the forall.
|
% quantified variables should not leave the scope of the forall.
|
||||||
quantified_vars(G,Extern,NG) :-
|
quantified_vars(G,Extern,NG) :-
|
||||||
@ -162,6 +247,10 @@ extra_head(Head) -->
|
|||||||
{ type(Head, _, _, aggregation(min, Arg)),
|
{ type(Head, _, _, aggregation(min, Arg)),
|
||||||
freshen(Head, Arg, VHead) },
|
freshen(Head, Arg, VHead) },
|
||||||
[ meld_interpreter:min(VHead, Arg, Head)].
|
[ meld_interpreter:min(VHead, Arg, Head)].
|
||||||
|
extra_head(Head) -->
|
||||||
|
{ type(Head, _, _, aggregation(sum, Arg)),
|
||||||
|
freshen(Head, Arg, VHead) },
|
||||||
|
[ meld_interpreter:sum(VHead, Arg, Head)].
|
||||||
|
|
||||||
extra_delete(Head) -->
|
extra_delete(Head) -->
|
||||||
{ type(Head, _, _, horn) },
|
{ type(Head, _, _, horn) },
|
||||||
@ -178,6 +267,10 @@ extra_delete(Head) -->
|
|||||||
{ type(Head, _, _, aggregation(min, Arg)),
|
{ type(Head, _, _, aggregation(min, Arg)),
|
||||||
freshen(Head, Arg, VHead) },
|
freshen(Head, Arg, VHead) },
|
||||||
[ meld_interpreter:delete_from_min(VHead, Arg, Head)].
|
[ meld_interpreter:delete_from_min(VHead, Arg, Head)].
|
||||||
|
extra_delete(Head) -->
|
||||||
|
{ type(Head, _, _, aggregation(sum, Arg)),
|
||||||
|
freshen(Head, Arg, VHead) },
|
||||||
|
[ meld_interpreter:delete_from_sum(VHead, Arg, Head)].
|
||||||
|
|
||||||
freshen(Head, Arg, VHead) :-
|
freshen(Head, Arg, VHead) :-
|
||||||
Head =.. [N|Args],
|
Head =.. [N|Args],
|
||||||
@ -217,4 +310,63 @@ listtobody([G], G) :- !.
|
|||||||
listtobody([G|GL], (G,Gs)) :-
|
listtobody([G|GL], (G,Gs)) :-
|
||||||
listtobody(GL, Gs).
|
listtobody(GL, Gs).
|
||||||
|
|
||||||
|
reorder_builtins(Head, BLF, BLF2) :-
|
||||||
|
term_variables(Head, Vs0),
|
||||||
|
reorder_term(BLF, Vs0, [], BLF2).
|
||||||
|
|
||||||
|
% 4 arguments
|
||||||
|
% list of input goals
|
||||||
|
% queue of built-ins waiting for execution
|
||||||
|
% list of current variables
|
||||||
|
% output variables
|
||||||
|
%
|
||||||
|
reorder_term([], _, [], []).
|
||||||
|
reorder_term(G.Gs, Vs0, Queue, NGs) :-
|
||||||
|
meld_builtin(G, Is, Os), !,
|
||||||
|
term_variables(Is, InpVs0),
|
||||||
|
sort(InpVs0, InpVs),
|
||||||
|
continue_reorder_term(Gs, G, InpVs, Vs0, Queue, Os, NGs).
|
||||||
|
reorder_term(G.Gs, Vs0, Queue, G.NGs) :-
|
||||||
|
term_variables(G, GVs0),
|
||||||
|
sort(GVs0, GVs),
|
||||||
|
ord_union(GVs, Vs0, Vs),
|
||||||
|
wake_queue(Queue, NewQueue, Vs, Vs0, NewQueue, FVs, NGs, NGs0),
|
||||||
|
reorder_term(Gs, FVs, NewQueue, NGs0).
|
||||||
|
|
||||||
|
continue_reorder_term(Gs, G, InpVs, Vs0, Queue, Os, G.NGs) :-
|
||||||
|
ord_subset(InpVs, Vs0), !,
|
||||||
|
term_variables(Os, OutVs0),
|
||||||
|
sort(OutVs0, OutVs),
|
||||||
|
ord_union(OutVs, Vs0, Vs),
|
||||||
|
wake_queue(Queue, NewQueue, Vs, Vs0, NewQueue, FVs, NGs, NGs0),
|
||||||
|
reorder_term(Gs, FVs, NewQueue, NGs0).
|
||||||
|
continue_reorder_term(Gs, G, InpVs, Vs0, Queue, Os, NGs) :-
|
||||||
|
term_variables(Os, OutVs0),
|
||||||
|
sort(OutVs0, OutVs),
|
||||||
|
reorder_term(Gs, Vs0, q(InpVs, OutVs, G).Queue, NGs).
|
||||||
|
|
||||||
|
wake_queue([], _, Vs, _, [], Vs) --> [].
|
||||||
|
wake_queue(Q.Queue, _, Vs, Vs0, Q.Queue, Vs) --> { Vs == Vs0 }, !.
|
||||||
|
wake_queue(q(InpVs,OutVs,G).Queue, NewQueue, Vs, Vs0, Queue, FVs) -->
|
||||||
|
{ ord_subset(InpVs, Vs) }, !,
|
||||||
|
[G],
|
||||||
|
{ ord_union(OutVs, Vs, NVs) },
|
||||||
|
% restart from beginning
|
||||||
|
wake_queue(NewQueue, NewNewQueue, NVs, Vs0, NewNewQueue, FVs).
|
||||||
|
wake_queue(Q.Queue, NewQueue, NVs, Vs0, Q.NQueue, FVs) -->
|
||||||
|
wake_queue(Queue, NewQueue, NVs, Vs0, NQueue, FVs).
|
||||||
|
|
||||||
|
|
||||||
|
meld_builtin(O is I, I, O).
|
||||||
|
meld_builtin(I1 =< I2, I1-I2, []).
|
||||||
|
meld_builtin(I1 >= I2, I1-I2, []).
|
||||||
|
meld_builtin(I1 =:= I2, I1-I2, []).
|
||||||
|
|
||||||
|
arithmetic( A+B, (+), A, B).
|
||||||
|
arithmetic( A-B, (-), A, B).
|
||||||
|
arithmetic( A*B, (*), A, B).
|
||||||
|
arithmetic( A/B, (/), A, B).
|
||||||
|
|
||||||
|
arithmetic( sin(A), sin, A).
|
||||||
|
arithmetic( cos(A), cos, A).
|
||||||
|
arithmetic( tan(A), tan, A).
|
||||||
|
@ -7,6 +7,7 @@
|
|||||||
first/2,
|
first/2,
|
||||||
min/3,
|
min/3,
|
||||||
max/3,
|
max/3,
|
||||||
|
sum/3,
|
||||||
minval/3,
|
minval/3,
|
||||||
maxval/3
|
maxval/3
|
||||||
]).
|
]).
|
||||||
@ -114,6 +115,16 @@ min(Skel,_,Goal) :-
|
|||||||
cache(Goal),
|
cache(Goal),
|
||||||
push(Goal).
|
push(Goal).
|
||||||
|
|
||||||
|
sum(Skel,Arg,Goal) :-
|
||||||
|
copy_term(Skel, NGoal),
|
||||||
|
meld_program:Skel,
|
||||||
|
arg(Arg, Skel, A0),
|
||||||
|
delete(Skel),
|
||||||
|
arg(Arg, Goal, A),
|
||||||
|
AN is A0+A,
|
||||||
|
arg(Arg, NGoal, AN),
|
||||||
|
push(NGoal).
|
||||||
|
|
||||||
clean(Skel) :-
|
clean(Skel) :-
|
||||||
% format('D~w~n',[Skel]),
|
% format('D~w~n',[Skel]),
|
||||||
retractall(meld_program:Skel).
|
retractall(meld_program:Skel).
|
||||||
@ -222,6 +233,16 @@ delete_from_max(Goal) :-
|
|||||||
retract(meld_cache:Goal),
|
retract(meld_cache:Goal),
|
||||||
push(deleted(Goal)).
|
push(deleted(Goal)).
|
||||||
|
|
||||||
|
delete_from_sum(Skel,Arg,Goal) :-
|
||||||
|
copy_term(Skel, NGoal),
|
||||||
|
meld_program:Skel,
|
||||||
|
arg(Arg, Skel, A0),
|
||||||
|
delete(Skel),
|
||||||
|
arg(Arg, Goal, A),
|
||||||
|
AN is A0-A,
|
||||||
|
arg(Arg, NGoal, AN),
|
||||||
|
push(NGoal).
|
||||||
|
|
||||||
new_max(VGoal,Arg) :-
|
new_max(VGoal,Arg) :-
|
||||||
arg(Arg, VGoal, A),
|
arg(Arg, VGoal, A),
|
||||||
maxval(A, meld_cache:VGoal, VGoal),
|
maxval(A, meld_cache:VGoal, VGoal),
|
||||||
|
Reference in New Issue
Block a user