1:- module(pair,
    2          [ ffst/3, ffst//3
    3          , fsnd/3, fsnd//3
    4          , dup/2, pair/3, fst/2, snd/2, is_pair/1
    5          , select_key_value/4
    6          , select_key_default_value/5
    7          , map_select_key_value/5
    8          , map_select_key_default_value/6
    9          , (&)/4
   10          , op(650,xfy,&)
   11			 ]).   12
   13:- meta_predicate fsnd(2,?,?),
   14						ffst(2,?,?),
   15                  fsnd(4,?,?,?,?),
   16						ffst(4,?,?,?,?),
   17                  &(2,2,?,?),
   18						map_select_key_value(2,+,-,+,-),
   19						map_select_key_default_value(2,+,+,-,+,-).
 is_pair(+X) is semidet
True if X is a pair.
   23is_pair(_-_).
 pair(X:A, Y:B, Z:pair(A,B)) is det
   26pair(X, Y, X-Y).
 dup(X:A, Y:pair(A,A)) is det
   29dup(X, X-X).
 fst(X:pair(A,B), Y:A) is det
   32fst(X-_, X).
 snd(X:pair(A,B), Y:B) is det
   35snd(_-Y, Y).
 ffst(+P:pred(A,B), X:pair(A,C), Y:pair(B,C)) is det
 ffst(+P:pred(A,B,S,S), X:pair(A,C), Y:pair(B,C), S1:S, S2:S) is det
Apply P to first element of pair. Two versions: one for normal use and another for use in DCG goals.
   41ffst(P,Y-X,Z-X) :- call(P,Y,Z).
   42ffst(P,Y-X,Z-X) --> call(P,Y,Z).
 fsnd(+P:pred(B,C), X:pair(A,B), Y:pair(A,C)) is det
 fsnd(+P:pred(B,C,S,S), X:pair(A,B), Y:pair(A,C), S1:S, S2:S) is det
Apply P to second element of pair. Two versions: one for normal use and another for use in DCG goals.
   48fsnd(P,X-Y,X-Z) :- call(P,Y,Z).
   49fsnd(P,X-Y,X-Z) --> call(P,Y,Z).
 &(+F:pred(A,B), +G:pred(A,C), X:A, Y:pair(B,C)) is det
Apply F and G to X and pair results.
   53&(F,G,X,Y-Z) :- call(F,X,Y), call(G,X,Z).
 map_select_key_value(+P:pred(A,B), K:C, Y:B, L1:list(pair(C,A)), L2:list(pair(C,A))) is nondet
True when L2 is L1 with an element K-X removed, and P maps X to Y.
   58map_select_key_value(P, K, Y, L1, L2) :-
   59	select(K-X, L1, L2), call(P,X,Y).
 map_select_key_default_value(+P:pred(A,B), K:C, Z:B, Y:B, L1:list(pair(C,A)), L2:list(pair(C,A))) is det
If key K exists in pair list L1, extract value associated with it and apply P to get Y. Otherwise unify default Z with Y.
   64map_select_key_default_value(P, K, Default, Y, L1, L2) :-
   65   (  select(K-X, L1, L2) -> call(P,X,Y)
   66   ;  Y=Default, L1=L2
   67   ).
 select_key_value(K:C, Y:B, L1:list(pair(C,A)), L2:list(pair(C,A))) is nondet
True when L2 is L1 with an element K-Y removed.
   71select_key_value(K, X, L1, L2) :- select(K-X, L1, L2).
 select_key_default_value(K:C, Z:B, Y:B, L1:list(pair(C,A)), L2:list(pair(C,A))) is det
If key K exists in pair list L1, extract value Y associated with it. Otherwise unify default Z with Y.
   76select_key_default_value(K, Default, X, L1, L2) :-
   77   map_select_key_default_value((=), K, Default, X, L1, L2).
   78
   79user:goal_expansion(fsnd(P,P1,P2), (P1=X-Y1, P2=X-Y2, call(P,Y1,Y2))).
   80user:goal_expansion(ffst(P,P1,P2), (P1=X1-Y, P2=X2-Y, call(P,X1,X2))).
   81user:goal_expansion(fst(P,X), P=X-_).
   82user:goal_expansion(snd(P,Y), P=_-Y).
   83user:goal_expansion(pair(X,Y,P), P=X-Y)