documentation and small fixes; also call for foreach

This commit is contained in:
Vítor Santos Costa
2013-09-29 11:31:18 +01:00
parent bef9cec46a
commit 7cf1b68c3a
7 changed files with 560 additions and 119 deletions

View File

@@ -48,7 +48,7 @@ problem(Z, X, InFlow, OutFlow, N) :-
% constraint
for(I in 1..N,
foreach(I in 1..N,
( I == Start ->
RHS[I] <== 1 ;
I == End ->
@@ -58,21 +58,21 @@ problem(Z, X, InFlow, OutFlow, N) :-
% must be larger than 0??
for( [I in 1..N, J in 1..N],
foreach( [I in 1..N, J in 1..N],
( D[J,I] = M ->
X[J,I] #= 0 ;
true )
),
% outflow constraint
for(I in 1..N,
foreach(I in 1..N,
OutFlow[I] #= sum(J in 1..N where D[J,I]<M, X[J,I])
),
% inflow constraint
for(J in 1..N,
foreach(J in 1..N,
InFlow[J] #= sum(I in 1..N where D[J,I]<M, X[J,I])
),
% inflow = outflow
for(I in 1..N, OutFlow[I]-InFlow[I]#=RHS[I]),
foreach(I in 1..N, OutFlow[I]-InFlow[I]#=RHS[I]),
% labeling
labeling( [], X).
@@ -118,7 +118,7 @@ out(Cost, Ts, Ins, Out, N) :-
format('Inputs =', []), maplist(out, InsL), nl,
format('Outputs =', []), maplist(out, OutL), nl,
format('transitions =~n', []),
for(I in 1..N, outl(Ts[_,I]) ).
foreach(I in 1..N, outl(Ts[_,I]) ).
outl( X ) :-
L <== X, % evaluate matrix notation to Prolog lists.

View File

@@ -18,11 +18,11 @@ problem(Ex, Els) :- ex(Ex, Exs),
Els ins 1..9,
M <== matrix( Els, [dim=[9,9]] ),
% select rows
for( I in 0..8 , all_different(M[I,*]) ),
foreach( I in 0..8 , all_different(M[I,*]) ),
% select cols
for( J in 0..8, all_different(M[*,J]) ),
foreach( J in 0..8, all_different(M[*,J]) ),
% select squares
for( [I,J] ins 0..2 ,
foreach( [I,J] ins 0..2 ,
all_different(M[I*3+(0..2),J*3+(0..2)]) ),
ex(Ex, Exs),
maplist( bound, Els, Exs),
@@ -39,12 +39,12 @@ bound(El, X) :-
%
output(Els) :-
M <== matrix( Els, [dim=[9,9]] ),
for( I in 0..2 , output(M, I) ),
foreach( I in 0..2 , output(M, I) ),
output_line.
output(M, I) :-
output_line,
for( J in 0..2 , output_row(M, J+I*3) ).
foreach( J in 0..2 , output_row(M, J+I*3) ).
output_row( M, Row ) :-
L <== M[Row,_],

View File

@@ -71,7 +71,7 @@
:- use_module(library(gecode)).
:- use_module(library(maplist)).
:- reexport(library(matrix), [(<==)/2, for/2, for/4, of/2]).
:- reexport(library(matrix), [(<==)/2, foreach/2, foreach/4, of/2]).
% build array of constraints
%
@@ -326,7 +326,8 @@ check(V, NV) :-
V = '$matrix'(_, _, _, _, C) -> C =.. [_|L], maplist(check, L, NV) ;
V = A+B -> check(A,NA), check(B, NB), NV = NB+NA ;
V = A-B -> check(A,NA), check(B, NB), NV = NB-NA ;
arith(V, _) -> V =.. [C|L], maplist(check, L, NL), NV =.. [C|NL] ).
arith(V, _) -> V =.. [C|L], maplist(check, L, NL), NV =.. [C|NL] ;
constraint(V) -> V =.. [C|L], maplist(check, L, NL), NV =.. [C|NL] ).
post( ( A #= B), Env, Reify) :-
post( rel( A, (#=), B), Env, Reify).
@@ -365,7 +366,8 @@ post( rel( A, Op, B), Space-Map, Reify):-
Space += rel(A, GOP, IB, Reify) ).
% sum([A,B,C]) #= X
post( rel( sum(L), Op, Out), Space-Map, Reify):-
post( rel( C, Op, Out), Space-Map, Reify):-
nonvar(C), C = sum(L),
checklist( var, L ),
( var(Out) -> l(Out, IOut, Map) ; integer(Out) -> IOut = Out ), !,
var(Out), !,
@@ -376,7 +378,8 @@ post( rel( sum(L), Op, Out), Space-Map, Reify):-
Space += linear(IL, GOP, IOut, Reify)
).
% X #= sum([A,B,C])
post( rel( Out, Op, sum(L)), Space-Map, Reify):-
post( rel( Out, Op, C), Space-Map, Reify):-
nonvar(C), C = sum(L),
checklist( var, L ),
( var(Out) -> l(Out, IOut, Map) ; integer(Out) -> IOut = Out ), !,
var(Out), !,
@@ -389,9 +392,10 @@ post( rel( Out, Op, sum(L)), Space-Map, Reify):-
% sum([I in 0..N-1, M[I]]) #= X
post( rel( sum(For, Cond), Op, Out), Space-Map, Reify):-
post( rel( C, Op, Out), Space-Map, Reify):-
nonvar(C), C = sum(Foreach, Cond),
( var(Out) -> l(Out, IOut, Map) ; integer(Out) -> IOut = Out ), !,
cond2list( For, Cond, Cs, L),
cond2list( Foreach, Cond, Cs, L),
maplist(ll(Map), [Out|L], [IOut|IL] ),
gecode_arith_op( Op, GOP ),
(L = [] -> true ;
@@ -399,9 +403,10 @@ post( rel( sum(For, Cond), Op, Out), Space-Map, Reify):-
Space += linear(Cs, IL, GOP, IOut);
Space += linear(Cs, IL, GOP, IOut, Reify)
).
post( rel( Out, Op, sum(For, Cond)), Space-Map, Reify):-
post( rel( Out, Op, C), Space-Map, Reify):-
nonvar(C), C = sum(Foreach, Cond),
( var(Out) -> l(Out, IOut, Map) ; integer(Out) -> IOut = Out ), !,
cond2list( For, Cond, Cs, L),
cond2list( Foreach, Cond, Cs, L),
maplist(ll(Map), [Out|L], [IOut|IL] ),
gecode_arith_op( Op, GOP ),
(L = [] -> true ;
@@ -590,6 +595,7 @@ arith(min(_,_), min).
arith(max(_,_), max).
arith((_ * _), times).
arith((_ / _), div).
arith(sum(_), sum).
% replace abs(min(A,B)-max(A,B)) by
% min(A,B,A1), max(A,B,A2), linear([1,-1],[A1,B1],=,A3), abs(A3,AN)
@@ -867,9 +873,9 @@ get_home(Home) :-
b_getval(gecode_space, Home).
cond2list((List where Goal), El, Cs, Vs) :- !,
for( List, add_el(Goal, El), ([])-([]), Cs-Vs ).
foreach( List, add_el(Goal, El), ([])-([]), Cs-Vs ).
cond2list(List, El, Cs, Vs) :- !,
for( List, add_el(true, El), ([])-([]), Cs-Vs ).
foreach( List, add_el(true, El), ([])-([]), Cs-Vs ).
add_el(G0, El, Cs-Vs, [C|Cs]-[V|Vs]) :-
call(G0), !,

View File

@@ -1031,6 +1031,7 @@ keep_list_(_, X) :-
(Space += element(X1,X2,X3,X4,X5,X6,X7)) :- !, element(Space,X1,X2,X3,X4,X5,X6,X7).
(Space += extensional(X1,X2)) :- !, extensional(Space,X1,X2).
(Space += extensional(X1,X2,X3)) :- !, extensional(Space,X1,X2,X3).
(Space += linear(X1,X2,X3)) :- !, linear(Space,X1,X2,X3).
(Space += linear(X1,X2,X3,X4)) :- !, linear(Space,X1,X2,X3,X4).
(Space += linear(X1,X2,X3,X4,X5)) :- !, linear(Space,X1,X2,X3,X4,X5).
(Space += linear(X1,X2,X3,X4,X5,X6)) :- !, linear(Space,X1,X2,X3,X4,X5,X6).