计算列表中列表中的每个元素?

发布于 2025-01-18 14:42:53 字数 8 浏览 0 评论 0原文

continue

I'm new to learn Prolog, I want to fulfill the predicate below, I have no idea how I implement this

count([9,9,2,2,1],X). -- input

X = [1-1,2-2,9-2].

[X-Y] = X is the value, Y is the counter.

如果你对这篇内容有疑问,欢迎到本站社区发帖提问 参与讨论,获取更多帮助,或者扫码二维码加入 Web 技术交流群。

扫码二维码加入Web技术交流群

发布评论

需要 登录 才能够评论, 你可以免费 注册 一个本站的账号。

评论(3

遗心遗梦遗幸福 2025-01-25 14:42:53
count_elements(Lst, LstCount) :-
    % "sort" also removes duplicates
    sort(Lst, LstSorted),
    findall(Elem-Count, (
        member(Elem, LstSorted), elem_in_list_count(Elem, Lst, Count)
    ), LstCount).
    
elem_in_list_count(Elem, Lst, Count) :-
    aggregate_all(count, member(Elem, Lst), Count).

swi-prolog 的结果:

?- time(count_elements([9, 9, 2, 2, 1], Pairs)).
% 61 inferences, 0.000 CPU in 0.000 seconds (96% CPU, 528143 Lips)
Pairs = [1-1,2-2,9-2].

这是一个逻辑上纯粹的版本(其中最终排序需要最多的编码工作):

:- use_module(library(reif)).

count_elements_pure(Lst, LstCountSorted) :-
    count_elem_pairs_(Lst, Lst, [], LstCount),
    keysort_pure(LstCount, LstCountSorted).

count_elem_pairs_([], _, _, []).
count_elem_pairs_([H|T], Lst, LstUnique, LstCount) :-
    memberd_t(H, LstUnique, Bool),
    ( Bool == true -> count_elem_pairs_(T, Lst, LstUnique, LstCount)
    ; list_elem_count(Lst, H, Count),
      % Add pair
      LstCount = [H-Count|LstCount0],
      count_elem_pairs_(T, Lst, [H|LstUnique], LstCount0)
    ).

% Count elements in list, with logical purity
list_elem_count(Lst, Elem, Count) :-
    list_elem_count_(Lst, Elem, Count).

list_elem_count_([], _Elem, 0).
list_elem_count_([H|T], Elem, Count) :-
    list_elem_count_(T, Elem, Count0),
    if_(H = Elem, Count is Count0 + 1, Count0 = Count).


lowest_pair(Lst, Elem) :-
    Lst = [H|T],
    lowest_pair_(T, H, Elem).

lowest_pair_([], E, E).
lowest_pair_([H|T], P, L) :-
    H = HKey-_,
    P = PKey-_,
    % The key is not limited to an integer
    when((nonvar(HKey), nonvar(PKey)), compare(Comp, HKey, PKey)),
    lowest_pair_comp_(Comp, T, H, P, L).

lowest_pair_comp_(<, T, H, _, L) :-
    lowest_pair_(T, H, L).

lowest_pair_comp_(>, T, _, P, L) :-
    lowest_pair_(T, P, L).


keysort_pure(Lst, LstSorted) :-
    keysort_pure_(Lst, LstSorted).

keysort_pure_([], []).
keysort_pure_([H|T], [E|Sorted]) :-
    lowest_pair([H|T], E),
    % Don't need to repeat the if_/3 checks
    select_once_eqeq([H|T], E, Rest),
    keysort_pure_(Rest, Sorted).

select_once_eqeq(Lst, Elem, Rest) :-
    Lst = [H|T],
    select_once_eqeq_(T, H, Elem, Rest).

select_once_eqeq_(Tail, Head, Elem, Rest) :-
    Elem == Head, !,
    Rest = Tail.

select_once_eqeq_([Head2|Tail], Head, Elem, [Head|Rest]) :-
    select_once_eqeq_(Tail, Head2, Elem, Rest).

swi-prolog 的结果:

?- time(count_elements_pure([9, 9, 2, 2, 1], Pairs)).
% 111 inferences, 0.000 CPU in 0.000 seconds (95% CPU, 1134876 Lips)
Pairs = [1-1,2-2,9-2].

组合会快速增加,所以这里只是一个尝试:

?- count_elements_pure([A, B], Pairs).
A = B,
Pairs = [B-2] ;
Pairs = [B-1,A-1],
dif(B,A),
when((nonvar(B),nonvar(A)),compare(<,B,A)) ;
Pairs = [A-1,B-1],
dif(B,A),
when((nonvar(B),nonvar(A)),compare(>,B,A)).
count_elements(Lst, LstCount) :-
    % "sort" also removes duplicates
    sort(Lst, LstSorted),
    findall(Elem-Count, (
        member(Elem, LstSorted), elem_in_list_count(Elem, Lst, Count)
    ), LstCount).
    
elem_in_list_count(Elem, Lst, Count) :-
    aggregate_all(count, member(Elem, Lst), Count).

Result in swi-prolog:

?- time(count_elements([9, 9, 2, 2, 1], Pairs)).
% 61 inferences, 0.000 CPU in 0.000 seconds (96% CPU, 528143 Lips)
Pairs = [1-1,2-2,9-2].

Here is a logically-pure version (in which the final sort needed the most coding effort):

:- use_module(library(reif)).

count_elements_pure(Lst, LstCountSorted) :-
    count_elem_pairs_(Lst, Lst, [], LstCount),
    keysort_pure(LstCount, LstCountSorted).

count_elem_pairs_([], _, _, []).
count_elem_pairs_([H|T], Lst, LstUnique, LstCount) :-
    memberd_t(H, LstUnique, Bool),
    ( Bool == true -> count_elem_pairs_(T, Lst, LstUnique, LstCount)
    ; list_elem_count(Lst, H, Count),
      % Add pair
      LstCount = [H-Count|LstCount0],
      count_elem_pairs_(T, Lst, [H|LstUnique], LstCount0)
    ).

% Count elements in list, with logical purity
list_elem_count(Lst, Elem, Count) :-
    list_elem_count_(Lst, Elem, Count).

list_elem_count_([], _Elem, 0).
list_elem_count_([H|T], Elem, Count) :-
    list_elem_count_(T, Elem, Count0),
    if_(H = Elem, Count is Count0 + 1, Count0 = Count).


lowest_pair(Lst, Elem) :-
    Lst = [H|T],
    lowest_pair_(T, H, Elem).

lowest_pair_([], E, E).
lowest_pair_([H|T], P, L) :-
    H = HKey-_,
    P = PKey-_,
    % The key is not limited to an integer
    when((nonvar(HKey), nonvar(PKey)), compare(Comp, HKey, PKey)),
    lowest_pair_comp_(Comp, T, H, P, L).

lowest_pair_comp_(<, T, H, _, L) :-
    lowest_pair_(T, H, L).

lowest_pair_comp_(>, T, _, P, L) :-
    lowest_pair_(T, P, L).


keysort_pure(Lst, LstSorted) :-
    keysort_pure_(Lst, LstSorted).

keysort_pure_([], []).
keysort_pure_([H|T], [E|Sorted]) :-
    lowest_pair([H|T], E),
    % Don't need to repeat the if_/3 checks
    select_once_eqeq([H|T], E, Rest),
    keysort_pure_(Rest, Sorted).

select_once_eqeq(Lst, Elem, Rest) :-
    Lst = [H|T],
    select_once_eqeq_(T, H, Elem, Rest).

select_once_eqeq_(Tail, Head, Elem, Rest) :-
    Elem == Head, !,
    Rest = Tail.

select_once_eqeq_([Head2|Tail], Head, Elem, [Head|Rest]) :-
    select_once_eqeq_(Tail, Head2, Elem, Rest).

Result in swi-prolog:

?- time(count_elements_pure([9, 9, 2, 2, 1], Pairs)).
% 111 inferences, 0.000 CPU in 0.000 seconds (95% CPU, 1134876 Lips)
Pairs = [1-1,2-2,9-2].

The combinations multiply quickly, so here is just a taste:

?- count_elements_pure([A, B], Pairs).
A = B,
Pairs = [B-2] ;
Pairs = [B-1,A-1],
dif(B,A),
when((nonvar(B),nonvar(A)),compare(<,B,A)) ;
Pairs = [A-1,B-1],
dif(B,A),
when((nonvar(B),nonvar(A)),compare(>,B,A)).
吻安 2025-01-25 14:42:53

一个可能的解决方案

count(L,LC):-
    findall(X,member(X,L),LX),
    sort(LX,LS),
    maplist(get_count(L),LS,C),
    maplist(pair,LS,C,LC).

pair(X,Y,X-Y).
get_count(L,El,N):-
    findall(X,nth0(X,L,El),LN),
    length(LN,N).

?- A= [1,2,1,4], count(A,B).
A = [1, 2, 1, 4],
B = [1-2, 2-1, 4-1]

A possible solution

count(L,LC):-
    findall(X,member(X,L),LX),
    sort(LX,LS),
    maplist(get_count(L),LS,C),
    maplist(pair,LS,C,LC).

pair(X,Y,X-Y).
get_count(L,El,N):-
    findall(X,nth0(X,L,El),LN),
    length(LN,N).

?- A= [1,2,1,4], count(A,B).
A = [1, 2, 1, 4],
B = [1-2, 2-1, 4-1]
狼亦尘 2025-01-25 14:42:53

在 SWI-Prolog 中,您还可以使用 clumped/2如下:

% count(+List, -Pairs)

  count(List, Pairs) :-
      msort(List, Sorted),
      clumped(Sorted, Pairs).

示例:

?- count([9, 9, 2, 2, 1], P).
P = [1-1, 2-2, 9-2].

?- count([X,Y,X,X,Y,Z,X,Z,W,Z], P).
P = [X-4, Y-2, Z-3, W-1].

In SWI-Prolog, you can also use clumped/2 as follows:

% count(+List, -Pairs)

  count(List, Pairs) :-
      msort(List, Sorted),
      clumped(Sorted, Pairs).

Examples:

?- count([9, 9, 2, 2, 1], P).
P = [1-1, 2-2, 9-2].

?- count([X,Y,X,X,Y,Z,X,Z,W,Z], P).
P = [X-4, Y-2, Z-3, W-1].
~没有更多了~
我们使用 Cookies 和其他技术来定制您的体验包括您的登录状态等。通过阅读我们的 隐私政策 了解更多相关信息。 单击 接受 或继续使用网站,即表示您同意使用 Cookies 和您的相关数据。
原文