1:- module(path_count7, [zdd0/1, co_compare/3]).    2
    3:- use_module(library(apply)).    4:- use_module(library(apply_macros)).    5:- use_module(library(clpfd)).    6:- use_module(library(statistics)).    7:- use_module(zdd('zdd-array')).    8:- use_module(util(math)).    9:- use_module(util(meta2).
   10:- use_module(pac(basic)).   11:- use_module(pac(meta)).   12:- use_module(util(misc)).   13:- use_module(pac('expand-pac')). % For the kind block.
   14:- use_module(zdd('zdd-misc')).   15:- use_module(zdd(zdd)).   16:- use_module(zdd('update-link')).   17:- use_module(pac(op)).   18
   19:- set_prolog_flag(stack_limit, 10_200_147_483_648).   20
   21 :- op(1060, xfy, ~).		% equivalence
   22 :- op(1060, xfy, #).		% exor
   23 :- op(1060, xfy, <->).		% equivalence
   24 :- op(1050, yfx, <-).   25 :- op(1060, xfy, <=> ).	% equivalence
   26 :- op(1040, xfy, \/).		% OR
   27 :- op(1030, xfy, /\).		% AND
   28 :- op(1020, fy, \).		% NOT
   29 :- op(700, xfx, :=).		% Assignment
   30 :- op(1000, xfy, &).   31
   32% for pac query.
   33 :- pac:op(1000, xfy, &).   34 :- pac:op(700, xfx, :=).   35
   36term_expansion --> pac:expand_pac.
   37
   38%@ true.
   39% ?- zdd0((true)).
   40% ?- zdd0((X<<pow([a,b]),  psa(X))).
   41
   42% :- meta_predicate zdd0(:).
   43% zdd0(X):- zdd((	set_compare(co_compare), X)).
   44
   45% ?- co_compare(C, c-d, c->d).
   46% ?- co_compare(C, c->d, c->d).
   47% ?- co_compare(C, c->d, c-d).
   48% ?- co_compare(C, c-d, c-d).
   49% ?- predsort(co_compare, [a->b, b->a], R).
   50% ?- predsort(co_compare, [a-b, b-a], R).
   51% ?- predsort(co_compare, [b->a, a->b, a-b, a->b, c-b, a-b, b-a], R).
   52% ?- zdd((set_compare(co_compare), zdd_compare(C, a-b, c-d))).
   53% ?- zdd((set_compare(co_compare), zdd_compare(C, c-d, c->d))).
   54% ?- zdd((set_compare(co_compare), zdd_compare(C, c->d, c-d))).
   55% ?- zdd((set_compare(co_compare), zdd_insert_atoms([a-b, c-d], 1, X))).
   56% ?- zdd((set_compare(co_compare), zdd_insert_atoms([a->b, c-d], 1, X), psa(X))).
   57
   58co_compare(C, X, Y):- compare(C0, X, Y),
   59	(	C0 = (=)  -> C = (=)
   60	;	functor(X, Fx, _),
   61		functor(Y, Fy, _),
   62		(	Fx == Fy
   63		-> 	(	Fx = (-)
   64			->  ( C0 = (<) -> C = (>) ; C = (<) )
   65			;	C = C0
   66			)
   67		;	(	Fx = (-) -> C = (<) ; C = (>) )
   68		)
   69	).
   70
   71% ?- predsort(co_compare, [a->b, b->a, a-b, a->b, c-b, b-a, a-b ], R).
   72% ?- predsort(co_compare, [a->b, b->a], R).
   73
   74% some tiny.
   75% x(p(X, _), X).
   76% y(p(_, Y), Y).
   77% link_symbol(_->_).
   78arrow_symbol( _ -> _).
   79change_symbol(A - B, A -> B).
   80%
   81touch(A - _, _ - A):-!.
   82touch(_ - A, A - _).
   83% ?- connect_pairs(a-b, [b-c, d-a], W).
   84% ?- connect_pairs(a-b, [a-c, a-b], W).  % false
   85connect_pairs(X-Y, [U-X, Y-V], U-V):-!.
   86connect_pairs(X-Y, [Y-V, U-X], U-V).
   87
   88%
   89prune_frontier_by_level(F, K, P, F0):-
   90	@(prune_frontier_by_level(F, K, P, F0)).
   91
   92% For rect only.
   93prune_frontier_by_level(F, _, _, F, _):- F<2, !.
   94prune_frontier_by_level(F, K, P, F0, S):- s_cofact(F, t(A, L, R), S),
   95	prune_frontier_by_level(L, K, P, L0, S),
   96	(	arrow_symbol(A)
   97	->	U = R
   98	;	(	(	A = (X-X)
   99			;	A = P - p(K,_)
  100			; 	A = p(K, _)-p(K, _)
  101			)
  102		->	prune_frontier_by_level(R, K, P, U, S)
  103		;	U = 0
  104		)
  105	),
  106	s_zdd_insert(A, U, R0, S),
  107	s_zdd_join(L0, R0, F0, S).
  108
  109card_path(X, ST, Y):- @(card_path(X, ST, Y)).
  110%
  111
  112card_path(X, ST, Y, S):- open_state(M, [hash_size(128)]),
  113	card_path(X, ST, Y, S, M),
  114	close_state(M).
  115
  116%
  117card_path(I, _, 0, _, _):- I < 2, !.
  118card_path(I, ST, C, S, M):- memo(I-C, M),
  119	(	nonvar(C) -> true
  120	;	cofact(I, t(A, L, R), S),
  121		card_path(L, ST, Cl, S, M),
  122		(	A = X-Y
  123		->	(	X = Y	-> card_path(R, ST, Cr, S, M)
  124			;  	A = ST	-> card_path1(R, Cr, S, M)
  125			;	Cr = 0
  126			)
  127		;  Cr = 0
  128		),
  129		C is Cr + Cl
  130	).
  131
  132card_path1(I, I, _, _):- I<2, !.
  133card_path1(I, C, S, M):- memo(I-C, M),
  134	(	nonvar(C) -> true
  135	;	cofact(I, t(A, L, R), S),
  136		card_path1(L, Cl, S, M),
  137		(  	A = X-Y
  138		->  (	X = Y ->  card_path1(R, Cr, S, M)
  139			;	Cr = 0
  140			)
  141		;	card(R, Cr, S, M)
  142		),
  143		C is Cr + Cl
  144	).
  145
  146% ?- bridge_shift(h, [p(1,1)-p(1,1)], X).
  147% ?- bridge_shift(v, [p(1,1)-p(1,1)], X).
  148
  149bridge_shift(F, X, Y):- maplist(shift_link(F), X, Y).
  150
  151% ?- zdd((convert_to_col([[1-2], [3-4]], Col, 0),
  152%	map_h_shift(Col, Col0))).
  153map_h_shift(X, Y):- @(map_h_shift(X, Y)).
  154%
  155map_h_shift([], [], _).
  156map_h_shift([X|Y], [X0|Y0], S):- h_shift(X, X0, S),
  157	map_h_shift(Y, Y0, S).
  158
  159% ?- zdd((convert_to_row([[1-2], [3-4]], Row, 0),
  160%	map_v_shift(Row, Row0))).
  161map_v_shift(X, Y):- @(map_v_shift(X, Y)).
  162%
  163map_v_shift([], [], _).
  164map_v_shift([X|Y], [X0|Y0], S):- v_shift(X, X0, S),
  165	map_v_shift(Y, Y0, S).
  166
  167%
  168h_shift(X, Y):- @(h_shift(X, Y)).
  169%
  170h_shift(X, X, _):- X < 2, !.
  171h_shift(X, Y, S):- cofact(X, t(p(I, J)-p(I, K), L, R), S),
  172	I0 is I + 1,
  173	h_shift(L, L0, S),
  174	h_shift(R, R0, S),
  175	cofact(Y, t(p(I0, J)-p(I0, K), L0, R0), S).
  176
  177v_shift(X, Y):- @(v_shift(X, Y)).
  178%
  179v_shift(X, X, _):- X < 2, !.
  180v_shift(X, Y, S):- cofact(X, t(p(I, J)-p(K, J), L, R), S),
  181	v_shift(L, L0, S),
  182	v_shift(R, R0, S),
  183	J0 is J + 1,
  184	cofact(Y, t(p(I, J0)-p(K, J0), L0, R0), S).
  185
  186% ?- gogo.
  187% ?- zdd0((solve_rect(rect(1,1), Z, C))).
  188% ?- zdd0((solve_rect(rect(2,2), Z, C))).
  189%@ C = 12 .
  190% ?- time(zdd0((solve_rect(rect(3,3), Z, C)))).
  191%@ % 37,629,160 inferences, 5.016 CPU in 5.895
  192%@ Z = 455351,
  193%@ C = 184 .
  194%@ % 37,629,160 inferences, 3.744 CPU in 3.945 seconds (95% CPU, 10049933 Lips)
  195%@ Z = 455351,
  196%@ C = 184 .
  197% ?- time(zdd0((solve_rect(rect(4,4), Z, C)))).
  198%@ % 15,026,838,147 inferences, 2173.210 CPU in 14110.223
  199%@ Z = 154551488,
  200%@ C = 8512 .
  201%@ % 6,527,546,920 inferences, 915.198 CPU in 956.075
  202%@ Z = 70016262,
  203%@ C = 7888 .
  204%@ path-count7.pl qcompiled.
  205
  206% ?- zdd0((solve_rect(rect(0,0), Z, C))).
  207% ?- zdd0((solve_rect(rect(0,1), Z, C))).
  208% ?- zdd0((solve_rect(rect(0,2), Z, C))).
  209% ?- zdd0((solve_rect(rect(0,3), Z, C))).
  210% ?- zdd0((solve_rect(rect(0,15), Z, C))).
  211% ?- zdd0((solve_rect(rect(1, 0), Z, C))).
  212% ?- zdd0((solve_rect(rect(2, 0), Z, C))).
  213% ?- zdd0((solve_rect(rect(3, 0), Z, C))).
  214% ?- zdd0((solve_rect(rect(10, 0), Z, C))).
  215% ?- zdd0((solve_rect(rect(15, 0), Z, C))).
  216% ?- zdd0((solve_rect(rect(20, 0), Z, C))).
  217
  218% ?- zdd0((solve_rect(rect(1,1), Z, C))).
  219% ?- zdd0((solve_rect(rect(2,1), Z, C))).
  220%@ C = 4 .
  221% ?- zdd0((solve_rect(rect(3,1), Z, C))).
  222% ?- zdd0((solve_rect(rect(4,1), Z, C))).
  223% ?- zdd0((solve_rect(rect(5,1), Z, C))).
  224% ?- zdd0((solve_rect(rect(10,1), Z, C))).
  225% ?- zdd0((solve_rect(rect(16,1), Z, C))).
  226% ?- zdd0((solve_rect(rect(20,1), Z, C))).
  227%@ Z = 116399365,
  228%@ C = 1048576 .
  229
  230% ?- zdd0((solve_rect(rect(3,3), Z, C))).
  231%@ Z = 802789,
  232%@ C = 184 .
  233%@ Z = 726823,
  234%@ C = 184 .
  235
  236% ?- time(zdd0((solve_rect(rect(4,4), Z, C)))).
  237%@ % 15,026,838,146 inferences, 2128.657 CPU in 2589.153
  238%@ Z = 154551488,
  239%@ C = 8512 .
  240%@ % 13,320,352,776 inferences, 1920.237 CPU in 2125.245
  241%@ Z = 146748055,
  242%@ C = 8512 .
  243
  244% ?- time(zdd0((solve_rect(rect(5,5), Z, C)))).
  245
  246% ?- zdd((X<<{[c,b,a]}, Y<<{[],[c],[b,c],[a,b,c]}, zdd_merge(X, Y, Z), psa(Z))).
  247
  248% gogogogo
  249% ?- zdd0((solve_rect(rect(1, 1), Z, C))).
  250%@ Z = 184,
  251%@ C = 2 .
  252% ?- zdd0((solve_rect(rect(1, 2), Z, C))).
  253%@ Z = 1886,
  254%@ C = 4 .
  255% ?- zdd0((solve_rect(rect(1, 3), Z, C))).
  256%@ Z = 16497,
  257%@ C = 8 .
  258% ?- zdd0((solve_rect(rect(1, 4), Z, C))).
  259%@ Z = 138089,
  260%@ C = 16 .
  261% ?- zdd0((solve_rect(rect(1, 5), Z, C))).
  262%@ Z = 1152578,
  263%@ C = 32 .
  264% ?- zdd0((solve_rect(rect(1, 6), Z, C))).
  265%@ Z = 12510705,
  266%@ C = 64 .
  267%@ Z = 12447245,
  268%@ C = 64 .
  269%@ Z = 9695864,
  270%@ C = 64 .
  271
  272% ?- call_with_time_limit(600, zdd0((solve_rect(rect(2,2), Z, C)))).
  273%@ Z = 10622,
  274%@ C = 12.
  275%@ Z = 7273,
  276%@ C = 12.
  277
  278% ?- call_with_time_limit(600, zdd0((solve_rect(rect(3,3), Z, C)))).
  279% ?- call_with_time_limit(3600, zdd0((solve_rect(rect(4,4), Z, C)))).
  280% ?- call_with_time_limit(5400, zdd0((solve_rect(rect(5,5), Z, C)))).
  281
  282solve_rect(R, C):- solve_rect(R, _, C).
  283solve_rect(rect(W, H), Z, C):- solve_rect(p(0,0), p(W, H), Z, C).
  284%
  285solve_rect(X, Y, Z, C):- @(solve_rect(X, Y, Z, C)).
  286%
  287solve_rect(p(I, J), p(I, L), Z, 1, S):-!, initial_column(I, J, L, Z, S).
  288solve_rect(p(I, J), p(K, L), Z, C, S):-
  289	initial_col_bridge(I, J, L, Col, B0, S),
  290	reverse(B0, B),
  291	N is (K-I),
  292	repeat_bridge(N, Col, I, p(I,J), Col, B, Z, S),
  293	card_path(Z, p(I,J)-p(K, L), C, S).
  294
  295% ?- dg_path_count_naive(dg([a,b],[a-b]), a-b, C).
  296% ?- dg_path_count_naive(dg([a,b],[b-a]), a-b, C).
  297% ?- dg_path_count_naive(dg([a, b, c],[a-b, b-c]), a-c, C).
  298% ?- dg_path_count_naive(dg([a, b, c],[a-b, b-c, a-c]), a-c, C).
  299% ?- dg_path_count_naive(dg([a, b, c, d],[a-b, a-c, b-a, b-d, c-a, c-d, d-c, d-b]), a-d, C).
  300% ?- dg_path_count_naive(dg([a, b, c, d],[b-c, c-b, a-b, a-d, a-c, b-a, b-d, c-a, c-d, d-c, d-b, d-a]), a-d, C).
  301%@ C = 5 .
  302
  303% ?- rect_dg(rect(1,1), X, Y), dg_path_count_naive(dg(X, Y), p(0,0)-p(1,1), C).
  304% ?- rect_dg(rect(2,2), X, Y), dg_path_count_naive(dg(X, Y), p(0,0)-p(2,2), C).
  305%@ C = 12 .
  306% ?- rect_dg(rect(1,2), X, Y), dg_path_count_naive(dg(X, Y), p(0,0)-p(1,2), C).
  307% ?- rect_dg(rect(1,3), X, Y), dg_path_count_naive(dg(X, Y), p(0,0)-p(1,3), C).
  308% ?- rect_dg(rect(1,5), X, Y), dg_path_count_naive(dg(X, Y), p(0,0)-p(1,5), C).
  309% ?- call_with_time_limit(100, (rect_dg(rect(3,3), X, Y), dg_path_count_naive(dg(X, Y), p(0,0)-p(3,3), C))).  % timeout.
  310
  311
  312% ?- rect_dg(rect(1,2), X, Y), dg_path_naive(dg(X, Y)).
  313% ?- rect_path_count_naive(rect(1,2), C).
  314% ?- rect_path_count_naive(rect(1,3), C).
  315% ?- rect_path_count_naive(rect(3,1), C).
  316% ?- rect_path_count_naive(rect(2,2), C).
  317% ?- rect_path_count_naive(rect(2,3), C).
  318% ?- rect_path_count_naive(rect(3,2), C).
  319% ?- rect_path_count_naive(rect(3,3), C).
  320
  321
  322rect_path_count_naive(rect(W, H), C):-
  323	rect_dg(rect(W, H), X, Y),
  324	dg_path_count_naive(dg(X, Y), p(0,0)-p(W, H), C).
  325
  326dg_path_count_naive(G, ST, C):- dg_path_count_naive(G, ST, _, C).
  327
  328dg_path_count_naive(dg(Ns, Es), ST, Fin, C):- zdd0(
  329	(
  330		zdd_sort(Es, E0s),
  331		findall(X-X, member(X, Ns), X_Xs),
  332		zdd_insert_atoms(X_Xs, 1, Initial),
  333		update_links(E0s, Initial, Fin),
  334		card_path(Fin, ST, C)
  335	)).
  336
  337% ?- dg_path_naive(dg([a, b, c, d],[a-b, a-c, b-a, b-d, c-a, c-d, d-c, d-b])).
  338dg_path_naive(dg(Ns, Es)):- zdd0(
  339	(	zdd_sort(Es, E0s),
  340		findall(X-X, member(X, Ns), Id),
  341		zdd_insert_atoms(Id, 1, Initial),
  342		update_links(E0s, Initial, Fin),
  343		psa(Fin)
  344	)).
  345
  346% ?- zdd0(zdd_sort([a, b, c], X)).
  347% ?- zdd0((solve_rect(rect(1, 1), Z, C))).
  348% ?- zdd0((solve_rect(rect(1, 2), Z, C))).
  349% ?- zdd0((solve_rect(rect(2, 1), Z, C))).
  350% ?- zdd0((solve_rect(rect(3, 1), Z, C))).
  351% ?- zdd0((solve_rect(rect(8, 1), Z, C))).
  352% ?- zdd0((solve_rect(rect(16, 1), Z, C))).
  353% ?- zdd0((solve_rect(rect(1, 2), Z, C))).
  354% ?- zdd0((solve_rect(rect(1, 3), Z, C))).
  355% ?- listing(s_zdd_insert).
  356% ?- listing(zdd_insert).
  357
  358
  359% ?- zdd0((solve_rect(rect(2, 2), Z, C))).
  360% ?- time(zdd0((solve_rect(rect(3, 3), Z, C)))).  % links_across.
  361%@ % 81,838,566 inferences, 10.673 CPU in 12.942 seconds (82% CPU, 7668071 Lips)
  362%@ Z = 726823,
  363%@ C = 184 .
  364
  365% ?- time(zdd0((solve_rect(rect(3, 3), Z, C)))).   % glue_frontiers.
  366%%@ % 114,953,539 inferences, 13.781 CPU in 16.134 seconds (85% CPU, 8341355 Lips)
  367%@ Z = 802789,
  368%@ C = 184
  369
  370% ?- time(zdd0((solve_rect(rect(4, 4), Z, C)))).
  371% ?- zdd0((solve_rect(rect(1, 2), Z, C))).
  372repeat_bridge(0, X, _, _, _, _, X, _):-!, writeln(bridge(0)).
  373repeat_bridge(N, X, K, P, C, B, Y, S):- writeln(bridge(N)),
  374	mqp_shift(h, C, C0, S),
  375	links_across(B, X, C0, X0, S),
  376%	glue_frontiers(B, X, C0, X0, S),
  377	maplist(shift_link(h), B, B0),
  378	K0 is K + 1,
  379	N0 is N - 1,
  380	prune_frontier_by_level(X0, K0, P, X1, S),
  381	repeat_bridge(N0, X1, K0, P, C0, B0, Y, S).
  382
  383% ?- time(zdd0((initial_col_bridge(0, 0, 15, C, B)))).
  384% ?- time(zdd0((initial_col_bridge(0, 0, 2, C, B), psa(C)))).
  385
  386initial_col_bridge(I, L, H, C, B):-	@(initial_col_bridge(I, L, H, C, B)).
  387%
  388initial_col_bridge(I, L, H, C, B, S):- initial_column(I, L, H, C, S),
  389	initial_bridge(I, L, H, B).
  390
  391% ?- zdd0((initial_column(1, 2, 4, Col), s_psa(Col))).
  392% ?- zdd0((initial_column(1, 0, 10, Col), card(Col, C))).
  393% ?- zdd0((initial_column(1, 0, 3, Col), card(Col, C))).  % seems good.
  394% ?- zdd0((initial_column(1, 0, 3, Col),
  395%	mqp_shift(h, Col, Col1),
  396%	mqp_shift(v, Col1, Col2),
  397%	card(Col, C),
  398%	card(Col1, C1),
  399%	card(Col2, C2))).
  400% ?- zdd0((initial_col_bridge(0, 0, 3, Col, B), card(Col, C))).
  401% ?- zdd0((initial_col_bridge(0, 0, 4, Col, B), card(Col, C))).
  402% ?- zdd0((initial_col_bridge(0, 0, 5, Col, B), card(Col, C))).
  403% ?- zdd0((initial_col_bridge(0, 0, 15, Col, B), card(Col, C))).
  404% ?- zdd0((initial_col_bridge(0, 0, 2, Col, B), card(Col, C))).
  405% ?- zdd0((initial_col_bridge(0, 0, 15, Col, B), card(Col, C))).
  406% ?- zdd0((initial_col_bridge(0, 0, 20, Col, B), card(Col, C))).
  407% ?- zdd0((initial_col_bridge(0, 0, 10, C, B), card(C, Count))), length(B, Len).
  408
  409initial_column(I, Low, Hi, Col):- @(initial_column(I, Low, Hi, Col)).
  410%
  411initial_column(I, Low, Hi, Col, S):-
  412	itr_linear_grid(Low, Hi, X, S),
  413	mqp_lift(x(I), X, Col, S).
  414
  415% initial_column(I, Low, Hi, Col, S):-
  416% 	s_mqp_linear_grid(Low, Hi, X, S),
  417% 	mqp_lift(x(I), X, Col, S).
  418
  419
  420% ?- initial_bridge(0, 1, 4, Bridge), maplist(writeln, Bridge).
  421initial_bridge(I, Low, Hi, Bridge):- J is I + 1,
  422	findall(A,
  423			(	member(A, [p(I, V)-p(J, V), p(J, V)-p(I, V)]),
  424				between(Low, Hi, V)
  425			),
  426			Bridge0),
  427	sort(Bridge0, Bridge).
  428
  429
  430% ?- spy(mqp_linear_grid).
  431% ?- I = 0, zdd0((mqp_linear_grid(0,I,X), psa(X))).
  432% ?- I = 1, zdd0((mqp_linear_grid(0,I,X), psa(X))).
  433% ?- I = 2, zdd0((mqp_linear_grid(0,I,X), psa(X))).
  434% ?- I = 3, zdd0((mqp_linear_grid(0,I,X), psa(X))).
  435% Checked by hand.
  436
  437% ?- forall(between(0, 20, I), zdd0((mqp_linear_grid(0,I,X), card(X, C), format("count(~w) = ~w\n", [I, C])))).
  438
  439% ?- zdd0((mqp_linear_grid(0,1,X))).
  440% ?- zdd0((mqp_linear_grid(0,2,X))).
  441% ?- zdd0((mqp_linear_grid(0,3,X), card(X, C))).
  442% ?- zdd0((mqp_linear_grid(0,4,X), card(X, C))).
  443
  444% ?- zdd0((initial_col_bridge(0, 0, 20, C, B), card(C, Count))), length(B, Len).
  445%@ C = 295985945,
  446%@ Count = 54608393,
  447%@ Len = 42.
  448
  449
  450% ?- zdd0((initial_col_bridge(0, 0, 20, C, B), card(C, Count))), length(B, Len).
  451%@ C = 26385389,
  452%@ Count = 4479227,
  453%@ Len = 42 .
  454
  455% ?- zdd0((initial_col_bridge(0, 0, 4, C, B), card(C, Count))), length(B, Len).
  456
  457		/*********************************************************
  458		*     mqp_linear_grid is better than itr_linear_grid.    *
  459		*********************************************************/
  460
  461
  462
  463% ?- time(zdd0((mqp_linear_grid(0,15,X), card(X, C)))).
  464%@ % 204,734,142 inferences, 17.969 CPU in 18.20
  465%@ X = 1837608,
  466%@ C = 665857 .
  467% ?- time(zdd0((mqp_linear_grid(0,16,X), card(X, C)))).
  468%@ % 567,780,697 inferences, 112.569 CPU in 158.862
  469%@ X = 4391322,
  470%@ C = 1607521
  471% ?- time(zdd0((mqp_linear_grid(0,16,X), card(X, C)))).
  472%@ % 567,780,697 inferences, 161.364 CPU in 327.436
  473%@ X = 4391322,
  474%@ C = 1607521 .
  475% ?- time(zdd0((mqp_linear_grid(0,16,X), card(X, C)))).
  476%@ % 567,780,697 inferences, 94.204 CPU in 135.880
  477%@ X = 4391322,
  478%@ C = 1607521 .
  479% ?- time(zdd0((mqp_linear_grid(0,18,X), card(X, C)))).
  480%@ % 2,946,152,712 inferences, 388.382 CPU in 402.191
  481%@ X = 25469487,
  482%@ C = 9369319
  483
  484% ?- time(zdd0((itr_linear_grid(0,15,X), card(X, C)))).
  485%@ % 211,111,055 inferences, 20.500 CPU in 21.370
  486%@ X = 1802950,
  487%@ C = 665857 .
  488% ?- time(zdd0((itr_linear_grid(0,16,X), card(X, C)))).
  489%@ % 586,094,784 inferences, 68.215 CPU in 87.623 seconds (78% CPU, 8591868 Lips)
  490%@ X = 4352186,
  491%@ C = 1607521 .
  492% ?- time(zdd0((itr_linear_grid(0,18,X), card(X, C)))).
  493%@ % 3,062,986,110 inferences, 378.321 CPU in 403.198
  494%@ X = 25364313,
  495%@ C = 9369319 .
  496
  497% simple line quasi path
  498mqp_linear_grid(X, Y, Z):-
  499	@(mqp_linear_grid(X, Y, Z)).
  500
  501mqp_linear_grid(E, X, Y, S):-atmark(S),!,
  502	s_mqp_linear_grid(E, X, Y, S).
  503mqp_linear_grid(E, X, Y, S):-
  504	open_state(M, [hash_size(128)]),
  505	s_mqp_linear_grid(E, X, Y, @(S, M)),
  506	close_state(M).
  507%
  508s_mqp_linear_grid(I, I, P, S):-!,
  509	s_zdd_singleton(I-I, P, S).
  510s_mqp_linear_grid(I, J, Q, S):-
  511	M is (I+J)//2,
  512	M0 is M+1,
  513	s_mqp_linear_grid(I, M, R, S),
  514	s_mqp_linear_grid(M0, J, R0, S),
  515%	s_zdd_merge(R, R0, U, S),
  516%	update_links([M-M0, M0-M], U, Q, S).
  517	links_across([M-M0, M0-M], R, R0, 0, Q0, S),
  518	s_zdd_merge(R, R0, U, S),
  519	s_zdd_join(U, Q0, Q, S).
  520
  521		/*******************************
  522		*     iterative linear grid    *
  523		*******************************/
  524% ?- spy(update_links).
  525% ?- spy(zdd0).
  526% ?- zdd0((itr_linear_grid(0, 0, Z), psa(Z))).
  527% ?- zdd0((itr_linear_grid(0, 1, Z), psa(Z))).
  528% ?- zdd0((itr_linear_grid(0, 2, Z), psa(Z))).
  529% ?- zdd0((itr_linear_grid(0, 3, Z), card(Z, C))).
  530% ?- zdd0((itr_linear_grid(0, 15, Z), card(Z, C))).
  531%@ Z = 3823906,
  532%@ C = 665857
  533% ?- zdd0((itr_linear_grid(0, 5, Z), mqp_linear_grid(0,5,X))).
  534%@ Z = X, X = 312 .
  535%@ Z = X, X = 582 .
  536% ?- zdd0((itr_linear_grid(0, 15, Z), mqp_linear_grid(0,15,X))).
  537%@ Z = X, X = 1802905 .
  538%@ Z = X, X = 3823862 .
  539%@ Z = X, X = 3823906 .
  540
  541itr_linear_grid(X, Y, Z):- @(itr_linear_grid(X, Y, Z)).
  542
  543itr_linear_grid(X, Y, Z, S):- atmark(S), !,
  544	s_itr_linear_grid(X, Y, Z, S).
  545itr_linear_grid(X, Y, Z, S):-
  546	open_state(M, [hash_size(128)]),
  547	s_itr_linear_grid(X, Y, Z, @(S, M)),
  548	close_state(M).
  549
  550% Best linear grid.
  551s_itr_linear_grid(I, I, P, S):-!, s_zdd_singleton(I-I, P, S).
  552s_itr_linear_grid(I, J, P, S):-J0 is J-1,
  553	s_itr_linear_grid(I, J0, Q, S),
  554	s_zdd_singleton(J-J, R, S),
  555	s_zdd_insert(J-J, Q, Q0, S),  %	equivalently, s_zdd_merge(R, Q, Q0, S),
  556	links_across([J0-J, J-J0], Q, R, Q0, P, S).
  557
  558% %
  559% s_itr_linear_grid(I, I, P, S):-!, s_zdd_singleton(I-I, P, S).
  560% s_itr_linear_grid(I, J, P, S):-J0 is J-1,
  561% 	s_itr_linear_grid(I, J0, Q, S),
  562% 	s_zdd_singleton(J-J, U, S),
  563% 	links_across([J0-J, J-J0], Q, U, P, S).
  564
  565% s_itr_linear_grid(I, I, P, S):-!, s_zdd_singleton(I-I, P, S).
  566% s_itr_linear_grid(I, J, P, S):-J0 is J-1,
  567% 	s_itr_linear_grid(I, J0, Q, S),
  568% 	s_zdd_insert(J-J, Q, Q0, S),
  569% 	links_across([J0-J, J-J0], Q0, P, S).
  570
  571
  572% works best
  573% s_itr_linear_grid(I, I, P, S):-!, s_zdd_singleton(I-I, P, S).
  574% s_itr_linear_grid(I, J, P, S):-J0 is J-1,
  575% 	s_itr_linear_grid(I, J0, Q, S),
  576% 	s_zdd_singleton(J-J, R, S),
  577% 	links_across([J0-J, J-J0], Q, R, 0, P, S).
  578
  579% woks!
  580% s_itr_linear_grid(I, I, P, S):-!, s_zdd_singleton(I-I, P, S).
  581% s_itr_linear_grid(I, J, P, S):-J0 is J-1,
  582% 	s_itr_linear_grid(I, J0, Q, S),
  583% 	s_zdd_singleton(J-J, R, S),
  584% 	s_zdd_merge(R, Q, U, S),
  585% 	links_across([J0-J, J-J0], Q, R, U, P, S).
  586
  587
  588		/********************************
  589		*     lift/shift  quasi path    *
  590		********************************/
  591
  592% ?- I = 3, zdd0((mqp_linear_grid(0,I,X), card(X, D),  mqp_lift(y(0), X, Y), card(Y, C))).
  593%
  594mqp_lift(F, X, Y):- @(mqp_lift(F, X, Y)).
  595%
  596mqp_lift(F, X, Y, S):-open_state(M, [hash_size(128)]),
  597	mqp_lift(F, X, Y, S, M),
  598	close_state(M).
  599%
  600mqp_lift(_, X, X, _, _):- X<2, !.
  601mqp_lift(F, X, Y, S, M):- memo(mqp_lift(X)-Y, M),  % F dropped.
  602	(	nonvar(Y)-> true
  603	;	s_cofact(X, t(A, L, R), S),
  604		mqp_lift(F, L, L0, S, M),
  605		mqp_lift(F, R, R0, S, M),
  606		lift_link(F, A, B),
  607		s_cofact(Y, t(B, L0, R0), S)
  608	).
  609
  610% ?- I = 3, zdd0((mqp_linear_grid(0,I,X), mqp_lift(y(0), X, Y), card(Y, C))).
  611% ?- I = 3, zdd0((mqp_linear_grid(0,I,X), mqp_lift(y(0), X, Y), card(Y, C),
  612%	mqp_shift(v, Y, Z), psa(Z), card(Z, D))).
  613% ?- I = 3, zdd0((mqp_linear_grid(0,I,X), mqp_lift(y(0), X, Y),
  614%	mqp_shift(v, Y, Z), mqp_shift(v, Z, U), psa(U), card(U, C))).
  615% ?- I = 3, zdd0((mqp_linear_grid(0,I,X), mqp_lift(x(0), X, Y),
  616%	mqp_shift(h, Y, Z), mqp_shift(h, Z, U), psa(U), card(U, C))).
  617%
  618mqp_shift(F, X, Y):- @(mqp_shift(F, X, Y)).
  619%
  620mqp_shift(F, X, Y, S):-
  621	open_state(M, [hash_size(128)]),
  622	mqp_shift(F, X, Y, S, M),
  623	close_state(M).
  624
  625%
  626mqp_shift(_, X, X, _, _):- X < 2, !.
  627mqp_shift(F, X, Y, S, M):- memo(mqp_shift(X)-Y, M),  % F dropped.
  628	(	nonvar(Y)-> true
  629	;	s_cofact(X, t(A, L, R), S),
  630		mqp_shift(F, L, L0, S, M),
  631		mqp_shift(F, R, R0, S, M),
  632		shift_link(F, A, B),
  633		s_cofact(Y, t(B, L0, R0), S)
  634	).
  635
  636% ?- lift_point(3, x(2), R).
  637% ?- lift_point(3, y(2), R).
  638%
  639lift_point(J, x(I), p(I, J)):-!.
  640lift_point(J, y(I), p(J, I)).
  641
  642% ?- lift_link(x(2), 4-5, R).
  643lift_link(Ctr, A-B, P-Q):-!, lift_point(A, Ctr, P),
  644	lift_point(B, Ctr, Q).
  645% ?- lift_link(x(2), 4->5, R).
  646lift_link(Ctr, A->B, P->Q):- lift_point(A, Ctr, P),
  647	lift_point(B, Ctr, Q).
  648%
  649shift_link(h, A, B):-!, h_shift_link(A, B).
  650shift_link(v, A, B):- v_shift_link(A, B).
  651
  652% ?- h_shift_point(p(1,1), R).
  653% ?- h_shift_point(-1, p(1,1), R).
  654h_shift_point(p(I, J), p(I0, J)):- I0 is I + 1.
  655h_shift_point(K, p(I, J), p(I0, J)):- I0 is I + K.
  656%
  657v_shift_point(p(I, J), p(I, J0)):- J0 is J + 1.
  658v_shift_point(K, p(I, J), p(I, J0)):- J0 is J + K.
  659
  660%
  661h_shift_link(P-Q, P0-Q0):-!, h_shift_point(P, P0),
  662	h_shift_point(Q, Q0).
  663h_shift_link(P->Q, P0->Q0):- h_shift_point(P, P0),
  664	h_shift_point(Q, Q0).
  665%
  666v_shift_link(P-Q, P0-Q0):-!, v_shift_point(P, P0),
  667	v_shift_point(Q, Q0).
  668v_shift_link(P->Q, P0->Q0):- v_shift_point(P, P0),
  669	v_shift_point(Q, Q0).
?- zdd(( qp_list(X, [a-a]), qp_list(Y, [b-b]), qp_joint([a-b, b-a], [X], [Y], Z), maplist(pred(([U]:-qp_list(U, List), writeln(List))), Z))). ?- zdd(( qp_list(X, [a-a]), qp_list(Y, [b-b]), qp_joint([a-b, b-a], [X], [Y], Z), zdd_join(X, Y, A), memo(qp_suc(A)-L), writeln(qp_suc(A)-L), maplist(pred(([U]:-qp_list(U, List), writeln(List))), Z))). ?- zdd(( qp_list(X, [a-a]), qp_list(Y, [b-b]), qp_joint([a-b, b-a], [X], [Y], Z), zdd_join(X, Y, A), memo(qp_suc(A)-L), writeln(qp_suc(A)-L), maplist(pred(([U]:-qp_list(U, List), writeln(List))), Z))).
  689% ?- rect_dg(rect(0,1), X, Y).
  690% ?- rect_dg(rect(0,0), X, Y).
  691% ?- rect_dg(rect(1,1), X, Y).
  692
  693rect_dg(rect(W, H), Nodes, Links):-
  694	rect_nodes(W, H, Nodes),
  695	rect_links(W, H, Nodes, Links).
  696
  697% ?- rect_nodes(4,5,Ns), length(Ns, L).
  698rect_nodes(W, H, Nodes):-
  699	findall(p(I, J),
  700			(	between(0, W, I),
  701				between(0, H, J)
  702			),
  703			Nodes0),
  704	sort(Nodes0, Nodes).
  705
  706%
  707rect_links(W, H, Ns, Links):-
  708	findall(P-Q,
  709			(	member(P, Ns),
  710				P = p(I, J),
  711				(	Q = p(I, J1),
  712					(	J1 is J-1,
  713						J1 >= 0
  714					;	J1 is J+1,
  715						J1 =< H
  716					)
  717				;   Q = p(I1, J),
  718					(	I1 is I-1,
  719						I1 >= 0
  720					;	I1 is I+1,
  721						I1 =< W
  722					)
  723				)
  724			),
  725			Links0),
  726	sort(Links0, Links)