Skip to content

Commit

Permalink
MODIFIED: Use SSU rules for some of the library(lists) predicates:
Browse files Browse the repository at this point in the history
max_member/2, min_member/2, sum_list/2, max_list/2, min_list/2, intersection/3,
union/3, subset/2 and subtract/3.   This causes errors if the input arguments
are non-lists or insufficiently instantiated.
  • Loading branch information
JanWielemaker committed Feb 10, 2021
1 parent c84c1ca commit c179126
Showing 1 changed file with 41 additions and 36 deletions.
77 changes: 41 additions & 36 deletions library/lists.pl
Expand Up @@ -543,8 +543,9 @@
max_member(Max, [H|T]) :-
max_member_(T, H, Max).

max_member_([], Max, Max).
max_member_([H|T], Max0, Max) :-
max_member_([], Max0, Max) =>
Max = Max0.
max_member_([H|T], Max0, Max) =>
( H @=< Max0
-> max_member_(T, Max0, Max)
; max_member_(T, H, Max)
Expand All @@ -562,8 +563,9 @@
min_member(Min, [H|T]) :-
min_member_(T, H, Min).

min_member_([], Min, Min).
min_member_([H|T], Min0, Min) :-
min_member_([], Min0, Min) =>
Min = Min0.
min_member_([H|T], Min0, Min) =>
( H @>= Min0
-> min_member_(T, Min0, Min)
; min_member_(T, H, Min)
Expand All @@ -581,8 +583,9 @@
sum_list(Xs, Sum) :-
sum_list(Xs, 0, Sum).

sum_list([], Sum, Sum).
sum_list([X|Xs], Sum0, Sum) :-
sum_list([], Sum0, Sum) =>
Sum = Sum0.
sum_list([X|Xs], Sum0, Sum) =>
Sum1 is Sum0 + X,
sum_list(Xs, Sum1, Sum).

Expand All @@ -596,8 +599,9 @@
max_list([H|T], Max) :-
max_list(T, H, Max).

max_list([], Max, Max).
max_list([H|T], Max0, Max) :-
max_list([], Max0, Max) =>
Max = Max0.
max_list([H|T], Max0, Max) =>
Max1 is max(H, Max0),
max_list(T, Max1, Max).

Expand All @@ -612,8 +616,9 @@
min_list([H|T], Min) :-
min_list(T, H, Min).

min_list([], Min, Min).
min_list([H|T], Min0, Min) :-
min_list([], Min0, Min) =>
Min = Min0.
min_list([H|T], Min0, Min) =>
Min1 is min(H, Min0),
min_list(T, Min1, Min).

Expand Down Expand Up @@ -709,15 +714,14 @@
%
% @see ord_intersection/3.

intersection([], _, []) :- !.
intersection([X|T], L, Intersect) :-
memberchk(X, L),
!,
Intersect = [X|R],
intersection(T, L, R).
intersection([_|T], L, R) :-
intersection(T, L, R).

intersection([], _, Set) =>
Set = [].
intersection([X|T], L, Intersect) =>
( memberchk(X, L)
-> Intersect = [X|R],
intersection(T, L, R)
; intersection(T, L, Intersect)
).

%! union(+Set1, +Set2, -Set3) is det.
%
Expand All @@ -728,14 +732,14 @@
%
% @see ord_union/3

union([], L, L) :- !.
union([H|T], L, R) :-
memberchk(H, L),
!,
union(T, L, R).
union([H|T], L, [H|R]) :-
union(T, L, R).

union([], L0, L) =>
L = L0.
union([H|T], L, Union) =>
( memberchk(H, L)
-> union(T, L, Union)
; Union = [H|R],
union(T, L, R)
).

%! subset(+SubSet, +Set) is semidet.
%
Expand All @@ -746,8 +750,8 @@
%
% @see ord_subset/2.

subset([], _) :- !.
subset([E|R], Set) :-
subset([], _) => true.
subset([E|R], Set) =>
memberchk(E, Set),
subset(R, Set).

Expand All @@ -761,10 +765,11 @@
%
% @see ord_subtract/3.

subtract([], _, []) :- !.
subtract([E|T], D, R) :-
memberchk(E, D),
!,
subtract(T, D, R).
subtract([H|T], D, [H|R]) :-
subtract(T, D, R).
subtract([], _, R) =>
R = [].
subtract([E|T], D, R) =>
( memberchk(E, D)
-> subtract(T, D, R)
; R = [E|R1],
subtract(T, D, R1)
).

1 comment on commit c179126

@JanWielemaker
Copy link
Member Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

This commit has been mentioned on SWI-Prolog. There might be relevant details there:

https://swi-prolog.discourse.group/t/ann-swi-prolog-8-3-19/3587/6

Please sign in to comment.