How to sort a list of strings "a", "bcd", "ef", and "ghij" in descending order of length?

506 Views Asked by At

Paul Graham asked:

In your favorite programming language, how do you sort a list of the strings "a", "bcd", "ef", and "ghij" in descending order of length?

One proposed solution was:

tag_negative_len(Str, NegLen-Str) :-
  atom_length(Str, StrLen),
  NegLen is -1*StrLen.

rem_tag(_-Val, Val).

sort_desc_len(StrLs, Sorted) :-
  maplist(tag_negative_len, StrLs, TaggedLs),
  keysort(TaggedLs, SortedTaggedLs),
  maplist(rem_tag, SortedTaggedLs, Sorted).

I assume that the above code was written for ISO Prolog, because it doesn't make use of implementation-specific features. Example usage:

?- sort_desc_len(["a", "bcd", "ef", "ghij"], L).
L = ["ghij", "bcd", "ef", "a"].

I would have solved it in a similar way. However, the solution is extremely verbose (as compared to the one or two-liners of other programming languages), and pollutes the program with helper/auxiliary predicates. Is there a better way to solve the problem in ISO Prolog?

3

There are 3 best solutions below

3
CapelliC On
sort_desc_len(L,S) :-
  findall(N-T,(member(T,L),atom_length(T,M),N is -M),LT),
  keysort(LT,ST),
  findall(T,member(_-T,ST),S).

that is, findall/3 implements the closures by means of member/2. setof/3 would allow to merge the first findall and the keysort calls, but it would remove duplicates...

Note that atom_length/2 could not work with an ISO compliant processor. Double quoted strings are lists of codes, not atoms.

Anyway, I agree Prolog is rather verbose when it come to functional programming. I think the cause is that it has a relational data model.

5
David Tonhofer On

I'm just thinking functionally:

Apparently predsort is the predicate to use. This is actually not ISO, but from library(list)

my_cmp(X,L,R) :- 
   atom_length(L,Llen),atom_length(R,Rlen),
   ((Llen < Rlen) -> X = '>' ;
    (Llen > Rlen) -> X = '<' ;
    X = '=').

sort_desc_len(L,S) :- predsort(my_cmp,L,S).

Depending on how atom_length/2 is computed (i.e. depending on whether one just needs to retrieve a hidden length value rather than traverse the string of the atom), this may be rather fast.

:- begin_tests(sort_desc_len).
test(empty)      :- sort_desc_len([],[]).
test(nop)        :- sort_desc_len([aaa,bb,c],[aaa,bb,c]).
test(reverse)    :- sort_desc_len([a,bb,ccc],[ccc,bb,a]).
test(duplicates) :- sort_desc_len([a,bb,bb,ccc],[ccc,bb,a]).
test(stability)  :- sort_desc_len([i,j,k],[i,j,k]).
test(random)     :- sort_desc_len([a,xx,fg,hhh,jk],[hhh,xx,fg,jk,a]).
test(exercise)   :- sort_desc_len([a,bcd,ef,ghij],[ghij,bcd,ef,a]).
:- end_tests(sort_desc_len).

So, I Herd U Liek Tests...

?- run_tests(sort_desc_len).
% PL-Unit: sort_desc_len ....
ERROR: user://4:87:
        test stability: failed

ERROR: user://4:88:
        test random: failed

. done
% 2 tests failed
% 5 tests passed

Sadly, predsort/3 removes duplicates. There absolutely should be a predsort/4 indicating whether duplicates should be goners or not.

?- sort_desc_len([i,j,k],X).
X = [i].

?- sort_desc_len([a,xx,fg,hhh,jk],X).
X = [hhh, xx, a].

FAIL.

Addendum

Less noisy using compare/3 as suggested in the comment by repeat.

N.B. compare/3 call with exchanged left and right lengths.

my_cmp(X,L,R) :- 
   atom_length(L,Llen),
   atom_length(R,Rlen),
   compare(X,Rlen,Llen).

sort_desc_len(L,S) :- predsort(my_cmp,L,S).
?- run_tests(sort_desc_len).
% PL-Unit: sort_desc_len ....
ERROR: user://1:20:
        test stability: failed

ERROR: user://1:21:
        test random: failed

. done
% 2 tests failed
% 5 tests passed
false.
1
Paulo Moura On

My reply on Twitter to Paul Graham question uses the Logtalk list::msort/3 library predicate and a lambda expression calling the ISO Prolog standard predicate compare/3 and the de facto standard length/2 predicate. Assuming the double_quotes flag is set to codes (the most portable setting; in fact, the only setting some Prolog systems support):

| ?- {types(loader)}.
yes

| ?- list::msort(
         [Order, List1, List2]>>(
             length(List1, N1), M1 is -N1,
             length(List2, N2), M2 is -N2,
             compare(Order, M1, M2)
         ),
         ["a", "bcd"",cd", "ef", "ghij"],
         Sorted
     ).
Sorted = [[98,99,100,34,44,99,100],[103,104,105,106],[101,102],[97]]
yes

When running on supported backend Prolog compilers that don't provide the length/2 predicate as a built-in predicate, we can use instead:

| ?- {types(loader)}.
yes

| ?- list::msort(
         [Order, List1, List2]>>(
             list::length(List1, N1), M1 is -N1,
             list::length(List2, N2), M2 is -N2,
             compare(Order, M1, M2)
         ),
         ["a", "bcd"",cd", "ef", "ghij"],
         Sorted
     ).
Sorted = [[98,99,100,34,44,99,100],[103,104,105,106],[101,102],[97]]
yes

Funny enough, this is one of the most portable solutions provided so far, working on 12 Prolog systems (i.e. in all Logtalk supported systems).

As @CapelliC remarked, a relational language will always provide a more verbose solution compared with a functional language.