
% generic shape constructor,
%   e.g. call using
%      shape(circle, [X,Y,R], S).
shape(Stype,Data,S) :-
   shapeType(Stype),        % make sure it is a valid shape type
   S =.. [Stype | Data],    % create the constructor 
   S.                       % invoke it

% generic dispatcher for shape methods, 
%   e.g. call using
%       shape(area,circle(X,Y,R),Area).
shape(Method,Shape,Result) :-
   functor(Shape,Stype,_),  % get the shape type from Shape
   shapeType(Stype),            % make sure it is a supported type
   shapeMethod(Method),         % make sure it is a supported method
   Cmd =.. [ Stype, Method, Shape, Result ],  % build the method call
   Cmd.                         % invoke the method call

% list the methods that all shapes must support
shapeMethod(area).

% list the supported shapes
shapeType(circle).

% circle constructor
circle(X,Y,R) :-
   number(X), number(Y),  % X,Y coordinates must be numeric
   number(R), R > 0.      % radius must be positive

% area method for circle
circle(area, circle(X,Y,R), Area) :-
   circle(X,Y,R),          % check the validity using the constructor
   A is 3.1415 * R * R,    % calculate the area
   A = Area.               % ensure Area matches the calculated value

