1:- module(hcycle, []). 2
3:- use_module(zdd('zdd-array')). 4:- use_module(zdd(zdd)). 5:- use_module(pac(op)). 6:- use_module(zdd('frontier-vector')). 7
17
24
25rect_hamilton(Rect, Cs):- rect_links(Rect, Links),
26 use_memo(hamilton(Links, Cs)).
27
28hamilton(Links, Cs):- prepare_udg(Links),
29 get_key(dom, D),
30 length(D, N),
31 udg_path(1-N, Cs0),
32 self_disjoint_merge(Cs0, Cs1),
33 writeln("merge completed"),
34 hamilton_filter(D, Cs1, Cs).
36self_disjoint_merge(X, Y):- zdd_disjoint_merge(X, X, Y).
37
38
42cycles(Links, FCs):- prepare_udg(Links),
43 get_key(dom, D),
44 length(D, N),
45 findall(I-J, (between(1, N, I), I0 is I+1,
46 between(I0, N, J)
47 ),
48 Pairs),
49 maplist(udg_path, Pairs, FPaths),
50 maplist(self_disjoint_merge, FPaths, FMs),
51 zdd_join_list(FMs, FCs).
52
60
61rect_cycles(Rect, FCs):- rect_links(Rect, Links),
62 cycles(Links, FCs)