1:- module(
    2  pure,
    3  [
    4    '='/3,                   % ?X, ?Y, ?Truth
    5    if_/3,                   % :If_1, :Then_0, :Else_0
    6    list_item_isMember/3,    % ?L, ?X, ?Truth
    7    list_list_intersection/3 % ?Xs, ?Ys, ?Zs
    8  ]
    9).   10:- reexport(library(dif)).

Pure predicates

Some pure predicates that I learned from others.

*/

   18:- meta_predicate
   19    if_(1, 0, 0).
 =(?X, ?Y, ?Truth)
   27=(X, Y, R) :- X == Y,    !, R = true.
   28=(X, Y, R) :- ?=(X, Y),  !, R = false. % syntactically different
   29=(X, Y, R) :- X \= Y,    !, R = false. % semantically different
   30=(X, Y, R) :- R == true, !, X = Y.
   31=(X, X, true).
   32=(X, Y, false) :-
   33   dif(X, Y).
 if_(:If_1, :Then_0, :Else_0)
   39if_(C_1, Then_0, Else_0) :-
   40  call(C_1, Truth),
   41  functor(Truth, _, 0), % safety check
   42  (Truth == true -> Then_0 ; Truth == false, Else_0).
 list_item_isMember(?L, ?X, ?Truth)
   48list_item_isMember([], _, false).
   49list_item_isMember([X|Xs], E, Truth) :-
   50  if_(E = X, Truth = true, list_item_isMember(Xs, E, Truth)).
 list_list_intersection(?Xs, ?Ys, ?Zs)
   56list_list_intersection([], _, []).
   57list_list_intersection([A|As], Bs, Cs1) :-
   58  if_(list_item_isMember(Bs, A), Cs1 = [A|Cs], Cs1 = Cs),
   59  list_list_intersection(As, Bs, Cs)