I have a list like this:
L = [range(2,3), range(5,6), range(10,9), range(-2,-30), range(-5,-30)]
Now, I need to make the term range(-5,-30)
the first element of this list, because it's the term with the lowest Y
, in the case that 2 terms has the lowest Y
, I'll choose the one with the lowest X
.
I don't know how to do it with Prolog, I tried something like:
find_n_make_first([F,S|T]) :-
F =.. [_,Fx,Fy],
S =.. [_,Sx,Sy],
( Sy<Fy ->
find_n_make_first([S,F|T])
; Fy<Sy ->
find_n_make_first([F,S|T])
; Fy = Sy ->
( Sx<Fx ->
find_n_make_first([S,F|T])
; Fx<Sx ->
find_n_make_first([F,S|T])
)
).
But it isn't working.
Actually, your first problem is to understand how such a definition would be used. Always start with imagining that you have already a working definition. You will learn there the most important part about relations: In relations there are no implicit "return values". You need to define them separately. So in your case this would be:
?- list_sortedby2([range(2,3),range(10,9),range(-2,-30),range(-5,-30)], Us).
Us = [range(-5,-30),range(-2,-30),range(2,3),range(10,9)].
Only then start to define it!
:- use_module(library(lambda)).
list_sortedby2(Ts, Us) :-
must_be_ground(Ts),
maplist(\T^(A2+T)^arg(2,T,A2), Ts, A2Ts), % or map1(Ts, A2Ts)
sort(A2Ts, A2Us),
maplist(\ (_+U)^U^true, A2Us, Us). % or map2(A2Us, Us)
must_be_ground(Ss) :-
( ground(Ss) -> true
; throw(error(instantiation_error,_))
).
In place of maplist/3
and λ, you could also write manually:
map1([], []).
map1([T|Ts], [A2+T|A2Ts]) :-
arg(2, T, A2),
map1(Ts, A2Ts).
map2([], []).
map2([_+U|A2Us], [U|Us]) :-
map2(A2Us, Us).
With an afterthought, there is something else: Better replace the goal arg(2, T, A2)
by ( T = range(_, A2) )
, since you are only interested in structures range/2
. In this manner, list_sortedby2([f(1,2)], Us)
fails which is a much safer way to handle an unexpected case. (It would be even safer to produce a type error, but at least it does not succeed.)