1
votes

I am trying to calculate cousin relationship in the format P'th cousin Qth removed. For example, In this picture below,

Thomas and Zack are cousins twice removed.

Thomas and Nikolay are second cousins once removed

Thomas and Saul are third cousins zero'th removed

Figure 1

So far I have a code like this that, finds the cousins:

ancestor(X,Z):-parent(X,Z).

ancestor(X,Z):-parent(X,Y), ancestor(Y,Z).

cousins(Child1, Child2) :-
  ancestor(Y1,Child1),
  ancestor(Y1,Child2),
  Child1 \= Child2.

My logic is as long as Child1 and Child2 shares a common ancestor they are cousins.

The issue I am having is in trying to find out whether they are first cousins, or second cousins, or third cousins etc and whether they are once removed, twice removed, or thrice removed.

Any suggestion or hints on how I could solve this problem would be greatly helpful.

Thanks!

1
What behavior do you need? A predicate which returns "Nth" cousin "Rth" removed given two names? A predicate that works in all directions (e.g. get all Nth cousins 2 removed)? - Fatalize

1 Answers

1
votes

I think I got this right.

You will need the CLP(FD) library to make this work. Simply write :- use_module(library(clpfd)). at the beginning of your program.

cousins_nth_removed/4

The first two arguments are atoms representing the persons' names. The third argument (in [1,sup)) represents the first/second/third/... cousins relationship, while the fourth argument (in [0,sup)) represents the zeroth/once/twice/... removed relationship

cousins_nth_removed(C1, C2, 1, 0) :-             % First cousins, zeroth removed
    dif(C1, C2),
    dif(P1, P2),                                 %   They have different parents
    parent_child(P1, C1),
    parent_child(P2, C2),
    parent_child(GP, P1),                        %   Their parents have the same parent GP
    parent_child(GP, P2).
cousins_nth_removed(C1, C2, N, 0) :-             % Nth cousins, zeroth removed
    N #> 1,
    dif(C1, C2),
    children_removed_ancestor(C1, C2, R, R),     %   They are both R generations away from
    dif(P1, P2),                                 %     their oldest common ancestor
    parent_child(P1, C1),
    parent_child(P2, C2),
    M #= N - 1,                                  %   Their parents are N-1th cousins
    cousins_nth_removed(P1, P2, M, 0).           %     zeroth removed        
cousins_nth_removed(C1, C2, N, R) :-             % Nth cousins, Rth removed
    R #> 0,
    dif(C1, C2),
    children_removed_ancestor(C1, C2, R1, R2),   %   R is the difference of the distances
    R #= abs(R2 - R1),                           %     between each cousin and their oldest
    S #= R - 1,                                  %     common ancestor
    (   R1 #= R2,                                %   R = 0 -> Zeroth removed, second rule
        cousins_nth_removed(C1, C2, N, 0)
    ;   R1 #> R2,                                %   C1 is younger than C2
        parent_child(P1, C1),                    %     -> C2 is Nth cousin R-1th removed
        cousins_nth_removed(P1, C2, N, S)        %     with the parent of C1
    ;   R1 #< R2,                                %   C2 is younger than C1
        parent_child(P2, C2),                    %     -> C1 is Nth cousin R-1th removed
        cousins_nth_removed(C1, P2, N, S)        %     with the parent of C2
    ).

children_removed_ancestor/4

The name isn't ideal, but this predicate is basically used to retrieve the generation gaps of two persons to their oldest common ancestor.

children_removed_ancestor(C1, C2, R1, R2) :-
    child_removed_oldest_ancestor(C1, R1, A), 
    child_removed_oldest_ancestor(C2, R2, A).

child_removed_oldest_ancestor/3

This predicate retrieves the generation gap between a person and their oldest ancestor.

child_removed_oldest_ancestor(C, 0, C) :-         %  The ancestor of all
    \+ parent_child(_, C).                        %   They have no parent   
child_removed_oldest_ancestor(C, N, A) :-
    N #> 0,
    parent_child(P, C),
    M #= N - 1,
    child_removed_oldest_ancestor(P, M, A).

Some queries

?- cousins_nth_removed(thomas, zack, N, R).      % Your example
N = 1,
R = 2 ;
false.


?- cousins_nth_removed(thomas, nikolay, N, R).   % Your example
N = 2,
R = 1 ;
false.


?- cousins_nth_removed(thomas, saul, N, R).      % Your example
N = 3,
R = 0 ;
false.


?- cousins_nth_removed(thomas, C, N, R).         % All cousins of thomas
C = farah,
N = 1,
R = 0 ;
C = ping,
N = 2,
R = 0 ;
C = william,
N = 3,
R = 0 ;
C = saul,
N = 3,
R = 0 ;
C = sean,
N = R, R = 1 ;
C = steven,
N = R, R = 1 ;
C = zack,
N = 1,
R = 2 ;
C = kyle,
N = 2,
R = 1 ;
C = nikolay,
N = 2,
R = 1 ;
C = wei,
N = 2,
R = 1 ;
false.


?- cousins_nth_removed(C1, C2, 3, 0).             % All third cousins zeroth removed
C1 = ping,
C2 = william ;
C1 = ping,
C2 = saul ;
C1 = farah,
C2 = william ;
C1 = farah,
C2 = saul ;
C1 = ignat,
C2 = william ;
C1 = ignat,
C2 = saul ;
C1 = thomas,
C2 = william ;
C1 = thomas,
C2 = saul ;
C1 = william,
C2 = ping ;
C1 = william,
C2 = farah ;
C1 = william,
C2 = ignat ;
C1 = william,
C2 = thomas ;
C1 = saul,
C2 = ping ;
C1 = saul,
C2 = farah ;
C1 = saul,
C2 = ignat ;
C1 = saul,
C2 = thomas ;
false.

Overall program

:- use_module(library(clpfd)).

parent_child(leila,min).
parent_child(leila,seema).
parent_child(min,ali).
parent_child(min,jesse).
parent_child(min,john).
parent_child(ali,sean).
parent_child(ali,steven).
parent_child(sean,ping).
parent_child(jesse,dallas).
parent_child(jesse,mustafa).
parent_child(dallas,farah).
parent_child(mustafa,ignat).
parent_child(mustafa,thomas).
parent_child(seema,zack).
parent_child(zack,kyle).
parent_child(zack,nikolay).
parent_child(zack,wei).
parent_child(kyle,william).
parent_child(nikolay,saul).


cousins_nth_removed(C1, C2, 1, 0) :-
    dif(C1, C2),
    dif(P1, P2),
    parent_child(P1, C1),
    parent_child(P2, C2),
    parent_child(GP, P1),
    parent_child(GP, P2).
cousins_nth_removed(C1, C2, N, 0) :-
    N #> 1,
    dif(C1, C2),
    children_removed_ancestor(C1, C2, R, R),
    dif(P1, P2),
    parent_child(P1, C1),
    parent_child(P2, C2),
    M #= N - 1,
    cousins_nth_removed(P1, P2, M, 0).
cousins_nth_removed(C1, C2, N, R) :-
    R #> 0,
    dif(C1, C2),
    children_removed_ancestor(C1, C2, R1, R2),
    R #= abs(R2 - R1),
    S #= R - 1,
    (   R1 #= R2,
        cousins_nth_removed(C1, C2, N, 0)
    ;   R1 #> R2,
        parent_child(P1, C1),
        cousins_nth_removed(P1, C2, N, S)
    ;   R1 #< R2,
        parent_child(P2, C2),
        cousins_nth_removed(C1, P2, N, S)
    ).

children_removed_ancestor(C1, C2, R1, R2) :-
    child_removed_oldest_ancestor(C1, R1, A), 
    child_removed_oldest_ancestor(C2, R2, A).

child_removed_oldest_ancestor(C, 0, C) :-
    \+ parent_child(_, C).
child_removed_oldest_ancestor(C, N, A) :-
    N #> 0,
    parent_child(P, C),
    M #= N - 1,
    child_removed_oldest_ancestor(P, M, A).

I now hate genealogical trees.