You selected rdb01.pl

headline:-
  wn('% -----------------------------------------------------------  %'),
  wn('%   Relational Algebra and Relational Data Base by Prolog'),
  wn('% -----------------------------------------------------------  %'),
  h0.
h0:-
  wn('%   principal predicates: '),
  wn('%    db(N,T,D) :   data base (=tuple). '),
  wn('%    display_db :  display the name of all tables. '),
  wn('%    display_table(N) :  display the contents of table. '),
  wn('% -- In each of the following rdb operations, you must sepecify '),
  wn('%  the 3rd or the last arity with a new output table name. -----  %'),
  wn('%    rdb_union(T1,T2,U) :  union of tables. '),
  wn('%    rdb_difference(T1,T2,D) :  difference of tables. '),
  wn('%    rdb_product(T1,T2,P) :  product of tables. '),
  wn('%    rdb_projection(T,A,U) :  projection of tables. '),
  wn('%    rdb_select(T,value(F=V),U) :  selection by value in tables. '),
  wn('%    rdb_select(T,theta(THETA),U) :  theta-selection. '),
  wn('%    rdb_join(T1,T2,CF,U) :  natural join of tables. '),
  wn('%    rdb_join(T1,T2,theta(THETA),U) :  theta-join of tables. '),
  wn('%    sql(Query,A) :  simulating SQL query language. '),
  wn('%   h0.   this.').
me:-
  wn('%  file: rdb01.pl'),
  wn('%  author: Kenryo INDO (Kanto Gakuen University)'),
  wn('%  created:  1 Mar 2003. (rdb0.pl)'),
  wn('%  modified:  5 Mar 2003. theta-select and theta-join (not correct)'),
  wn('%  modified:  6 Mar 2003. domain based revision.').
references:-
  wn('% references:'),
  wn('% [1]  E. F. Codd, A relational model of data for large shared data '),
  wn('%  banks, Comm. ACM 13 (6) (1970), 377-387. '),
  wn('%*[2]  E. F. Codd, Extending the database relational model to capture more meaning. '),
  wn('%  ACM Trans. on Database Systems 4(4) (1979), 397-434. ').


wn(Z):- write(Z),nl.
nw(Z):- nl,write(Z).

:- headline.

:- dynamic db /3.
:- dynamic db_log /2.


%
%   examples of database
% -----------------------------------------------------------  %

%---------------------------
% example 1. music database
%---------------------------
db(table(baroque),fields,[composer]).
db(table(baroque),tuple,[bach]).

db(table(classic),fields,[composer]).
db(table(classic),tuple,[mozart]).
db(table(classic),tuple,[beethoven]).

db(table(romantic),fields,[composer]).
db(table(romantic),tuple,[chopin]).
db(table(romantic),tuple,[paganini]).

db(table(modern),fields,[composer]).
db(table(modern),tuple,[bartok]).
db(table(modern),tuple,[takemitsu]).

db(table(works),fields,[composer,instrument]).
db(table(works),tuple,[bach,pipe_organ]).
db(table(works),tuple,[bach,recorder]).
db(table(works),tuple,[mozart,piano]).
db(table(works),tuple,[mozart,symphony]).
db(table(works),tuple,[mozart,opera]).
db(table(works),tuple,[beethoven,piano]).
db(table(works),tuple,[beethoven,symphony]).
db(table(works),tuple,[chopin,piano]).
db(table(works),tuple,[paganini,violin]).

db(table(instrument),fields,[instrument]).
db(table(instrument),tuple,[pipe_organ]).
db(table(instrument),tuple,[recorder]).
db(table(instrument),tuple,[piano]).
db(table(instrument),tuple,[symphony]).
db(table(instrument),tuple,[opera]).
db(table(instrument),tuple,[violin]).
db(table(instrument),tuple,[guitar]).

%------------------------------------
% example 2. curriculum database
%------------------------------------
db(table(teacher),fields,[teacher_id,name,position]).
db(table(teacher),tuple,[t001,smith,professor]).
db(table(teacher),tuple,[t002,johnson,lecturerer]).
db(table(teacher),tuple,[t003,ito,professor]).
db(table(teacher),tuple,[t004,kim,associate_professor]).
db(table(teacher),tuple,[t005,simon,professor]).
db(table(teacher),tuple,[t006,keynes,professor]).

db(table(subject),fields,[class_id,subject,day,hour,room,teacher]).
db(table(subject),tuple,[c001,english,mon,1,103,smith]).
db(table(subject),tuple,[c002,english,fri,1,104,smith]).
db(table(subject),tuple,[c003,english,tues,2,103,johnson]).
db(table(subject),tuple,[c003,english,tues,3,104,johnson]).
db(table(subject),tuple,[c005,mathematics,fri,1,205,ito]).
db(table(subject),tuple,[c006,statistics,fri,3,101,ito]).
db(table(subject),tuple,[c007,computer,wed,1,c1,kim]).
db(table(subject),tuple,[c008,economics,wed,2,201,simon]).
db(table(subject),tuple,[c009,economics,thurs,3,201,keynes]).

db(table(room),fields,[room_id,capacity]).
db(table(room),tuple,[101,150]).
db(table(room),tuple,[102,50]).
db(table(room),tuple,[103,80]).
db(table(room),tuple,[104,30]).
db(table(room),tuple,[201,100]).
db(table(room),tuple,[202,150]).
db(table(room),tuple,[203,50]).
db(table(room),tuple,[204,30]).
db(table(room),tuple,[205,150]).
db(table(room),tuple,[c1,200]).

% domain of relations.

db(domain(baroque),composer,D):-composers_domain_1(D).
db(domain(classic),composer,D):-composers_domain_1(D).
db(domain(romantic),composer,D):-composers_domain_1(D).
db(domain(modern),composer,D):-composers_domain_1(D).
db(domain(works),composer,D):-composers_domain_1(D).
db(domain(works),instrument,D):- db(domain(instrument),instrument,D).
db(domain(instrument),instrument,D):-
   D = [pipe_organ, recorder, piano, symphony, opera, violin, guitar].
db(domain(teacher),teacher_id,[t001, t002, t003, t004, t005, t006]).
db(domain(teacher),name,[smith, johnson, ito, kim, simon, keynes]).
db(domain(teacher),position,[professor, lecturerer, professor, associate_professor, professor, professor]).
db(domain(subject),class_id,[subject,day,hour,room,teacher]).
db(domain(subject),subject,D):-
   D = [computer, economics, english, mathematics, statistics].
db(domain(subject),day,[mon, tues, wed, thurs, fri]).
db(domain(subject),hour,[1,2,3,4,5,spcial]).
db(domain(subject),room,D):- db(domain(room),room_id,D).
db(domain(subject),teacher,D):- db(domain(teacher),name,D).
db(domain(room),room_id,[101, 102, 103, 104, 201, 202, 203, 204, 205, c1]).
db(domain(room),capacity,[20, 30, 50, 80, 100, 150, 200, 250, 300]).

composers_domain_1(D):-
   D1 = [bach, vivaldi, handel],
   D2 = [haydn, mozart, beethoven],
   D3 = [brahms, chopin, paganini, tschaikowsky],
   D4 = [stravinsky,bartok,takemitsu],
   Ds = [D1,D2,D3,D4],
   findall(X,(member(Y,Ds),member(X,Y)),D).

domains(Table,Domains):-
   db(table(Table),fields,_),
   findall(D,
     db(domain(Table),_Field,D),
   Domains).

current_values_of_table(T,F,Domain):-
   db(table(T),fields,Fs),
   nth1(K,Fs,F),
   findall(X,
     (
      db(table(T),tuple,Data),
      nth1(K,Data,X)
     ),
   D),
   sort(D,Domain).

%
%  relations on simple domains
% -----------------------------------------------------------  %
% R1. no duplication of tuples
% R2. order of tuples is irrelevant
% R3. order of fields (i.e., attributes) is irrelevant
% R4. all table entries are atomic, i.e., not decomposable by db sys.

%
% -----------------------------------------------------------  %
%  The five basic operations on tables (relations)
% -----------------------------------------------------------  %

basic_operations([union,difference,product,projection,selection]).

basic_operation(A):-
   basic_operations(C),
   member(B,C),
   concat('rdb_',B,A).

%------------
% union
%------------

% combine tuples (ie, relations) of pair of tables which has same
% set of fields (i.e, attributes), i.e., union-compatible relations.

% Among the following operations, each of union (,intersection,) and 
% difference is defined on any union-compatible relations  
% so that it can be seen of the set operations as for tuples.

is_union_compatible(Table1,Table2,Fields,Domains):-
   check_existence_of_db(Table1,Fields,yes),
   check_existence_of_db(Table2,Fields,yes),
   domains(Table1,Domains),
   domains(Table2,Domains).

% a refined program of union using list and common utilities.
 
rdb_union(Table1,Table2,Union):-
   is_union_compatible(Table1,Table2,Fields,Domains),
   check_existence_of_db(Union,_,no),
   create_table(Union,Fields,Domains),
   collect_tuples(Table1,X1),
   collect_tuples(Table2,X2),
   union(X1,X2,Update),
   update_table(Union,Update),
   display_table(Union).

% note:
% you may not use append /3 of SWI-prolog instead of union /3.
% and you may replace it by intersection /3 if you would like to
% speak rdb_intersection /3. 

% a naive program of union, without removal of multiplictions,
% without the verification and update of the common domain.

rdb_union_0(Table1,Table2,Union):-
   (
    db(table(Union),_,_)
     ->
      (
       nw('name already exists'),fail
      )
     ;true
   ),
   db(table(Table1),fields,Labels),
   db(table(Table2),fields,Labels),
   assert(
     db(table(Union),fields,Labels)
   ),
   forall(
     (
      db(table(Table1),tuple,Data);
      db(table(Table2),tuple,Data)
     ),
     (
      wn(a_tuple_asserted(Data)),
      assert(
        db(table(Union),tuple,Data)
      )
     )
   ),
   display_table(Union).

% a test.
% ?- rdb_union(baroque,classic,music1).

%------------
% difference
%------------

% difference applied to union-compatible relatins.
% there is no genuine difference to union but subtract /3.

rdb_difference(Table1,Table2,Differ):-
   is_union_compatible(Table1,Table2,Fields,Domains),
   check_existence_of_db(Differ,_,no),
   create_table(Differ,Fields,Domains),
   collect_tuples(Table1,X1),
   collect_tuples(Table2,X2),
   subtract(X1,X2,Update),
   update_table(Differ,Update),
   display_table(Differ).

% a test.
% ?- rdb_difference(music1,classic,music2).


%------------
% product
%------------

% Cartesian product, or simply, prduct of any pair of relations
% is an extended relation which has both of the set of 
% attributes from the originate relations and consists of 
% all possible combinations of the tuples in these relations.

rdb_product(Table1,Table2,Product):-
   check_existence_of_db(Table1,F1,yes),
   check_existence_of_db(Table2,F2,yes),
   check_existence_of_db(Product,_,no),
   composit_append(F1/Table1,F2/Table2,Fields),
   domains(Table1,D1),
   domains(Table2,D2),
   append(D1, D2, Domains),
   create_table(Product,Fields, Domains),
   collect_tuples(Table1,X1),
   collect_tuples(Table2,X2),
   findall(Y,
     (
      member(W1,X1),
      member(W2,X2),
      append(W1,W2,Y)
     ),
   Update),
   update_table(Product,Update),
   display_table(Product).

composit_append(A/S,B/T,C):-
   composit_rename(A/S,C1),
   composit_rename(B/T,C2),
   append(C1,C2,C).

composit_rename(A/S,C):-
   findall(X,
     (
      member(Y,A),
      X = S : Y
     ),
   C).


% a test.
% ?- rdb_product(modern,instrument,music3).


%------------
% projection
%------------

% reduce the table so that it has only specified subset of fields
% (i.e, attributes). And the multiplicity of tuples are reduced.

% rdb_projection /3 uses list_projection /3 cited from set.pl.

rdb_projection(Table,Selects,Project):-
   check_existence_of_db(Table,Fields,yes),
   check_existence_of_db(Project,_,no),
   check_of_fields(Selects/Fields),
   list_projection(LPX,Fields,Selects),
   domains(Table,Domains),
   list_projection(LPX,Domains,NewDomains),
   create_table(Project,Selects, NewDomains),
   collect_tuples(Table,Tuples0),
   findall(X,
     (
      member(D,Tuples0),
      list_projection(LPX,D,X)
     ),
   Tuples1),
   sort(Tuples1, Tuples),  
   update_table(Project,Tuples),
   display_table(Project).

% a test.
% ?- rdb_projection(works,[composer],music4).


%------------
% selection
%------------

% `select' is a case of more general operation `theta-select' 
% where the possibility of theta is, somewhat enlarged 
% operators than theta of Codd originally defined [2], 
% a member of 
%  ['<','=<','=:=','>=','>','=\='] (for numeric) and  
%  ['@<','=','@>','\='] (for strings or atom)  
% in accordance with Prolog notation. 
% When the equality 
% comarison operator '=' or '=:=' has specified, it is called 
% equi-select or simply `select' which selects the rows
% (tuples) from a table with sepcified value of attribute.

switch_by_theta_cases(THETA,Field,Operator,Value):-
   Case1 = ((Field < Value),'<'),
   Case2 = ((Field =< Value),'=<'),
   Case3 = ((Field =:= Value),'=:='),
   Case4 = ((Field >= Value),'>='),
   Case5 = ((Field > Value),'>'),
   Case6 = ((Field =\= Value),'=\='),
   Case7 = ((Field @< Value),'@<'),
   Case8 = ((Field = Value),'='),
   Case9 = ((Field @> Value),'@>'),
   Case10 = ((Field \= Value),'\='),
   A = [Case1,Case2,Case3,Case4,Case5,Case6],
   B = [Case7,Case8,Case9,Case10],
   union(A,B,C),
   member((THETA,Operator),C).

% select. 

rdb_select(Table,value(Field=Value),Select):-
   check_existence_of_db(Table,AllFields,yes),
   check_existence_of_db(Select,_,no),
   check_of_fields([Field]/AllFields),
   nth1(K,AllFields,Field),
   domains(Table,Domains),
   create_table(Select,AllFields,Domains),
   collect_tuples(Table,Data),
   findall(X,
     (
      member(X,Data),
      nth1(K,X,Value)
     ),
   Update),
   update_table(Select,Update),
   display_table(Select).


% a test.
% ?- rdb_select(works,value(instrument=piano),pianists1).
% nother one
% ?- rdb_select(teacher,value(position=professor),prof).


% theta-select 

rdb_select(Table,theta(THETA),Select):-
   switch_by_theta_cases(THETA,Field,Operator,Value),
   check_existence_of_db(Table,AllFields,yes),
   check_existence_of_db(Select,_,no),
   check_of_fields([Field]/AllFields),
   nth1(K,AllFields,Field),
   domains(Table,Domains),
   create_table(Select,AllFields,Domains),
   collect_tuples(Table,Data),
   findall(X,
     (
      member(X,Data),
      nth1(K,X,VX),
      G=.. [Operator,VX,Value],
      G
     ),
   Update),
   update_table(Select,Update),
   display_table(Select).


%  selection by comparison of a pair of fields within a table, 
%  which will be applied to the extended table in join.

rdb_select(Table,field(F1=F2),Select):-
   check_existence_of_db(Table,Fields,yes),
   check_existence_of_db(Select,_,no),
   check_of_fields([F1,F2]/Fields),
   db(domain(Table), F1,CommonDomain),
   db(domain(Table), F2,CommonDomain),
   nth1(K,Fields,F1),
   nth1(L,Fields,F2),
   domains(Table,Domains),
   create_table(Select,Fields,Domains),
   collect_tuples(Table,Data),
   findall(X,
     (
      member(X,Data),
      nth1(K,X,Value),
      nth1(L,X,Value)
     ),
   Update),
   update_table(Select,Update),
   display_table(Select).

% the theta-version applied to extended table to be used by theta-join

rdb_select(Table,field_theta(THETA),Select):-
   switch_by_theta_cases(THETA,F1,Operator,F2),
   check_existence_of_db(Table,Fields,yes),
   check_existence_of_db(Select,_,no),
   check_of_fields([F1,F2]/Fields),
   domains(Table, Domains),
   nth1(K,Fields,F1),
   nth1(L,Fields,F2),
   create_table(Select,Fields,Domains),
   collect_tuples(Table,Data),
   findall(X,
     (
      member(X,Data),
      nth1(K,X,Value1),
      nth1(L,X,Value2),
      G=.. [Operator,Value1,Value2],
      G
     ),
   Update),
   update_table(Select,Update),
   display_table(Select).


/*
% sample executions for theta select.

?- display_table(room).

-----------------------------------------------------
table=room

fields:
  [room_id, capacity]

data:
  [101, 150]
  [102, 50]
  [103, 80]
  [104, 30]
  [201, 100]
  [202, 150]
  [203, 50]
  [204, 30]
  [205, 150]
  [c1, 200]
  end of db

Yes
?- rdb_select(room,theta(capacity>100),large1).

table=large1

fields:
  [room_id, capacity]

data:
  [201, 100]
  [202, 150]
  [205, 150]
  [c1, 200]
  end of db

Yes
*/

%
% -----------------------------------------------------------  %
%  Join for two tables 
% -----------------------------------------------------------  %

% A join of two tables is a table which consists of tuples 
% each of which has the same specified value of common attribute. 
% In order to process this, do product for both at first, then do select.


% equi-join (i.e., a case of theta-join )
% for a pair of (field:table)s with common domain

rdb_join(Table1,Table2,equi(F1=F2),Join):-
   check_existence_of_db(Join,_,no),
   check_existence_of_db(Table1,Fields1,yes),
   check_of_fields([F1]/Fields1),
   check_existence_of_db(Table2,Fields2,yes),
   check_of_fields([F2]/Fields2),
   db(domain(Table1), F1,CommonDomain),
   (
    db(domain(Table2), F2,CommonDomain)
     -> true
      ; (
         wn(' The fields do not have common domain.'),
         fail
        )
   ),
   X = Table1 : F1, 
   Y = Table2 : F2, 
   Condition = field(X = Y),
   T = product_for_join(Table1,Table2),
   (
    check_existence_of_db(T,_,no)
     -> rdb_product(Table1,Table2,T)
     ;  true
   ),
   rdb_select(T,Condition,Join).


% natural join, or simply join 
% same as equi-join except that the redundunt fields are removed.

rdb_join(Table1,Table2,(F1=F2),Join):-
   % \+ member((F1=F2),[equi(_),theta(_)]),
   check_existence_of_db(Join,_,no),
   (
    check_existence_of_db(join0(Join),F0,no)
    -> 
     (
      rdb_join(Table1,Table2,equi(F1=F2),join0(Join)),
      db(table(join0(Join)),fields,F0)
     )
    ;
     true
   ),
   subtract(F0,[(Table2 : F2)],NewFields),
   rdb_projection(join0(Join),NewFields,Join).


% a test.
% ?- rdb_join(teacher,subject,teacher,new).


% theta-join for a pair of (field:table)s with common domain.

rdb_join(Table1,Table2,theta(THETA),Join):-
   switch_by_theta_cases(THETA,F1,Operator,F2),
   check_existence_of_db(Join,_,no),
   T = product_for_join(Table1,Table2),
   (
    check_existence_of_db(T,_,no)
     -> rdb_product(Table1,Table2,T)
     ;  true
   ),
   db(domain(Table1), F1,CommonDomain),
   db(domain(Table2), F2,CommonDomain),
   X = Table1 : F1, 
   Y = Table2 : F2, 
   switch_by_theta_cases(THETA1,X,Operator,Y),
   rdb_select(T,field_theta(THETA1),Join).


/*
% sample executions for select and join.


?- rdb_select(room,theta(capacity>100),large1).

-----------------------------------------------------
table=large1

fields:
  [room_id, capacity]

data:
  [101, 150]
  [202, 150]
  [205, 150]
  [c1, 200]
  end of db


Yes
?- rdb_join(large1,subject,theta(room_id=room),class1).

-----------------------------------------------------
table=class1

fields:
  [large:room_id, large:capacity, subject:class_id, subject:subject, subject:day, subject:hour, subject:room, subject:teacher]

data:
  [101, 150, c006, statistics, fri, 3, 101, ito]
  [205, 150, c005, mathematics, fri, 1, 205, ito]
  [c1, 200, c007, computer, wed, 1, c1, kim]
  end of db

Yes
?-

*/

%-----------------------------
% SQL like language 
%-----------------------------

sql( A, B, C , SQL) :-
   A =  select : Fields,
   B =  from : [Table],
   C =  where : [Condition],
   (
    check_existence_of_db(sql0(A,B,C),_,yes)
    -> true
    ; rdb_select(Table,Condition,sql0(A,B,C))
   ),
   rdb_projection(sql0(A,B,C),Fields,SQL).


% Further extension may be left to reader's exercise.

% a test
/*
?- sql(select:[composer],
|    from:[works],
|    where:[value(instrument=piano)],pianist2).
*/

%-----------------------------
% common utilities for db 
%-----------------------------

check_existence_of_db(Table,Fields,yes):-
   (
    db(table(Table),fields,Fields)
     ->
      true
     ;
      (
       nw(' The table '),
       write(Table),
       wn(' does not exists.'),
       fail
      )
   ).

check_existence_of_db(Table,Fields,no):-
   \+ var(Table),
   (
    db(table(Table),fields,Fields)
     ->
      (
       nw(' The table '),
       write(Table),
       wn(' already exists.'),
       fail
      )
     ;true
   ).

check_existence_of_db(Table,_,no):-
   var(Table),
   nw(' Please specify the name for new table. '),
   fail.

check_of_fields(Selects/Fields):-
   subtract(Selects,Fields,Differ),
   (
    Differ = []
     -> true
     ;
      (
       nw(' The field '),
       write(Differ),
       wn(' not exists.'),
       fail
      )
   ).


% maybe it is not appropriate for large dbs.

collect_tuples(Table,Data):-
   findall(D,
     db(table(Table),tuple,D),
   Data).


% rdb table creation.

create_table(New,Fields,Domains):-
   length(Fields,N),
   (length(Domains,N)->true; 
     wn(' domain and fields are not compatible.')
   ),
   check_existence_of_db(New,_,no),
   assert(
     db(table(New),fields,Fields)
   ),
   forall(nth1(K,Domains,D),
     (
      nth1(K,Fields,F),
      assert(
        db(domain(New),F,D)
      )
     )
   ),
   time_stamp(S),
   assert(
     db_log(S,
        a_new_table_has_created(New,fields,Fields)
      )
   ).

update_table(Table,Y):-
   check_existence_of_db(Table,_,yes),
   forall(
     member(Data,Y),
     (
      assert(
        db(table(Table),tuple,Data)
      ),
      nw(a_tuple_has_asserted(Data)),
      time_stamp(S),
      assert(
        db_log(S,
          a_tuple_has_updated(Table,tuple,Data)
        )
      )
     )
   ).


delete_table(Old,Fields):-
   check_existence_of_db(Old,Fields,yes),
   (
    db(table(Old),tuple,_)
    ->
     (
      wn('-- there are tuples. delete all of them ? (y/n) ---'), 
      read(y)
     )
   ),
   delete_all_tuples(Old),
   retract(
     db(table(Old),fields,Fields)
   ),
   time_stamp(S),
   assert(
     db_log(S,
        a_table_has_deleted(Old,fields,Fields)
     )
   ).

delete_all_tuples(Old):-
   forall(
     (
      G = db(table(Old),tuple,Data),
      G
     ),
     (
      retract(G),
      time_stamp(S0),
      assert(
        db_log(S0,
          a_tuple_has_deleted(Old,tuple,Data)
        )
      )
     )
   ),
   time_stamp(S),
   assert(
     db_log(S,
        all_tuples_has_deleted(Old)
     )
   ).

undo_delete_all_tuples(Old):-
   db_log(S,
        all_tuples_has_deleted(Old)
   ),
   \+ db_log(
        undo_delete_all_tuples(Old,S)
   ),
   forall(
     (
      G = db_log(_,
        a_tuple_has_deleted(Old,tuple,Data,_)
      ),
      G
     ),
     (
      retract(G),
      assert(
        db(table(Old),tuple,Data)
      )
     )
   ),
   time_stamp(S),
   assert(
     db_log(
        undo_delete_all_tuples(Old,S)
     )
   ).



% time stamp
%--------------------------------------%
% cited from moji.pl(impl12.pl)

time_stamp(T):-
  get_time(U),
  convert_time(U,A,B,C,D,E,F,_G),
  T = [date(A/B/C), time(D:E:F)].


% a sequence of binary choice for a list:
%--------------------------------------------------
% cited from: set.pl

list_projection([],[],[]).
list_projection([X|Y],[_|B],C):-
   list_projection(Y,B,C),
   X = 0.
list_projection([X|Y],[A|B],[A|C]):-
   list_projection(Y,B,C),
   X = 1.

% complement
c_list_projection([],[],[]).
c_list_projection([X|Y],[_|B],C):-
   c_list_projection(Y,B,C),
   X = 1.
c_list_projection([X|Y],[A|B],[A|C]):-
   c_list_projection(Y,B,C),
   X = 0.

%
%  display all database tables
% -----------------------------------------------------------  %
display_db:-
   display_db(A),
   forall(member(B,A),nw(table(B))).

display_db(A):-
   findall(X,
     db(table(X),fields,_),
   A).

%
%  display all tuples of exsiting table
% -----------------------------------------------------------  %
display_table(T):-
   db(table(T),fields,L),
   nw('-----------------------------------------------------'),
   nw((table = T)),nl,
   nw(fields),write(':'),
   nl,tab(2),wn(L),
   nw(data),write(':'),
   forall(db(table(T),tuple,B),(nl,tab(2),write(B))),
   nw('  end of db'),
   nl.


% end

return to front page.