same_length/2的更好的纯版本



给定same_length/2作为的频繁纯定义

same_length([],[]).
same_length([_|As], [_|Bs]) :-
same_length(As, Bs).
?- same_length(L, [_|L]).
loops.

有没有一个纯粹的定义在这种情况下不循环?类似于append/3的纯(但效率较低(版本append2u/3

我知道如何使用var/1等手动捕获此类情况,但理想情况下,需要与原始定义一样纯粹的版本。或者至少它应该很简单。

我尝试的是上面的定义。

一个澄清似乎是有序的:

请注意,某些查询本质上不能终止。想想:

?- same_length(Ls, Ks).
Ls = [], Ks = []
;  Ls = [_A], Ks = [_B]
;  Ls = [_A,_B], Ks = [_C,_D]
;  Ls = [_A,_B,_C], Ks = [_D,_E,_F]
;  Ls = [_A,_B,_C,_D], Ks = [_E,_F,_G,_H]
;  ... .

没有其他方法可以使用句法答案替换的语言来列举所有的解决方案。

但是对于给定的查询,仍然可以终止实现。

这个答案旨在最大限度地降低运行时成本。

它构建在'$skip_max_list'/4上,运行在Scryer Prolog上。

首先,一些辅助代码:

:- use_module(library(lists)).
'$skip_list'(N,Xs0,Xs) :-
'$skip_max_list'(N,_,Xs0,Xs).
is_list([]).
is_list([_|Xs]) :-
is_list(Xs).
sam_length_([],[]).
sam_length_([_|Xs],[_|Ys]) :-
sam_length_(Xs,Ys).

现在主菜:

sam_length(Ls1,Ls2) :-
'$skip_list'(L1,Ls1,Rs1),
(  Rs1 == []
-> length(Ls2,L1)
;  var(Rs1),
'$skip_max_list'(L2,L1,Ls2,Rs2),
(  L2 < L1
-> var(Rs2),
Rs1 == Rs2,
'$skip_max_list'(_,L2,Ls1,Ps1),
sam_length_(Ps1,Rs2)
;  '$skip_list'(N2,Rs2,Ts2),
(  Ts2 == []
-> M1 is N2-L1,
length(Rs1,M1)
;  var(Ts2),
(  N2 > 0
-> Ts2 == Rs1,
sam_length_(Rs2,Rs1)     % switch argument order
;  Rs1 == Rs2
-> is_list(Rs1)             % simpler enumeration
;  sam_length_(Rs1,Rs2)
)
)
)
).

示例查询:

?-sam_length(L,[_|L](。false。?-sam_length([_],L(。L=[_A]。?-sam_长度(L,M(。L=[],M=[];L=[A],M=[_B]

使用'$skip_max_list'/4:的解决方案

% Clause for `?- L = [a|L], same_length(L, _)`.
same_length(As, Bs) :-
(Cs = As ; Cs = Bs),
'$skip_max_list'(_, _, Cs, Cs0),
subsumes_term([_|_], Cs0), !,
false.
% Clause for `?- same_length(L, [_|L])`.
same_length(As, Bs) :-
As == Bs,
'$skip_max_list'(S, _, As, As0),
'$skip_max_list'(T, _, Bs, Bs0),
As0 == Bs0,
S == T, !,
false.
same_length(As, Bs) :-
same_length_(As, Bs).
same_length_([], []).
same_length_([_|As], [_|Bs]) :-
same_length_(As, Bs).

查询:

?- L = [a|L], same_length(L, _).
false.
?- same_length(L, [_|L]).
false.
?- same_length([_], L).
L = [_A].
?- same_length(L, M).
L = [], M = []
;  L = [_A], M = [_B]
;  ... .

更新的解决方案

这是我的解决方案:

same_length(A, A).
same_length([_|A], [_|B]) :- same_length(A, B).

?- same_length(L, [_|L]).
L = [_1696|L]

我不确定它是否拥有你想要的所有房产。例如,如果您调用

? - same_length(L, [1,2,3]).

则它列出了许多答案,例如L=[_X,2,3],而不仅仅是[_X、_Y、_Z]。但它是纯粹的,并为引用的查询生成正确的答案。

这相当优雅,但性能下降:

% Using a previously-seen-tails list
same_length2(L, M) :-
same_length2_(L, M, []).
same_length2_([], [], _).
% P is list of tails previously visited
same_length2_([HL|L], [HM|M], P) :-
same_length2_chk_([HL|L], P),
same_length2_chk_([HM|M], P),
% Append after checking, to never see again
append([[HL|L], [HM|M]], P, P1),
same_length2_(L, M, P1).
same_length2_chk_(T, P) :-
% Ensure no match with previously-seen tails
+ (
member(E, P),
T == E
).

swi-prolog中的结果:

?- same_length2([_|L], [_|L]).
L = [] ;
L = [_] ;
L = [_, _] ;
?- length(L, 10_000_000), time(same_length2(L, [])).
% 3 inferences, 0.000 CPU in 0.000 seconds (88% CPU, 153249 Lips)
false.
?- freeze(R, R=[_|L]), same_length2(L, R).
false.
?- L = [_|L], same_length2(L, []).
false.
?- same_length2([1,2|L], [3,4,5|L]).
false.
?- same_length2(L, [_|L]).
false.
?- same_length2([_|L], L).
false.
?- same_length2(L, [_,_|L]).
false.
?- same_length2([_,_|L], L).
false.
?- same_length2(non_list, non_list).
false.
?- same_length2([a,b,c], [1,2,3]).
true.
?- same_length2([1|L], [3,4,5|R]).
L = [_, _],
R = [] ;
L = [_, _, _],
R = [_] ;
L = [_, _, _, _],
R = [_, _] ;
% Increasingly slow
?- time(same_length2(L1, L2)).
% 1 inferences, 0.000 CPU in 0.000 seconds (61% CPU, 116455 Lips)
L1 = L2, L2 = [] ;
% 13 inferences, 0.000 CPU in 0.000 seconds (87% CPU, 729354 Lips)
L1 = [_],
L2 = [_] ;
% 15 inferences, 0.000 CPU in 0.000 seconds (82% CPU, 795123 Lips)
L1 = [_, _],
L2 = [_, _] ;
% 19 inferences, 0.000 CPU in 0.000 seconds (82% CPU, 1558399 Lips)
L1 = [_, _, _],
L2 = [_, _, _] ;

怎么样:

same_length2(L1, L2) :-
lists2_end_len(L1, E1, Len1, L2, E2, Len2),
% If ends are same, the length before the ends must be same
(   E1 == E2
% == is fastest portable integer comparison in swi-prolog
->  Len1 == Len2,
same_length(E1, E2)
;   same_length(L1, L2)
). 
lists2_end_len(L1, E1, Len1, L2, E2, Len2) :-
lists2_end_len_(L1, E1, _, 0, Len1Calc, L2, E2, _, 0, Len2Calc),
Len1 = Len1Calc,
Len2 = Len2Calc.

% Not using '$skip_list', to be portable
lists2_end_len_(L, E, Cl, U, Len, L2, E2, Cl2, U2, Len2) :-
(   + + L = []
% Found end of list
->  E = L,
Len = U,
(   L == []
->  Cl = true,
% Can fail fast if other list is longer
(   integer(U2)
->  U >= U2
)
;   Cl = false
),
(   nonvar(Len2)
% Both lists traversed
->  true
;   lists2_end_len_(L2, E2, Cl2, U2, Len2, L, E, Cl, U, Len)
)
;   L = [_|T],
% Occurs check 
T == L,
U1 is U + 1,
lists2_end_len_(L2, E2, Cl2, U2, Len2, T, E, Cl, U1, Len)
).

swi-prolog中的结果:

?- length(L, 10_000_000), time(same_length2(L, [])).
% 6 inferences, 0.000 CPU in 0.000 seconds (89% CPU, 253336 Lips)
false.
?- freeze(R, R=[_|L]), same_length2(L, R).
false.
?- L = [_|L], same_length2(L, []).
false.
?- same_length2([1,2|L], [3,4,5|L]).
false.
?- same_length2(L, [_|L]).
false.
?- same_length2(L, [_,_|L]).
false.
?- same_length2([_|L], L).
false.
?- same_length2([_,_|L], L).
false.
?- same_length2(non_list, non_list).
false.
?- same_length2([a,b,c], [1,2,3]).
true.
?- same_length2(L1, L2).
L1 = L2, L2 = [] ;
L1 = [_],
L2 = [_] ;
L1 = [_, _],
L2 = [_, _] ;
?- same_length2([1|L], [3,4,5|R]).
L = [_, _],
R = [] ;
L = [_, _, _],
R = [_] ;
L = [_, _, _, _],
R = [_, _] ;

最新更新