Efficient solution for the same-fringe problem for binary trees
Asked Answered
S

7

5

The fringe of a binary tree is the sequence composed by its leaves, from left to right. The same-fringe problem [Hewitt & Patterson, 1970] consists of determining whether two binary trees have the same fringe. For example, the first two trees below have the same fringe, but the last two do not:

%         .         .         .
%        / \       / \       / \
%       .   3     1   .     1   .
%      / \           / \       / \
%     1   2         2   3    -2   3

example(1, fork(fork(leaf(1), leaf(2)), leaf(3))).
example(2, fork(leaf(1), fork(leaf(2), leaf(3)))).
example(3, fork(leaf(1), fork(leaf(-2), leaf(3)))).

A simple solution is to collect the leaves of one tree into a list and then compare them with the leaves of the other tree.

/*
 * SIMPLE SOLUTION
 */

sf_1(T1, T2) :-
    walk(T1, [], Xs),
    walk(T2, [], Xs).

walk(leaf(X), A, [X|A]).
walk(fork(L, R), A0, Xs) :-
    walk(R, A0, A1),
    walk(L, A1, Xs).

Although simple, this solution is considered inelegant: first, because it can be impractical when the first tree is very large; and, second, because it is very inefficient when the trees differ in the first few leaves. Thus, a better solution would be to stop the comparison as soon as the first difference is found, without completely generating the list containing the fringe of the first tree.

/*
 * SUPPOSEDLY BETTER SOLUTION
 */

sf_2(T1, T2) :-
    step([T1], [T2]).

step([], []).
step([T1|S1], [T2|S2]) :-
    next(T1, S1, X, R1),
    next(T2, S2, X, R2),
    step(R1, R2).

next(leaf(X), S, X, S).
next(fork(L, R), S0, X, S) :-
    next(L, [R|S0], X, S).

To compare the performance of these two solutions, I implemented some predicates to run automated experiments (by using SWI-prolog, version 9.0.4):

/*
 * EMPIRICAL COMPARISON
 */

comp(Case) :-
    format('fsize sf-1 sf-2\n'),
    forall( between(1, 10, I),
            (   N is 100000 * I,
                tree(1, N, A),
                (   Case = true         % trees with same fringes
                ->  tree(1, N, B)
                ;   M is random(N//10), % trees with different fringes
                    flip(A, M, B) ),
                time(10, sf_1(A, B), T1),
                time(10, sf_2(A, B), T2),
                format('~0e ~2f ~2f\n', [N, T1, T2]) ) ).

time(N, G, T) :-
    garbage_collect,
    S is cputime,
    forall(between(1, N, _), ignore(call(G))),
    T is (cputime - S) / N.

/*
 * RANDOM TREE GENERATION AND MODIFICATION
 */

tree(X1, Xn, leaf(X1)) :-
    X1 = Xn,
    !.
tree(X1, Xn, fork(L, R)) :-
    X1 < Xn,
    random(X1, Xn, Xi),
    Xj is Xi + 1,
    tree(X1, Xi, L),
    tree(Xj, Xn, R).


flip(leaf(X), Y, leaf(Z)) :-
    (  X = Y
    -> Z is -X
    ;  Z is  X ).
flip(fork(L0, R0), X, fork(L, R)) :-
    flip(L0, X, L),
    flip(R0, X, R).

The empirical results show that the second solution is, in fact, faster than the first when the trees do not have the same fringes:

?- comp(false).
fsize sf-1 sf-2
1e+05 0.01 0.00
2e+05 0.03 0.00
3e+05 0.05 0.00
4e+05 0.07 0.01
5e+05 0.09 0.01
6e+05 0.11 0.00
7e+05 0.12 0.01
8e+05 0.14 0.01
9e+05 0.17 0.00
1e+06 0.18 0.00
true.

However, when the trees do have the same fringe, the second solution is a little slower than the first:

?- comp(true).
fsize sf-1 sf-2
1e+05 0.02 0.03
2e+05 0.04 0.05
3e+05 0.06 0.08
4e+05 0.08 0.11
5e+05 0.10 0.12
6e+05 0.12 0.14
7e+05 0.12 0.16
8e+05 0.14 0.18
9e+05 0.17 0.19
1e+06 0.18 0.22
true.

QUESTION: Is it possible to implement a solution (in Prolog) that is faster than the simple solution (by a constant factor, not necessarily asymptotically faster) when the fringes are distinct, yet is not slower when the fringes are the same? In other words, can we achieve the efficient comparison without the overhead? If so, how?

Sefton answered 15/6, 2024 at 15:38 Comment(23)
If you shift work to the tree modification functions, you could keep a signed count 'unmatchedcount' say, of leaves on tree1 and not on tree2 minus on tree2 and not on tree1 respectively, then you could know in O(1) time if they matched or not.Septavalent
Suggestion: Use swi-prolog.org/pldoc/man?section=threadcom and perform each walk in its own thread (i.e. create 2 threads), with the main thread checking that the leaves returned using thread_get_message are equal (albeit in different orders). Is a swi-prolog-specific solution acceptable?Grodno
The second benefits from some micro-optimizations. It never has a better big O. Finding micro-optimizations for the first in the case where the second does best is going to be language, platform, and data specific.Fatuitous
@Grodno Yes, a swi-prolog-specific solution would be acceptable. Thank you for the suggestion.Sefton
@SimonGoater Tree generation/modification aims only to automatically generate data for empirical comparison of the predicates sf_1/2 e sf_2/2. The two proposed solutions should not create or modify the trees, but only check whether or not they have the same fringe.Sefton
@Fatuitous Exactly! Clearly, both solutions are O(n), in the worst case, since it is not possible to compare all n leaves of the two trees in less time than that (when I say faster I do not mean asymptotically faster) and, in fact, the desired solution must be specific to the Prolog language (which is why the question is tagged with prolog).Sefton
Fun fact: there are cases, where speedup could be from O(N) to O(1)!Celiotomy
As an alternative to threads: delimited continuations: swi-prolog.org/pldoc/man?section=delcontGrodno
just a sidenote, your sf_1 does not "collect the leaves of one tree into a list and then compare them with the leaves of the other tree". it collects leaves of each tree into its own list independently and then, having built the second list up to its head element, compares the second list with the first list. this is because of the order of goals in walk -- A1 is completely independent from Xs. only when the very leftmost leaf is reached, we'll have { walk(L, A1, Xs) = walk(leaf(X), A, [X|A]) } === { L=leaf(X),A1=A,Xs=[X|A] } === { L=leaf(X), Xs=[X|A1] }.Bosson
(contd.) this is because it builds its lists bottom-up. if it were building the lists top-down, then the second walk, i.e. the walk along the second tree with the fully built list of leaves from the first tree, would have a chance to fail on the first mismatching leaf from the second tree. of course it would still have to make a complete walk through the first tree, first.Bosson
That -2 seems to be an ambiguous example - is it demonstrating that traversing the tree does not guarantee an ordered list, or is it demonstrating a blatantly-wrong value?Grodno
I don't see what's ambiguous about 1,2,3 vs 1,-2,3.Bosson
@Celiotomy you accepted answer is more or less what I had in mind. I don't see what's wrong with it? BTW this "burrowing" to the leftmost leaf is the same idea as that of "gopher" from John McCarthy, the originator of LISP - except he actually rotates the tree to the right, whereas you build up a stack, but it's the same thing.Bosson
what's wrong with it? It could be much better termination-wise.Celiotomy
Or, cost could be constant when it is O(max(N1,N2))Celiotomy
Exemplum: ?- sf_(leaf(X),fork(_,_)). so far all loop, but this could fail finitely. And thus all other instances being gigantic trees with more than one fork.Celiotomy
...speaking of which, even ?- sf_(leaf(X),T). should terminate, obviously.Celiotomy
@Celiotomy so now we don't see the question to which the new answers were posted in response, i.e., the bounty requirements. may I suggest posting a new, separate question instead the next time, with the back link to the originating entry (like this one, in this case) as needed. It is perfectly OK to place a bounty on one's own question, to "draw attention to the question". this way, both the original and the followup questions are preserved, and each answer appears under its own separate question. Thank you.Bosson
@Will, agreed for the missing text, which was an instance of OP's question above (that is, better termination which means better O). But posting again a new question with the currently low traffic? Think of it, I intend to put another bounty on this question... Will put the bounty question as a comment too.Celiotomy
@Celiotomy this is really not the accepted SO way. the SO way has a question's answers respond to it, not to something else. the way it is right now is really confusing. every time you post a bounty on an existing question with new requirements, creates this problem. traffic or no traffic, is an orthogonal issue. I think if you would post a question, people will take interest. if not, you'd add a bonus and they will notice. comments are supposed to be ephemeral. they are comments, not contents.Bosson
All my bounties are refinements of the original questions. The OP asked for not necessarily asymptotically faster.Celiotomy
... however, seems you, @Will got more into SO-policing than programming.Celiotomy
I just addressed you with my opinion. That IS what comments are for.Bosson
C
3

Merge the two approaches into one. Always better than sf_2. Spacewise should be better than or equal to sf_1, because the first list is not generated. In SWI the next/3 goal needs to be unfolded to get always better or equal runtime.

sf_3(T1, T2) :-
   stepping(T1, [T2],[]).

next(X, [T|Ts0],Ts) :-
   t_next(T, X, Ts0,Ts).

t_next(leaf(X), X, Ts,Ts).
t_next(fork(L, R), X, Ts0,Ts) :-
   t_next(L, X, [R|Ts0],Ts).

stepping(leaf(X), T2s0,T2s):-
   next(X, T2s0,T2s).
stepping(fork(L, R), T2s0,T2s) :-
   stepping(L, T2s0,T2s1),
   stepping(R, T2s1,T2s).
Celiotomy answered 16/6, 2024 at 8:22 Comment(2)
Eliminating the predicate next/3 and replacing the clause stepping(leaf(X), T2s0, T2s) :- next(X, T2s0, T2s). with stepping(leaf(X), [T|Ts0], T2s ) :- t_next(T, X, Ts0, T2s). makes the implementation even faster.Sefton
(That's what I meant by unfold next/3)Celiotomy
C
2

For a fair comparison, also the original program should be written more in Prolog style. The information of the nodes in T1 can already be used to make the second transformation fail sooner (Ideally, we could fail as soon as possible, but sf_1b just fails sooner only). This can be best observed by looking at termination. Also, this version avoids the re-creation of that list for the second tree.

sf_1b(T1, T2) :-
   phrase(leaves(T1), Xs),
   phrase(leaves(T2), Xs).

leaves(leaf(X)) -->
   [X].
leaves(fork(L,R)) -->
   leaves(L),
   leaves(R).

?- sf_1(leaf(1),fork(leaf(2),_)).
   loops, unexpected.

?- sf_1b(leaf(1),fork(leaf(2),_)).
   false. % as expected
Celiotomy answered 16/6, 2024 at 13:35 Comment(2)
Interesting! By preventing the list for the second tree from being created, the predicate sf_1b/2is faster than sf_1/2 when the trees do not have the same fringe; however, when they have the same fringe, sf_1b/2 may be slightly slower than sf_1/2.Sefton
@Abdu: You are removing the very information that is of interest to anyone understanding this answer. sf_1b is not the optimal solution.Celiotomy
G
2

For proper termination, and an improvement on my previous answer:

sf_br10(leaf(L), leaf(L)).
sf_br10(fork(A1, A2), fork(B1, B2)) :-
    sf_br10_leaf(A1, B1, [A1, A2], [B1, B2], A2, B2, AR, BR),
    sf_br10(AR, BR).

% Compare left-most leaves
sf_br10_leaf(leaf(L), leaf(L), _, _, A, B, A, B).
sf_br10_leaf(leaf(L), fork(B1, B2), AF, BF, AU, BU, AR, BR) :-
    sf_br10_fork(AF, AFR),
    sf_br10_leaf(leaf(L), B1, AFR, BF, AU, fork(B2, BU), AR, BR).
sf_br10_leaf(fork(A1, A2), leaf(L), AF, BF, AU, BU, AR, BR) :-
    sf_br10_fork(BF, BFR),
    sf_br10_leaf(A1, leaf(L), AF, BFR, fork(A2, AU), BU, AR, BR).
sf_br10_leaf(fork(A1, A2), fork(B1, B2), AF, BF, AU, BU, AR, BR) :-
    sf_br10_fork(AF, AFR),
    sf_br10_fork(BF, BFR),
    sf_br10_leaf(A1, B1, AFR, BFR, fork(A2, AU), fork(B2, BU), AR, BR).

% Ensures a fork on both sides, for termination
sf_br10_fork([fork(L, R)|T], [L,R|T]).
sf_br10_fork([leaf(_)|T], R) :-
    sf_br10_fork(T, R).

Results:

?- sf_br10(fork(fork(leaf(1), leaf(2)), leaf(3)),
   fork(leaf(1), fork(leaf(2), leaf(3)))).
true ;  % Succeeds
false.

?- sf_br10(fork(fork(leaf(1), leaf(2)), leaf(3)),
   fork(leaf(1), fork(leaf(-2), leaf(3)))).
false.  % As intended

?- sf_br10(leaf(X), fork(_,_)).
false.  % Terminates

?- sf_br10(leaf(X), T).
T = leaf(X).  % Terminates

?- T1 = fork(leaf(1),fork(leaf(2),leaf(3))), sf_br10(T2,T1).
T1 = T2, T2 = fork(leaf(1), fork(leaf(2), leaf(3))) ;
T1 = fork(leaf(1), fork(leaf(2), leaf(3))),
T2 = fork(fork(leaf(1), leaf(2)), leaf(3)) ;
false.  % Terminates

?- T = fork(leaf(1),fork(leaf(2),fork(leaf(3),leaf(4)))), sf_br10(T,T2).
T = T2, T2 = fork(leaf(1), fork(leaf(2), fork(leaf(3), leaf(4)))) ;
T = fork(leaf(1), fork(leaf(2), fork(leaf(3), leaf(4)))),
T2 = fork(leaf(1), fork(fork(leaf(2), leaf(3)), leaf(4))) ;
T = fork(leaf(1), fork(leaf(2), fork(leaf(3), leaf(4)))),
T2 = fork(fork(leaf(1), leaf(2)), fork(leaf(3), leaf(4))) ;
T = fork(leaf(1), fork(leaf(2), fork(leaf(3), leaf(4)))),
T2 = fork(fork(leaf(1), fork(leaf(2), leaf(3))), leaf(4)) ;
T = fork(leaf(1), fork(leaf(2), fork(leaf(3), leaf(4)))),
T2 = fork(fork(fork(leaf(1), leaf(2)), leaf(3)), leaf(4)) ;
false.  % Terminates
Grodno answered 25/6, 2024 at 6:42 Comment(9)
?- T = fork(leaf(1),fork(leaf(2),fork(leaf(3),leaf(4)))), tree_equal(T,_), false. loops, unexpected. Please do testing before posting.Celiotomy
Here is a test: ?- numbered_from(L,1),tree_leaves(T,L), ( true ; tree_equal(T,_), false ). will loop for the simplest counterexample, if there is one.Celiotomy
Also note that your member_exists/2 still produces multiple answers because of the _-variables. ?- member_exists(fork(_,_),[fork(leaf(1),leaf(2)),fork(leaf(3),leaf(4))]). true ; true ; false.Celiotomy
Apologies, corrected, using a simple method I'd previously discounted. Where is the code for numbered_from please?Grodno
Search it on SO, or google :-)Celiotomy
One more: it would help if you would stick to the original names, so some sf_br99 or so such that all versions can be loaded simultaneously without any extra moduling.Celiotomy
Termination is fine, but it is now incomplete. ?- T = fork(leaf(1),fork(leaf(2),fork(leaf(3),leaf(4)))), T2 = fork(fork(leaf(1),fork(leaf(2),leaf(3))),leaf(4)), tree_equal(T,T2). false, unexpected.Celiotomy
?- T = fork(leaf(1),fork(leaf(2),_)), T2 = fork(fork(_,fork(_,_)),_), tree_equal(T,T2). false, unexpected. So even this generalization fails.Celiotomy
Finally achieved completeness and termination.Grodno
G
2

This is simpler and also hugely faster than sf_br10:

sf_br11(A, B) :-
    % A and B to compare the leaves
    % Then A and B to balance the forks
    sf_br11_leaf([A], [B], [A], [B]).

% Compare left-most leaves
% Finish when all leaves have been compared
% The balance-fork A and B lists may have leaves remaining in them
sf_br11_leaf([], [], _, _).
sf_br11_leaf([leaf(L)|AT], [leaf(L)|BT], A, B) :-
    % Equal leaf - compare the remainder of the leaves
    sf_br11_leaf(AT, BT, A, B).
sf_br11_leaf([leaf(L)|AT], [fork(B1, B2)|BT], A, B) :-
    % One tree has a fork, so the other tree must have a fork somewhere
    sf_br11_bal(A, AR),
    sf_br11_leaf([leaf(L)|AT], [B1, B2|BT], AR, B).
sf_br11_leaf([fork(A1, A2)|AT], [leaf(L)|BT], A, B) :-
    sf_br11_bal(B, BR),
    sf_br11_leaf([A1, A2|AT], [leaf(L)|BT], A, BR).
sf_br11_leaf([fork(A1, A2)|AT], [fork(B1, B2)|BT], A, B) :-
    % Degrades performance significantly if removed
    sf_br11_bal(A, AR),
    sf_br11_bal(B, BR),
    sf_br11_leaf([A1, A2|AT], [B1, B2|BT], AR, BR).

% Take a fork, for balance
sf_br11_bal([fork(A, B)|T], [A, B|T]).
% Don't care about a leaf here
sf_br11_bal([leaf(_)|T], R) :-
    sf_br11_bal(T, R).

Performance comparison in swi-prolog:

?- L = fork(fork(fork(leaf(8749506093),fork(leaf(4992332622),leaf(3545171255))),fork(fork(leaf(758963778),leaf(5031170155)),fork(leaf(3596209336),leaf(9352234176)))),fork(fork(leaf(6258654833),fork(leaf(8658914980),leaf(8528104405))),leaf(929585720))), time(findall(C, sf_br10(L, C), Cs)), length(Cs, CsLen).
% 55,525,766 inferences, 4.320 CPU in 4.336 seconds (100% CPU, 12854198 Lips)
CsLen = 16796.
?- L = fork(fork(fork(leaf(8749506093),fork(leaf(4992332622),leaf(3545171255))),fork(fork(leaf(758963778),leaf(5031170155)),fork(leaf(3596209336),leaf(9352234176)))),fork(fork(leaf(6258654833),fork(leaf(8658914980),leaf(8528104405))),leaf(929585720))), time(findall(C, sf_br11(L, C), Cs)), length(Cs, CsLen).
% 524,687 inferences, 0.073 CPU in 0.073 seconds (100% CPU, 7227540 Lips)
CsLen = 16796.
Grodno answered 15/9, 2024 at 7:57 Comment(0)
G
1

For better termination:

tree_equal(leaf(L), leaf(L)).
tree_equal(fork(A1, A2), fork(B1, B2)) :-
    tree_equal(A1, B1),
    tree_equal(A2, B2).
% Two equivalent forking structures
tree_equal(fork(fork(A1, A2), A3), fork(B1, fork(B2, B3))) :-
    fork_equal(A1, A2, A3, B1, B2, B3).
tree_equal(fork(B1, fork(B2, B3)), fork(fork(A1, A2), A3)) :-
    fork_equal(A1, A2, A3, B1, B2, B3).

fork_equal(A1, A2, A3, B1, B2, B3) :-
    tree_equal(fork(A1, fork(A2, A3)), fork(B1, fork(B2, B3))).

Results:

?- tree_equal(fork(fork(leaf(1), leaf(2)), leaf(3)),
   fork(leaf(1), fork(leaf(2), leaf(3)))).
true ;  % Succeeds
false.

?- tree_equal(fork(fork(leaf(1), leaf(2)), leaf(3)),
   fork(leaf(1), fork(leaf(-2), leaf(3)))).
false.

?- tree_equal(leaf(X),fork(_,_)).
false.  % Terminates

?- tree_equal(leaf(X),T).
T = leaf(X).  % Terminates

?- T1 = fork(leaf(1),fork(leaf(2),fork(leaf(3),leaf(4)))),
   T2 = fork(fork(leaf(1),fork(leaf(2),leaf(3))),leaf(4)),
   tree_equal(T1,T2).
T1 = fork(leaf(1), fork(leaf(2), fork(leaf(3), leaf(4)))),
T2 = fork(fork(leaf(1), fork(leaf(2), leaf(3))), leaf(4)) ;
false.
Grodno answered 24/6, 2024 at 13:32 Comment(4)
?- T1 = fork(leaf(1),fork(leaf(2),fork(leaf(3),leaf(4)))), T2 = fork(fork(leaf(1),fork(leaf(2),leaf(3))),leaf(4)), trees_equal(T1,T2). false, unexpected.Celiotomy
(It would help to stick to the naming convention. trees suggests a list of tree)Celiotomy
Fixed. I hope (not certain) it's generic enough now.Grodno
(seems to be correct) ?- T1 = fork(leaf(1),fork(leaf(2),leaf(3))), tree_equal(T1,T2), false. loops. this was not required by the bounty, if you find an improvement to this, please use another answer.Celiotomy
C
1

This is the definition I had in mind. It terminates if the first argument is given. But first, why sf_1b is not ideal using a

leaves(leaf(X)) --> {false},
   [X].
leaves(fork(L,R)) -->
   leaves(L), {false},
   leaves(R).

?- phrase(leaves(T), []).
   loops, unexpected.
   false. % expected, but not found.

So an example of left-recursion which can be readily avoided.

sf_1c(T1, T2) :-
   phrase(leaves(T1), Xs),
   tree_leaves(T2, Xs).

tree_leaves(T, Xs) :-
   Xs = [_|C],
   phrase(tleaves(T, C,[]), Xs).

tleaves(leaf(X), C,C) -->
   [X].
tleaves(fork(L,R), [_|C0],C) -->
   tleaves(L, C0,C1),
   tleaves(R, C1,C).

This now terminates for the first argument:

sf_1c(A,B)terminates_if b(A).
    % optimal. loops found: [sf_1c(fork(_,_),_),sf_1c(fork(_,_),y)].

As a consequence of this termination property, the (worst case) complexity of ground queries depends (in this case) exclusively on the arguments mentioned in the termination condition. The other arguments, here the second, have no influence! At best they may improve complexity, but they never can deteriorate it. This can be best observed by looking at the runtime of left-leaning trees which are linear instead of constant for the solutions prior to sf_1c.

leftleaves(leaf(N)) -->
   [N].
leftleaves(fork(T,leaf(N))) -->
   [N],
   leftleaves(T).

?- T1 = leaf(1), numbered_from(L, 2), ( true ; phrase(leftleaves(T2),L), time(sf_1c(T1,T2)) ).

This can still be improved.

Celiotomy answered 24/6, 2024 at 18:43 Comment(0)
G
0

As another improvement - this is simpler, and faster, and will use less memory than sf_br11:

sf_br12(A, B) :-
    % Turn tree into list of leaves
    sf_br12_leaf([A], [B]).

% Compare left-most leaves
% Finish when all leaves have been compared
sf_br12_leaf([], []).
sf_br12_leaf([leaf(L)|AT], [leaf(L)|BT]) :-
    % Equal leaf - compare the remainder of the leaves
    sf_br12_leaf(AT, BT).
sf_br12_leaf([leaf(L)|AT], [fork(B1, B2)|BT]) :-
    % One tree has a fork, so the other tree must have a fork somewhere
    sf_br12_bal(AT, AR),
    sf_br12_leaf([leaf(L)|AR], [B1, B2|BT]).
sf_br12_leaf([fork(A1, A2)|AT], [leaf(L)|BT]) :-
    sf_br12_bal(BT, BR),
    sf_br12_leaf([A1, A2|AT], [leaf(L)|BR]).
sf_br12_leaf([fork(A1, A2)|AT], [fork(B1, B2)|BT]) :-
    sf_br12_leaf([A1, A2|AT], [B1, B2|BT]).

% Take a fork, for balance
sf_br12_bal([fork(A, B)|T], [A, B|T]).
% Keep leaf but still look for a fork
sf_br12_bal([leaf(L)|T], [leaf(L)|R]) :-
    sf_br12_bal(T, R).

Performance comparison in swi-prolog:

?- set_prolog_flag(stack_limit, 4_000_000_000).
true.

?- L = fork(fork(fork(leaf(4299109730),fork(leaf(1079612320),leaf(7580680894))),fork(fork(leaf(2332129931),leaf(1349094717)),fork(leaf(9423885106),leaf(1498448997)))),fork(fork(fork(leaf(8331413833),leaf(692082554)),fork(leaf(2358532999),leaf(2002056711))),fork(fork(leaf(5720431031),leaf(21650271)),fork(leaf(7605477582),leaf(6592554308))))), time(findall(C, sf_br11(L, C), Cs)), length(Cs, CsLen).
% 82,925,160 inferences, 10.488 CPU in 10.535 seconds (100% CPU, 7906441 Lips)
CsLen = 2674440.

With sf12 instead of sf11:

% 51,076,134 inferences, 7.838 CPU in 7.850 seconds (100% CPU, 6516488 Lips)
CsLen = 2674440.
Grodno answered 23/9, 2024 at 18:57 Comment(0)

© 2022 - 2025 — McMap. All rights reserved.