How to check which items on the list meet certain

2019-02-28 03:47发布

How to make a function called busLineLonger, which receives at least two parameters to decide if a bus line is longer or not?

*/This is how it works*/
* busStops(number_of_the_bus,number_of_stops)*/

/*?- busLineLonger([busStops(1,7),busStops(2,4),busStops(3,6)],5,WHICH).
* WHICH = [1,3].

Using only comparative things, like @> <@ /==@. Sorry my english

Edit... So far I've think of something like this

busLineLonger([busStops(A,B)|R],N,[_|_]):-
   N@>B,
   busLineLonger(R,N,A).

标签: prolog
2条回答
Melony?
2楼-- · 2019-02-28 04:35

Here's how you could do it using , reified test predicates, and lambda expressions.

:- use_module(library(lambda)).

First, we define the reified test predicate (>)/3 like this:

>(X,Y,Truth) :- (X > Y -> Truth=true ; Truth=false).

Next, we define three different implementations of busLineLonger/3 (named busLineLonger1/3, busLineLonger2/3, and busLineLonger3/3) in terms of the following meta-predicates: maplist/3, tfilter/3, tfiltermap/4, and tchoose/3. Of course, in the end we will only need one---but that shouldn't keep us from exploring the various options we have!

#1: based on tfilter/3 and maplist/3

Do two separate steps: 1. Select items of concern. 2. Project those items to the data of interest.

busLineLonger1(Ls0,N,IDs) :-
    tfilter(\busStops(_,L)^(L>N), Ls0,Ls1),
    maplist(\busStops(Id,_)^Id^true, Ls1, IDs).

#2: based on tfiltermap/4

Here, we use exactly the same lambda expressions as before, but we pass them both to meta-predicate tfiltermap/4. Doing so can help reduce save some resources.

busLineLonger2(Ls,N,IDs) :-
    tfiltermap(\busStops(_,L)^(L>N), \busStops(Id,_)^Id^true, Ls,IDs).

Here's how tfiltermap/4 can be implemented:

:- meta_predicate tfiltermap(2,2,?,?).
tfiltermap(Filter_2,Map_2,Xs,Ys) :-
   list_tfilter_map_list(Xs,Filter_2,Map_2,Ys).

:- meta_predicate list_tfilter_map_list(?,2,2,?).
list_tfilter_map_list([],_,_,[]).
list_tfilter_map_list([X|Xs],Filter_2,Map_2,Ys1) :-
   if_(call(Filter_2,X), (call(Map_2,X,Y),Ys1=[Y|Ys0]), Ys1=Ys0),
   list_tfilter_map_list(Xs,Filter_2,Map_2,Ys0).

#3: based on tchoose/3

Here we do not use two separate lambda expressions, but a combined one.

busLineLonger3(Ls,N,IDs) :-
    tchoose(\busStops(Id,L)^Id^(L>N), Ls,IDs).

Here's how tchoose/3 can be implemented:

:- meta_predicate tchoose(3,?,?).
tchoose(P_3,Xs,Ys) :-
   list_tchoose_list(Xs,P_3,Ys).

:- meta_predicate list_tchoose_list(?,3,?).
list_tchoose_list([],_,[]).
list_tchoose_list([X|Xs],P_3,Ys1) :-
   if_(call(P_3,X,Y), Ys1=[Y|Ys0], Ys1=Ys0),
   list_tchoose_list(Xs,P_3,Ys0).

Let's see them in action!

?- Xs = [busStops(1,7),busStops(2,4),busStops(3,6)], busLineLonger1(Xs,5,Zs).
Xs = [busStops(1, 7), busStops(2, 4), busStops(3, 6)],
Zs = [1, 3].

?- Xs = [busStops(1,7),busStops(2,4),busStops(3,6)], busLineLonger2(Xs,5,Zs).
Xs = [busStops(1, 7), busStops(2, 4), busStops(3, 6)],
Zs = [1, 3].

?- Xs = [busStops(1,7),busStops(2,4),busStops(3,6)], busLineLonger3(Xs,5,Zs).
Xs = [busStops(1, 7), busStops(2, 4), busStops(3, 6)],
Zs = [1, 3].

Done!

So... what's the bottom line?

  • Many meta-predicates are versatile and can be used in a lot of sitations similar to the one here.
  • Implementing these meta-predicates is a one time effort that is amortized quickly.
  • Many meta-predicates handle the "recursive part", which enables you to focus on actual work.
  • Often, with meta-predicates (as with regular ones), "there's more than one way to do things".
    • Depending on the concrete circumstances, using a particular meta-predicate may be better than using another one, and vice versa.
    • For this question, I think, implementation #3 (the one using tchoose/3) is best.
查看更多
三岁会撩人
3楼-- · 2019-02-28 04:37

Some things to fix in your code:

  • 3rd argument is [_|_], that is the result are free variables... doesn't make sense. You need two cases: one in which the B is greater than N and you include the result; the other in which B is less or equal than N, and you don't include that result.
  • base case is missing. what's the result when bus list is empty?

A possible solution:

busLineLonger([],_,[]).
busLineLonger([busStops(A,B)|R],N,[A|S]) :- B>N, busLineLonger(R,N,S).
busLineLonger([busStops(_,B)|R],N,S) :- B=<N, busLineLonger(R,N,S).

?- busLineLonger([busStops(1,7),busStops(2,4),busStops(3,6)],5,WHICH).
WHICH = [1, 3]
查看更多
登录 后发表回答