Prolog, find minimum in a list
Asked Answered
S

14

20

in short: How to find min value in a list? (thanks for the advise kaarel)

long story:

I have created a weighted graph in amzi prolog and given 2 nodes, I am able to retrieve a list of paths. However, I need to find the minimum value in this path but am unable to traverse the list to do this. May I please seek your advise on how to determine the minimum value in the list?

my code currently looks like this:

arc(1,2).
arc(2,3).
arc(3,4).
arc(3,5).
arc(3,6).
arc(2,5).
arc(5,6).
arc(2,6).

path(X,Z,A) :- 
 (arc(X,Y),path(Y,Z,A1),A is A1+1;arc(X,Z), A is 1).

thus, ' keying findall(Z,path(2,6,Z),L).' in listener allows me to attain a list [3,2,2,1]. I need to retrieve the minimum value from here and multiply it with an amount. Can someone please advise on how to retrieve the minimum value? thanks!

Schneider answered 19/10, 2010 at 3:6 Comment(1)
Please replace the text of your question by a single sentence "How to determine the smallest number in a list?" ;)Diazo
L
29

It is common to use a so-called "lagged argument" to benefit from first-argument indexing:

list_min([L|Ls], Min) :-
    list_min(Ls, L, Min).

list_min([], Min, Min).
list_min([L|Ls], Min0, Min) :-
    Min1 is min(L, Min0),
    list_min(Ls, Min1, Min).

This pattern is called a fold (from the left), and foldl/4, which is available in recent SWI versions, lets you write this as:

list_min([L|Ls], Min) :- foldl(num_num_min, Ls, L, Min).

num_num_min(X, Y, Min) :- Min is min(X, Y).


Notice though that this cannot be used in all directions, for example:

?- list_min([A,B], 5).
is/2: Arguments are not sufficiently instantiated

If you are reasoning about integers, as seems to be the case in your example, I therefore recommend you use CLP(FD) constraints to naturally generalize the predicate. Instead of (is)/2, simply use (#=)/2 and benefit from a more declarative solution:

:- use_module(library(clpfd)).

list_min([L|Ls], Min) :- foldl(num_num_min, Ls, L, Min).

num_num_min(X, Y, Min) :- Min #= min(X, Y).

This can be used as a true relation which works in all directions, for example:

?- list_min([A,B], 5).

yielding:

A in 5..sup,
5#=min(B, A),
B in 5..sup.
Lippi answered 19/10, 2010 at 7:30 Comment(0)
F
18

This looks right to me (from here).

min_in_list([Min],Min).                 % We've found the minimum

min_in_list([H,K|T],M) :-
    H =< K,                             % H is less than or equal to K
    min_in_list([H|T],M).               % so use H

min_in_list([H,K|T],M) :-
    H > K,                              % H is greater than K
    min_in_list([K|T],M).               % so use K
Forb answered 19/10, 2010 at 3:25 Comment(3)
Thanks andersoj. I actually saw this code while searching online prior to submitting my qn here. Somehow, I did not understand it, now i do, thanks!Schneider
It's been years since I've thought in Prolog, but I suspect @Lippi has the readability edge on what I posted...Forb
The problem with your solution is also that you compare H and K twice, the min-function probably does not do that...Diazo
V
5
%Usage: minl(List, Minimum).
minl([Only], Only).
minl([Head|Tail], Minimum) :-
    minl(Tail, TailMin),
    Minimum is min(Head, TailMin). 

The second rule does the recursion, in english "get the smallest value in the tail, and set Minimum to the smaller of that and the head". The first rule is the base case, "the minimum value of a list of one, is the only value in the list".

Test:

| ?- minl([2,4,1],1).

true ? 

yes
| ?- minl([2,4,1],X).

X = 1 ? 

yes

You can use it to check a value in the first case, or you can have prolog compute the value in the second case.

Virulence answered 2/5, 2011 at 16:6 Comment(0)
F
3

SWI-Prolog offers library(aggregate). Generalized and performance wise.

:- [library(aggregate)].
min(L, M) :- aggregate(min(E), member(E, L), M).

edit

A recent addition was library(solution_sequences). Now we can write

min(L,M) :- order_by([asc(M)], member(M,L)), !.
max(L,M) :- order_by([desc(M)], member(M,L)), !.

Now, ready for a surprise :) ?

?- test_performance([clpfd_max,slow_max,member_max,rel_max,agg_max]).
clpfd_max:99999996
% 1,500,000 inferences, 0.607 CPU in 0.607 seconds (100% CPU, 2470519 Lips)
slow_max:99999996
% 9,500,376 inferences, 2.564 CPU in 2.564 seconds (100% CPU, 3705655 Lips)
member_max:99999996
% 1,500,009 inferences, 1.004 CPU in 1.004 seconds (100% CPU, 1494329 Lips)
rel_max:99999996
% 1,000,054 inferences, 2.649 CPU in 2.648 seconds (100% CPU, 377588 Lips)
agg_max:99999996
% 2,500,028 inferences, 1.461 CPU in 1.462 seconds (100% CPU, 1710732 Lips)
true 
with these definitions:

```erlang
:- use_module(library(clpfd)).

clpfd_max([L|Ls], Max) :- foldl([X,Y,M]>>(M #= max(X, Y)), Ls, L, Max).

slow_max(L, Max) :-
   select(Max, L, Rest), \+ (member(E, Rest), E @> Max).

member_max([H|T],M) :-
    member_max(T,N), ( \+ H@<N -> M=H ; M=N ).
member_max([M],M).

rel_max(L,M) :-
    order_by([desc(M)], member(M,L)), !.

agg_max(L,M) :-
    aggregate(max(E), member(E,L), M).

test_performance(Ps) :-
    test_performance(Ps,500 000,_).
test_performance(Ps,N_Ints,Result) :-
    list_of_random(N_Ints,1,100 000 000,Seq),
    maplist({Seq}/[P,N]>>time((call(P,Seq,N),write(P:N))),Ps,Ns),
    assertion(sort(Ns,[Result])).

list_of_random(N_Ints,L,U,RandomInts) :-
    length(RandomInts,N_Ints),
    maplist({L,U}/[Int]>>random_between(L,U,Int),RandomInts).

clpfd_max wins hands down, and to my surprise, slow_max/2 turns out to be not too bad...

Firebug answered 7/12, 2011 at 11:30 Comment(0)
D
2

SWI-Prolog has min_list/2:

min_list(+List, -Min)
    True if Min is the smallest number in List.

Its definition is in library/lists.pl

min_list([H|T], Min) :-
    min_list(T, H, Min).

min_list([], Min, Min).
min_list([H|T], Min0, Min) :-
    Min1 is min(H, Min0),
    min_list(T, Min1, Min).
Diazo answered 19/10, 2010 at 6:26 Comment(0)
O
2

This program may be slow, but I like to write obviously correct code when I can.

smallest(List,Min) :- sort(List,[Min|_]).

Octuple answered 26/2, 2019 at 3:35 Comment(1)
Yes, but what about input lists that contain logical variables?Cirilla
S
2

This is ok for me :

minimumList([X], X).        %(The minimum is the only element in the list)

minimumList([X|Q], M) :-    % We 'cut' our list to have one element, and the rest in Q
 minimumList(Q, M1),         % We call our predicate again with the smallest list Q, the minimum will be in M1
 M is min(M1, X).            % We check if our first element X is smaller than M1 as we unstack our calls

Sassanid answered 13/3, 2019 at 13:57 Comment(0)
V
1

Similar to andersoj, but using a cut instead of double comparison:

min([X], X).

min([X, Y | R], Min) :-
    X < Y, !,
    min([X | R], Min).

min([X, Y | R], Min) :-
   min([Y | R], Min).
Vacuum answered 6/5, 2012 at 19:7 Comment(0)
S
1

Solution without "is".

min([],X,X).
min([H|T],M,X) :- H =< M, min(T,H,X).
min([H|T],M,X) :- M < H, min(T,M,X).
min([H|T],X) :- min(T,H,X).
Slushy answered 3/8, 2012 at 8:57 Comment(1)
min([1,1],X). should succeed, but it fails.Conoscenti
S
0

thanks for the replies. been useful. I also experimented furthur and developed this answer:

% if list has only 1 element, it is the smallest. also, this is base case.
min_list([X],X).

min_list([H|List],X) :-
min_list(List,X1), (H =< X1,X is H; H > X1, X is X1).

% recursively call min_list with list and value,
% if H is less than X1, X1 is H, else it is the same. 

Not sure how to gauge how good of an answer this is algorithmically yet, but it works! would appreciate any feedback nonetheless. thanks!

Schneider answered 19/10, 2010 at 14:58 Comment(0)
E
0
min([Second_Last, Last], Result):-
    Second_Last < Last
 -> Result = Second_Last
 ;  Result = Last, !.

min([First, Second|Rest], Result):-
    First < Second
 -> min([First|Rest], Result)
 ;  min([Second|Rest], Result).

Should be working.

Exequies answered 7/12, 2011 at 9:28 Comment(0)
L
0

This works and seems reasonably efficient.

min_in_list([M],M).    
min_in_list([H|T],X) :-
    min_in_list(T,M),
    (H < M, X = H; X = M).   

min_list(X,Y) :- min_in_list(X,Y), !.
Laud answered 8/3, 2016 at 2:1 Comment(1)
prolog-cut has made your code lose steadfastness, which means that the code behaves logically sound with "just the right amount of instantiation", but gets logically unsound when working with terms that have too much instantiation. This is why ?- min_in_list([1,2,3],2). succeeds—it should fail!Cirilla
B
0
smallest(List,X):-
         sort(List,[X|_]).
Builtup answered 6/3, 2022 at 8:37 Comment(0)
R
-1

% find minimum in a list

min([Y],Y):-!.

min([H|L],H):-min(L,Z),H=<Z.

min([H|L],Z):-min(L,Z),H>=Z.

% so whattaya think!

Runyan answered 18/5, 2013 at 7:41 Comment(1)
It may seem elegant at first glance - however, it unfortunately is not deterministic, and can even yield more solutions than there are elements in the list. Try for example: ?- min([1,1,1,1], Min)., which yields 8 solutions. Or try ?- numlist(1, 1000, Ls), min(Ls, Min)., in SWI-Prolog and press SPACE for further solutions after it emits Min = 1 and be prepared to wait. Also, it's not tail-recursive and hence less usable for long lists: Try for example ?- numlist(1, 10_000_000, Ls), min(Ls, Min)., which yields a local stack overflow whereas other versions that are posted here don't.Lippi

© 2022 - 2024 — McMap. All rights reserved.