How to write a predicate minmax(L, X, Y) to find out min value of X and max value of Y in list of integer L.
Example:
?- minmax([1, -10, 1, 0, 7, 7], X, Y).
X = -10, Y = 7.
Let's define list_minnum_maxnum/3
like list_minnum/2
:
list_minnum_maxnum([E|Es],Min,Max) :-
V is E,
list_minnum0_minnum_maxnum0_maxnum(Es,V,Min,V,Max).
list_minnum0_minnum_maxnum0_maxnum([] ,Min ,Min,Max ,Max).
list_minnum0_minnum_maxnum0_maxnum([E|Es],Min0,Min,Max0,Max) :-
V is E,
Min1 is min(Min0,V),
Max1 is max(Max0,V),
list_minnum0_minnum_maxnum0_maxnum(Es,Min1,Min,Max1,Max).
Sample query as given by the OP:
?- list_minnum_maxnum([1,-10,1,0,7,7], Min,Max).
Min = -10,
Max = 7.
Note that this implementation of list_minnum_maxnum/3
works with all kinds of numbers.
?- list_minnum_maxnum([1,-10,1,0,7.2,7,7], Min,Max).
Min = -10,
Max = 7.2.
If you only care about handling integers, use clpfd!
:- use_module(library(clpfd)).
We define list_zmin_zmax/3
as follows:
list_zmin_zmax([E|Es],Min,Max) :-
V #= E,
list_zmin0_zmin_zmax0_zmax(Es,V,Min,V,Max).
list_zmin0_zmin_zmax0_zmax([] ,Min ,Min,Max ,Max).
list_zmin0_zmin_zmax0_zmax([E|Es],Min0,Min,Max0,Max) :-
V #= E,
Min1 #= min(Min0,V),
Max1 #= max(Max0,V),
list_zmin0_zmin_zmax0_zmax(Es,Min1,Min,Max1,Max).
Same sample use as before:
?- list_zmin_zmax([1,-10,1,0,7,7], Min,Max).
Min = -10,
Max = 7.
OK! What about support for non-integer numbers?
?- list_zmin_zmax([1,-10,1,0,7.2,7,7], Min,Max).
ERROR: Domain error: `clpfd_expression' expected, found `7.2'
We expected getting an error, we got an error...
Note that thanks to clpfd, we can run more general queries, too!
?- list_zmin_zmax([A,B], Min,Max).
A #>= Min, Max #>= A, Min #= min(A,B),
B #>= Min, Max #>= B, Max #= max(A,B).
As noted, you need to iterate over the list, accumulating the min and max values as you go. So, assuming that you have to write this from scratch, the first thing you need to do is decompose the problem into simple steps:
That leads to a min/3
and max/3
, thus:
min(X,X,X).
min(X,Y,X) :- X < Y .
min(X,Y,Y) :- X > Y .
max(X,X,X).
max(X,Y,X) :- X > Y .
max(X,Y,Y) :- X < Y .
For your purposes here, one could even combine them into a single predicate, if you liked:
rank( X , X , X , X ) .
rank( X , Y , X , Y ) :- X < Y .
rank( X , Y , Y , X ) :- X > Y .
A pretty typical programming pattern in Prolog is to have a simple public API predicate that invokes a private "worker" predicate that does the actual work. Often the worker predicate will carry temporary "accumulator" variables that simplify the job. Your public predicate might look like:
minmax([X|Xs],Min,Max) :- minmax_scan( Xs , X , X , Min , Max ).
Here, your public API predicate accepts a non-empty list, seeding the min/max accumulators the worker predicate uses with the head of the list, then calling the worker predicate with the tail of the list.
Your worker predicate then might look like this:
% if the list is empty, we've solved the puzzle, right?
minmax_scan( [] , Min , Max , Min , Max ) .
% if the list is non-empty, we need to compare its head to
% the current value for min/max to determine the new values for min/max
% (which might be the same), and then recurse down on the tail of the list
minmax_scan( [X|Xs] , CurrMin , CurrMax , Min , Max ) :-
min( X , CurrMin , NextMin ) ,
max( X , CurrMax , NextMax ) ,
minmax_scan( Xs , NextMin , NextMax , Min , Max )
.
Easy!
take the first value from the list, then examine each other element of the list, selecting lower/higher values as temporary min/max.
When at the end of list, you have both...
minmax([First|Rest], Min, Max) :-
minmax(Rest, First, First, Min, Max).
minmax([], Min, Max, Min, Max).
minmax([Value|Ns], MinCurr, MaxCurr, Min, Max) :-
....
minmax(Ns, MinNext, MaxNext, Min, Max).
I'll let you write the tests before the recursive call (i.e. fill the dots!)
edit just to point out library(aggregate), available in several Prolog systems:
1 ?- [user].
minmax(L, X, Y) :- aggregate( (min(E), max(E)), member(E, L), (X, Y) ).
|:
true.
2 ?- minmax([1, -10, 1, 0, 7, 7], X, Y).
X = -10,
Y = 7.
Here's something convoluted and a bit complex.
is_minmax(A,B-D,C-E) :-
D is min(...),
E is max(...) .
pair(A,B,A-B).
minmax(L,MIN,MAX) :-
L=[A|_], length(L,N), N2 is N-1,
length(L2,N2), append(L2,[MIN],L22),
length(L3,N2), append(L3,[MAX],L33),
maplist(pair, [A|L2], L22, KL2),
maplist(pair, [A|L3], L33, KL3),
maplist(is_minmax, L, KL2, KL3).
(works in SWI Prolog). Try to figure out what to write in place of dots ...
.