簡體   English   中英

收集物品並計算出現次數

[英]Collecting Items and Counting the Number of Occurrences

我正在嘗試編寫一個遞歸規則collCount/2 ,它將列表中相同的項目與它們各自的出現次數分組為元組。

例如, collCount([a,b,a,b,c,b],F)F[(a,2),(b,3),(c,1)]綁定。 運行此查詢時,Prolog只返回no

以下是我迄今為止所做的工作:

collCount([H|T],[(H,N)|L2]) :-
    countDel(H,[H|T],L,N),
    collCount(L,L2).

countDel(X,T,Rest,N) :-
    occur(X,T,N),
    delAll(X,T,Rest).

occur(_,[],0).
occur(X,[X|T],N) :-
    occur(X,T,NN),
    N is NN + 1.
occur(X,[H|T],N) :-
    occur(X,T,N),
    X \= H.

delAll(_,[],[]).
delAll(X,[X|T],Ans) :-
    delAll(X,T,Ans).
delAll(X,[H|T],[H|Rest]) :-
    delAll(X,T,Rest),
    X \= H.

謂詞countDel/4計算並刪除列表中特定項的所有匹配項。 例如, countDel(2,[1,2,3,2,2],L,N)將L與[1,3]結合, N3

謂詞occur/3計算列表中特定項的所有出現次數。 例如, occur(3,[1,2,3,4,3],Num)Num2綁定。

謂詞delAll/3刪除列表中特定項的所有匹配項。 例如, delAll(3,[1,2,3,4,3],L)L[1,2,4]結合。

任何幫助是極大的贊賞。

我想提請你注意你和@ CapelliC解決方案的一小部分內容。 無害的:

occur(_,[],0) :- false.
occur(X,[X|T],N) :-
    occur(X,T,NN), false,
    N is NN + 1.
occur(X,[H|T],N) :-
    occur(X,T,N), false,
    X \= H.

所以我在這里做的是在你的程序中插入一些false目標。 通過這種方式,這個程序現在將采取比沒有更少的推論。 不過,有一些值得注意的事情。 考慮:

?- length(As,M), M>9, maplist(=(a),As), \+ time(occur(a,As,_)).
% 3,072 inferences, 0.002 CPU in 0.002 seconds (100% CPU, 1989931 Lips)
As = [a, a, a, a, a, a, a, a, a|...],
M = 10 ;
% 6,144 inferences, 0.003 CPU in 0.003 seconds (100% CPU, 2050613 Lips)
As = [a, a, a, a, a, a, a, a, a|...],
M = 11 ;
% 12,288 inferences, 0.006 CPU in 0.006 seconds (100% CPU, 2128433 Lips)
As = [a, a, a, a, a, a, a, a, a|...],
M = 12

你看夠了嗎? 添加另一個元素時,推理數量會翻倍。 簡而言之,有指數開銷 你需要首先考慮不平等的目標。 更好的是,使用dif(X, H)

請注意,此屬性與尾遞歸無關。 仍然有一些優化的地方,但遠不如這個。

有關使用此技術的更多示例,請參閱

對於邏輯上純粹的實現,請查看對相關問題“ 如何計算Prolog中列表中元素出現次數 ”的答案

在那個答案中,我提出了list_counts/2的實現,它保留了

讓我們使用list_counts/2

?- list_counts([a,b,a,b,c,b],F).
F = [a-2, b-3, c-1].

注意, list_counts/2表示KV對作為KV 通常,由於多種原因(可讀性,與其他標准庫謂詞的互操作性,效率),這優於基於逗號(K,V)或列表[K,V]表示。

如果您確實需要使用基於逗號的表示法,則可以按如下方式定義collCount/2

:- use_module(library(lambda)).

collCount(Xs,Fss) :-
    list_counts(Xs,Css),
    maplist(\ (K-V)^(K,V)^true,Css,Fss).

所以我們讓collCount/2使用:

?- collCount([a,b,a,b,c,b],F).
F = [(a,2), (b,3), (c,1)].           % succeeds deterministically

編輯2015-05-13

出於好奇,讓我們考慮@false在他的回答中提到的表現方面。

以下查詢大致對應於@false在其答案中使用的查詢。 在這兩者中,我們對通用終止所需的努力感興趣:

?- length(As,M), 
   M>9, 
   maplist(=(a),As), 
   time((list_item_subtracted_count0_count(As,a,_,1,_),false ; true)).
% 73 inferences, 0.000 CPU in 0.000 seconds (95% CPU, 1528316 Lips)
As = [a, a, a, a, a, a, a, a, a|...],
M = 10 ;
% 80 inferences, 0.000 CPU in 0.000 seconds (96% CPU, 1261133 Lips)
As = [a, a, a, a, a, a, a, a, a|...],
M = 11 ;
% 87 inferences, 0.000 CPU in 0.000 seconds (96% CPU, 1315034 Lips)
As = [a, a, a, a, a, a, a, a, a|...],
M = 12 ...

你的代碼大多是正確的。 我已將評論放在我修改過的地方。

collCount([],[]).  % miss base case
collCount([H|T],[(H,N)|L2]) :-
    countDel(H,[H|T],L,N),
    collCount(L,L2).

countDel(X,T,Rest,N) :-
    occur(X,T,N),
    delAll(X,T,Rest).

occur(_,[],0).
occur(X,[X|T],N) :-
    occur(X,T,NN),
    N is NN + 1.
occur(X,[H|T],N) :-
    occur(X,T,N),
    X \= H.

delAll(_,[],[]).
delAll(X,[X|T],Ans) :-
    delAll(X,T,Ans).
delAll(X,[H|T],[H|Rest]) :-
    X \= H,  % moved before recursive call
    delAll(X,T,Rest).

這收益率

?- collCount([a,b,a,b,c,b],F).
F = [ (a, 2), (b, 3), (c, 1)] ;
false.

單程:

frequencies_of( []     , []     ) .  % empty list? success!
frequencies_of( [X|Xs] , [F|Fs] ) :- % non-empty list?
  count( Xs , X:1 , F , X1 ) ,       % count the occurrences of the head, returning the source list with all X removed
  frequencies_of( X1 , Fs )          % continue
  .                                  %

count( [] , F , F , [] ) .           % empty list? success: we've got a final count.
count( [H|T] , X:N , F , Fs ) :-     % otherwise...
  H = X ,                            % - if the head is what we're counting, 
  N1 is N+1 ,                        % - increment the count
  count( T , X:N1 , F , Fs )         % - recurse down
  .                                  %
count( [H|T] , X:N , F , [H|Fs] ) :- % otherwise...
  H \= X ,                           % - if the head is NOT what we're counting
  count( T , X:N , F , Fs )          % - recurse down, placing the head in the remainder list
  .                                  %

另一種看待它的方式:

frequencies_of( Xs , Fs ) :-     % compile a frequency table
  frequencies_of( Xs , [] , Fs ) % by invoking a worker predicate with its accumulator seeded with the empty list
  .

frequencies_of( []     , Fs , Fs ) .  % the worker predicate ends when the source list is exhausted
frequencies_of( [X|Xs] , Ts , Fs ) :- % otherwise...
  count( X , Ts , T1 ) ,              % - count X in the accumulator
  frequencies_of( Xs , T1 , Fs )      % - and recursively continue
  .                                   %

count( X , []       , [X:1]     ) .   % if we get to the end, we have a new X: count it
count( X , [X:N|Ts] , [X:N1|Ts] ) :-  % otherwise, if we found X,
  N1 is N+1                           % - increment the count
  .                                   % - and end.
count( X , [T:N|Ts] , [T:N|Fs]  ) :-  % otherwise
  X \= T ,                            % - assuming we didn't find X
  increment( X , Ts , Fs )            % - just continue looking
  .                                   % Easy!

第三種方法是首先對列表進行排序,而不刪除重復項。 一旦列表被排序,有序列表的簡單1遍游程編碼為您提供頻率表,如下所示:

frequencies_of( Xs , Fs ) :- % to compute the frequencies of list elements
  msort( Xs , Ts ) ,         % - sort the list (without removing duplicates)
  rle( Ts , Fs )             % - then run-length encode the sorted list
  .                          % Easy!

rle( []    , [] ) .    % the run length encoding of an empty list is the empty list.
rle( [H|T] , Rs ) :-   % the run length encoding is of a non-empty list is found by
  rle( T , H:1 , Rs )  % invoking the worker on the tail with the accumulator seeded with the head
  .                    %

rle( []    , X:N , [X:N] ) .     % the end of the source list ends the current run (and the encoding).
rle( [H|T] , X:N , Rs    ) :-    % otherwise...
  H = X     ,                    % - if we have a continuation of the run,
  N1 is N+1 ,                    % - increment the count
  rle( T , X:N1 , Rs )           % - and recursively continue
  .                              %
rle( [H|T] , X:N , [X:N|Rs] ) :- % otherwise...
  H \= X ,                       % - if the run is at an end,
  rle( T , H:1 , Rs)             % - recursively continue, starting a new run and placing the current encoding in the result list.
  .                              %

暫無
暫無

聲明:本站的技術帖子網頁,遵循CC BY-SA 4.0協議,如果您需要轉載,請注明本站網址或者原文地址。任何問題請咨詢:yoyou2525@163.com.

 
粵ICP備18138465號  © 2020-2024 STACKOOM.COM