%------------------------------------------------------------------------------
% person(ID,    FirstName,     LastName,   Gender).
%------------------------------------------------------------------------------

person(alan,    'Alan',        'Smith',    m).
person(barbara, 'Barbara',     'Smith',    f).
person(chris,   'Christopher', 'Johnson',  m).
person(doris,   'Doris',       'Johnson',  f).
person(eric,    'Eric',        'Smith',    m).
person(fiona,   'Fiona',       'Smith',    f).
person(george,  'George',      'Johnson',  m).
person(helen,   'Helen',       'Johnson',  f).
person(ian,     'Ian',         'Smith',    m).
person(julia,   'Julia',       'Smith',    f).
person(ken,     'Kenneth',     'Smith',    m).
person(laura,   'Laura',       'Williams', f).

%------------------------------------------------------------------------------
% parent(Child, Parent).
%------------------------------------------------------------------------------

parent(eric, alan).
parent(eric, barbara).
parent(fiona, chris).
parent(fiona, doris).
parent(george, chris).
parent(george, doris).
parent(ian, eric).
parent(ian, fiona).
parent(julia, eric).
parent(julia, fiona).
parent(ken, george).
parent(ken, helen).

%------------------------------------------------------------------------------
% couple(Partner1, Partner2).
%------------------------------------------------------------------------------

couple(alan, barbara).
couple(chris, doris).
couple(eric, fiona).
couple(george, helen).
couple(ken, laura).

%------------------------------------------------------------------------------
% man(PersonID).
%------------------------------------------------------------------------------

man(X) :-
	person(X, _, _, m).

%------------------------------------------------------------------------------
% woman(PersonID).
%------------------------------------------------------------------------------

woman(X) :-
	person(X, _, _, f).


%------------------------------------------------------------------------------
% father(Child, Father).
%------------------------------------------------------------------------------

father(Child, Father) :-
	parent(Child, Father),
	man(Father).

%------------------------------------------------------------------------------
% mother(Child, Mother).
%------------------------------------------------------------------------------

mother(Child, Mother) :-
	parent(Child, Mother),
	woman(Mother).

%------------------------------------------------------------------------------
% grandparent(Child, Grandparent).
%------------------------------------------------------------------------------

grandparent(Child, Grandparent) :-
	parent(Child, Parent),
	parent(Parent, Grandparent).

%------------------------------------------------------------------------------
% married_with(Person1, Person2).
%------------------------------------------------------------------------------

married_with(X, Y) :-
	couple(X, Y).

married_with(X, Y) :-
	couple(Y, X).

%------------------------------------------------------------------------------
% ancestor(Child, Ancestor).
%------------------------------------------------------------------------------

ancestor(Child, Parent) :-
	parent(Child, Parent).

ancestor(Child, Ancestor) :-
	parent(Child, Parent),
	ancestor(Parent, Ancestor).

