Logtalk 2.26.2 files.

git-svn-id: https://yap.svn.sf.net/svnroot/yap/trunk@1487 b08c6af1-5177-4d33-ba66-4b1c6b8b522a
This commit is contained in:
pmoura
2005-12-24 18:07:41 +00:00
parent 9f1b358c04
commit 3455276aa2
55 changed files with 6535 additions and 0 deletions

View File

@@ -0,0 +1,11 @@
=================================================================
Logtalk - Object oriented extension to Prolog
Release 2.26.2
Copyright (c) 1998-2005 Paulo Moura. All Rights Reserved.
=================================================================
This example is an adaptation of the LPA Prolog++ timetables example.
To load this example and for sample queries, please see the SCRIPT file.

View File

@@ -0,0 +1,532 @@
=================================================================
Logtalk - Object oriented extension to Prolog
Release 2.26.2
Copyright (c) 1998-2005 Paulo Moura. All Rights Reserved.
=================================================================
% start by loading the necessary library support example files (if not
% already loaded):
| ?- logtalk_load(library(types_loader)).
...
% now you are ready for loading the example:
| ?- logtalk_load(lpa_timetables(loader)).
...
% the setup phase initializes the timetable:
| ?- timetable::setup.
yes
| ?- timetable::make(2).
+ first_year - p1 - nicky - french
+ first_year - p2 - nicky - biology
+ first_year - p3 - brian - maths
+ first_year - p4 - brian - music
+ first_year - p5 - clive - prolog
+ second_year - p1 - brian - maths
+ second_year - p2 - brian - music
+ second_year - p3 - nicky - french
+ second_year - p4 - nicky - biology
+ second_year - p5 - diane - accountancy
+ third_year - p1 - dave - maths
+ third_year - p2 - clive - french
+ third_year - p3 - clive - prolog
+ third_year - p4 - diane - accountancy
+ third_year - p5 - nicky - biology
+ fourth_year - p1 - clive - french
+ fourth_year - p2 - dave - maths
+ fourth_year - p3 - diane - accountancy
+ fourth_year - p4 - clive - prolog
+ fourth_year - p5 - brian - music
yes
% the partially completed timetable is ...
| ?- timetable::print.
FORM TIMETABLE...
FORM: first_year
p1: nicky teaches french
p2: nicky teaches biology
p3: brian teaches maths
p4: brian teaches music
p5: clive teaches prolog
FORM: second_year
p1: brian teaches maths
p2: brian teaches music
p3: nicky teaches french
p4: nicky teaches biology
p5: diane teaches accountancy
FORM: third_year
p1: dave teaches maths
p2: clive teaches french
p3: clive teaches prolog
p4: diane teaches accountancy
p5: nicky teaches biology
FORM: fourth_year
p1: clive teaches french
p2: dave teaches maths
p3: diane teaches accountancy
p4: clive teaches prolog
p5: brian teaches music
PERIOD TIMETABLE ...
PERIOD: p1
first_year: nicky teaches french
second_year: brian teaches maths
third_year: dave teaches maths
fourth_year: clive teaches french
PERIOD: p2
first_year: nicky teaches biology
second_year: brian teaches music
third_year: clive teaches french
fourth_year: dave teaches maths
PERIOD: p3
first_year: brian teaches maths
second_year: nicky teaches french
third_year: clive teaches prolog
fourth_year: diane teaches accountancy
PERIOD: p4
first_year: brian teaches music
second_year: nicky teaches biology
third_year: diane teaches accountancy
fourth_year: clive teaches prolog
PERIOD: p5
first_year: clive teaches prolog
second_year: diane teaches accountancy
third_year: nicky teaches biology
fourth_year: brian teaches music
TEACHER TIMETABLE ...
TEACHER: nicky
p1: teach french to first_year
p2: teach biology to first_year
p3: teach french to second_year
p4: teach biology to second_year
p5: teach biology to third_year
TEACHER: brian
p1: teach maths to second_year
p2: teach music to second_year
p3: teach maths to first_year
p4: teach music to first_year
p5: teach music to fourth_year
TEACHER: dave
p1: teach maths to third_year
p2: teach maths to fourth_year
p3:
p4:
p5:
TEACHER: clive
p1: teach french to fourth_year
p2: teach french to third_year
p3: teach prolog to third_year
p4: teach prolog to fourth_year
p5: teach prolog to first_year
TEACHER: diane
p1:
p2:
p3: teach accountancy to fourth_year
p4: teach accountancy to third_year
p5: teach accountancy to second_year
TEACHER: phil
p1:
p2:
p3:
p4:
p5:
SUBJECT TIMETABLE ...
SUBJECT: maths
p1: second_year taught by brian
p1: third_year taught by dave
p2: fourth_year taught by dave
p3: first_year taught by brian
SUBJECT: music
p2: second_year taught by brian
p4: first_year taught by brian
p5: fourth_year taught by brian
SUBJECT: french
p1: first_year taught by nicky
p1: fourth_year taught by clive
p2: third_year taught by clive
p3: second_year taught by nicky
SUBJECT: prolog
p3: third_year taught by clive
p4: fourth_year taught by clive
p5: first_year taught by clive
SUBJECT: biology
p2: first_year taught by nicky
p4: second_year taught by nicky
p5: third_year taught by nicky
SUBJECT: prolog++
SUBJECT: accountancy
p3: fourth_year taught by diane
p4: third_year taught by diane
p5: second_year taught by diane
yes
| ?- timetable::make(5).
+ first_year - p1 - diane - accountancy
+ first_year - p2 - phil - prolog++
+ second_year - p1 - phil - prolog++
Swap subject...
- third_year - p4 - diane - accountancy
+ third_year - p4 - phil - prolog++
Swap teacher...
- third_year - p2 - clive - french
+ third_year - p2 - diane - accountancy
Swap teacher...
- second_year - p2 - brian - music
+ second_year - p2 - clive - prolog
Swap teacher...
Swap subject...
- third_year - p2 - diane - accountancy
+ third_year - p2 - brian - music
Swap teacher...
- third_year - p2 - brian - music
+ third_year - p2 - diane - accountancy
Swap teacher...
- second_year - p2 - clive - prolog
+ second_year - p2 - brian - music
Swap teacher...
Swap teacher...
- second_year - p2 - brian - music
+ second_year - p2 - clive - prolog
Swap teacher...
- second_year - p2 - clive - prolog
+ second_year - p2 - brian - music
Swap teacher...
Swap teacher...
- second_year - p2 - brian - music
+ second_year - p2 - clive - prolog
Swap teacher...
- second_year - p2 - clive - prolog
+ second_year - p2 - brian - music
Swap teacher...
Swap teacher...
- second_year - p2 - brian - music
+ second_year - p2 - clive - prolog
Swap teacher...
Swap teacher...
- second_year - p2 - clive - prolog
+ second_year - p2 - brian - music
Swap teacher...
- second_year - p2 - brian - music
+ second_year - p2 - clive - prolog
Swap teacher...
Swap teacher...
- second_year - p2 - clive - prolog
+ second_year - p2 - brian - music
Swap teacher...
- second_year - p2 - brian - music
+ second_year - p2 - clive - prolog
Swap teacher...
Swap teacher...
- second_year - p2 - clive - prolog
+ second_year - p2 - brian - music
Swap teacher...
- second_year - p2 - brian - music
+ second_year - p2 - clive - prolog
Swap teacher...
Swap teacher...
- second_year - p2 - clive - prolog
+ second_year - p2 - brian - music
Swap teacher...
- second_year - p2 - brian - music
+ second_year - p2 - clive - prolog
Swap teacher...
Swap teacher...
- second_year - p2 - clive - prolog
+ second_year - p2 - brian - music
Swap teacher...
- second_year - p2 - brian - music
+ second_year - p2 - clive - prolog
Swap teacher...
Swap teacher...
- second_year - p2 - clive - prolog
+ second_year - p2 - brian - music
Swap subject...
- third_year - p2 - diane - accountancy
+ third_year - p2 - clive - french
Swap subject...
- third_year - p4 - phil - prolog++
+ third_year - p4 - diane - accountancy
Swap teacher...
- third_year - p3 - clive - prolog
+ third_year - p3 - phil - prolog++
Swap subject...
Swap subject...
Swap subject...
- third_year - p3 - phil - prolog++
+ third_year - p3 - clive - prolog
Swap subject...
- third_year - p4 - diane - accountancy
+ third_year - p4 - phil - prolog++
Swap teacher...
- third_year - p2 - clive - french
+ third_year - p2 - diane - accountancy
+ second_year - p2 - clive - prolog
Swap subject...
- fourth_year - p3 - diane - accountancy
+ fourth_year - p3 - phil - prolog++
Swap teacher...
- fourth_year - p4 - clive - prolog
+ fourth_year - p4 - diane - accountancy
Swap subject...
- third_year - p4 - phil - prolog++
+ third_year - p4 - clive - french
Swap teacher...
- third_year - p3 - clive - prolog
+ third_year - p3 - phil - prolog++
Swap subject...
- fourth_year - p3 - phil - prolog++
+ fourth_year - p3 - clive - prolog
Swap teacher...
Swap teacher...
Swap subject...
- fourth_year - p4 - diane - accountancy
+ fourth_year - p4 - phil - prolog++
Swap teacher...
- fourth_year - p3 - clive - prolog
+ fourth_year - p3 - diane - accountancy
Swap subject...
- fourth_year - p3 - diane - accountancy
+ fourth_year - p3 - clive - prolog
Swap teacher...
- fourth_year - p3 - clive - prolog
+ fourth_year - p3 - diane - accountancy
Swap subject...
- third_year - p3 - phil - prolog++
+ third_year - p3 - clive - prolog
Swap teacher...
- third_year - p5 - nicky - biology
+ third_year - p5 - phil - prolog++
Swap teacher...
- fourth_year - p5 - brian - music
+ fourth_year - p5 - nicky - biology
Swap teacher...
Swap teacher...
- fourth_year - p5 - nicky - biology
+ fourth_year - p5 - brian - music
Swap teacher...
- fourth_year - p5 - brian - music
+ fourth_year - p5 - nicky - biology
Swap teacher...
Swap teacher...
- fourth_year - p5 - nicky - biology
+ fourth_year - p5 - brian - music
Swap teacher...
- fourth_year - p5 - brian - music
+ fourth_year - p5 - nicky - biology
Swap teacher...
Swap teacher...
- fourth_year - p5 - nicky - biology
+ fourth_year - p5 - brian - music
Swap teacher...
- fourth_year - p5 - brian - music
+ fourth_year - p5 - nicky - biology
+ third_year - p5 - brian - music
yes
% the completed timetable is ...
| ?- timetable::print.
FORM TIMETABLE...
FORM: first_year
p1: nicky teaches french
p2: nicky teaches biology
p3: brian teaches maths
p4: brian teaches music
p5: clive teaches prolog
FORM: second_year
p1: brian teaches maths
p2: brian teaches music
p3: nicky teaches french
p4: nicky teaches biology
p5: diane teaches accountancy
FORM: third_year
p1: dave teaches maths
p2: diane teaches accountancy
p3: clive teaches prolog
p4: clive teaches french
p5: phil teaches prolog++
FORM: fourth_year
p1: clive teaches french
p2: dave teaches maths
p3: diane teaches accountancy
p4: phil teaches prolog++
p5: nicky teaches biology
PERIOD TIMETABLE ...
PERIOD: p1
first_year: nicky teaches french
second_year: brian teaches maths
third_year: dave teaches maths
fourth_year: clive teaches french
PERIOD: p2
first_year: nicky teaches biology
second_year: brian teaches music
third_year: diane teaches accountancy
fourth_year: dave teaches maths
PERIOD: p3
first_year: brian teaches maths
second_year: nicky teaches french
third_year: clive teaches prolog
fourth_year: diane teaches accountancy
PERIOD: p4
first_year: brian teaches music
second_year: nicky teaches biology
third_year: clive teaches french
fourth_year: phil teaches prolog++
PERIOD: p5
first_year: clive teaches prolog
second_year: diane teaches accountancy
third_year: phil teaches prolog++
fourth_year: nicky teaches biology
TEACHER TIMETABLE ...
TEACHER: nicky
p1: teach french to first_year
p2: teach biology to first_year
p3: teach french to second_year
p4: teach biology to second_year
p5: teach biology to fourth_year
TEACHER: brian
p1: teach maths to second_year
p2: teach music to second_year
p3: teach maths to first_year
p4: teach music to first_year
p5: teach music to third_year
TEACHER: dave
p1: teach maths to third_year
p2: teach maths to fourth_year
p3:
p4:
p5:
TEACHER: clive
p1: teach french to fourth_year
p2: teach prolog to second_year
p3: teach prolog to third_year
p4: teach french to third_year
p5: teach prolog to first_year
TEACHER: diane
p1: teach accountancy to first_year
p2: teach accountancy to third_year
p3: teach accountancy to fourth_year
p4:
p5: teach accountancy to second_year
TEACHER: phil
p1: teach prolog++ to second_year
p2: teach prolog++ to first_year
p3:
p4: teach prolog++ to fourth_year
p5: teach prolog++ to third_year
SUBJECT TIMETABLE ...
SUBJECT: maths
p1: second_year taught by brian
p1: third_year taught by dave
p2: fourth_year taught by dave
p3: first_year taught by brian
SUBJECT: music
p2: second_year taught by brian
p4: first_year taught by brian
p5: third_year taught by brian
SUBJECT: french
p1: first_year taught by nicky
p1: fourth_year taught by clive
p3: second_year taught by nicky
p4: third_year taught by clive
SUBJECT: prolog
p2: second_year taught by clive
p3: third_year taught by clive
p5: first_year taught by clive
SUBJECT: biology
p2: first_year taught by nicky
p4: second_year taught by nicky
p5: fourth_year taught by nicky
SUBJECT: prolog++
p1: second_year taught by phil
p2: first_year taught by phil
p4: fourth_year taught by phil
p5: third_year taught by phil
SUBJECT: accountancy
p1: first_year taught by diane
p2: third_year taught by diane
p3: fourth_year taught by diane
p5: second_year taught by diane
yes

View File

@@ -0,0 +1,80 @@
:- object(forms).
:- info([
version is 1.0,
date is 2005/5/8,
author is 'Example by LPA; adapted to Logtalk by Paulo Moura.',
comment is 'General attributes & methods for all forms.']).
:- public(print/0).
:- info(print/0, [
comment is 'Print the complete timetable from the pupil viewpoint.']).
print :-
nl, write('FORM TIMETABLE...'), nl, nl,
forall(extends_object(Form, form), Form::print), nl.
:- end_object.
:- object(form).
:- info([
version is 1.0,
date is 2005/5/8,
author is 'Example by LPA; adapted to Logtalk by Paulo Moura.',
comment is 'General attributes & methods for all forms.']).
:- public(print/0).
:- info(print/0, [
comment is 'Print the complete timetable from the pupil viewpoint.']).
:- public(print_period/1).
:- info(print_period/1, [
comment is 'Print the pupil timetable for a specific period.',
argnames is ['Period']]).
print :-
self(Self),
write('FORM: '), write(Self), nl,
forall(extends_object(Period, period), Period::print_form(Self)), nl.
print_period(Period) :-
self(Self),
timetable::filled_entry(Self, Period, Teacher, Subject),
!,
write(Self), write(': '),
write(Teacher), write(' teaches '),
write(Subject), nl.
print_period(_) :-
self(Self),
write(Self), write(': '), nl.
:- end_object.
:- object(first_year,
extends(form)).
:- end_object.
:- object(second_year,
extends(form)).
:- end_object.
:- object(third_year,
extends(form)).
:- end_object.
:- object(fourth_year,
extends(form)).
:- end_object.

View File

@@ -0,0 +1,8 @@
:- initialization(
logtalk_load([
timetable,
forms,
periods,
subjects,
teachers])).

View File

@@ -0,0 +1,129 @@
:- object(periods).
:- info([
version is 1.0,
date is 2005/5/8,
author is 'Example by LPA; adapted to Logtalk by Paulo Moura.',
comment is 'General attributes & methods for all periods.']).
:- public(print/0).
:- info(print/0, [
comment is 'Print period timetable.']).
print :-
nl, write('PERIOD TIMETABLE ...'), nl, nl,
forall(extends_object(Period, period), Period::print), nl.
:- end_object.
:- object(period).
:- info([
version is 1.0,
date is 2005/5/8,
author is 'Example by LPA; adapted to Logtalk by Paulo Moura.',
comment is 'General attributes & methods for all periods.']).
:- public(print/0).
:- info(print/0, [
comment is 'Print complete timetable from the period viewpoint.']).
:- public(print_teacher/1).
:- info(print_teacher/1, [
comment is 'Print entry for a specific teacher in this period.',
argnames is ['Teacher']]).
:- public(print_form/1).
:- info(print_form/1, [
comment is 'Print entry for a specific form in this period.',
argnames is ['Form']]).
:- public(print_subject/1).
:- info(print_subject/1, [
comment is 'Print entry for a specific subject in this period.',
argnames is ['Subject']]).
print :-
self(Self),
write('PERIOD: '), write(Self), nl,
forall(extends_object(Form, form), Form::print_period(Self)), nl.
print_teacher(Teacher) :-
self(Self),
timetable::filled_entry(Form, Self, Teacher, Subject),
!,
write(Self), write(': teach '),
write(Subject), write(' to '),
write(Form), nl.
print_teacher(_) :-
self(Self),
write(Self), write(':'), nl.
print_form(Form) :-
self(Self),
timetable::filled_entry(Form, Self, Teacher, Subject),
!,
write(Self), write(': '),
write(Teacher), write(' teaches '),
write(Subject), nl.
print_form(_) :-
self(Self),
write(Self), write(':'), nl.
print_subject(Subject) :-
self(Self),
timetable::filled_entry(Form, Self, Teacher, Subject),
write(Self), write(': '),
write(Form), write(' taught by '),
write(Teacher), nl,
fail.
print_subject(_).
:- end_object.
:- object(p1,
extends(period)).
:- end_object.
:- object(p2,
extends(period)).
:- end_object.
:- object(p3,
extends(period)).
:- end_object.
:- object(p4,
extends(period)).
:- end_object.
:- object(p5,
extends(period)).
:- end_object.

View File

@@ -0,0 +1,82 @@
:- object(subjects).
:- info([
version is 1.0,
date is 2005/5/8,
author is 'Example by LPA; adapted to Logtalk by Paulo Moura.',
comment is 'General attributes & methods for all subjects.']).
:- public(print/0).
:- info(print/0, [
comment is 'Print complete timetable from the subject viewpoint.']).
print :-
nl, write('SUBJECT TIMETABLE ...'), nl, nl,
forall(extends_object(Subject, subject), Subject::print),
nl.
:- end_object.
:- object(subject).
:- info([
version is 1.0,
date is 2005/5/8,
author is 'Example by LPA; adapted to Logtalk by Paulo Moura.',
comment is 'General attributes & methods for all subjects.']).
:- public(print/0).
:- info(print/0, [
comment is 'Print complete timetable from the subject viewpoint.']).
print :-
self(Self),
write('SUBJECT: '), write(Self), nl,
forall(extends_object(Period, period), Period::print_subject(Self)),
nl.
:- end_object.
:- object(maths,
extends(subject)).
:- end_object.
:- object(music,
extends(subject)).
:- end_object.
:- object(french,
extends(subject)).
:- end_object.
:- object(prolog,
extends(subject)).
:- end_object.
:- object(biology,
extends(subject)).
:- end_object.
:- object('prolog++',
extends(subject)).
:- end_object.
:- object(accountancy,
extends(subject)).
:- end_object.

View File

@@ -0,0 +1,128 @@
:- object(teachers).
:- info([
version is 1.0,
date is 2005/5/8,
author is 'Example by LPA; adapted to Logtalk by Paulo Moura.',
comment is 'General attributes & methods for all teachers.']).
:- public(print/0).
:- info(print/0, [
comment is 'Print teachers timetable.']).
print :-
nl, write('TEACHER TIMETABLE ...'), nl, nl,
forall(extends_object(Teacher, teacher), Teacher::print),
nl.
:- end_object.
:- object(teacher).
:- info([
version is 1.0,
date is 2005/5/8,
author is 'Example by LPA; adapted to Logtalk by Paulo Moura.',
comment is 'General attributes & methods for all teachers.']).
:- public(teach_period/1).
:- info(teach_period/1, [
comment is 'A period for which the teacher can be assigned.']).
:- public(teach_subject/1).
:- info(teach_subject/1, [
comment is 'A subject which the teacher can teach.']).
:- public(print/0).
:- info(print/0, [
comment is 'Print complete timetable from the teacher viewpoint.']).
:- public(freetime/1).
:- info(freetime/1, [
comment is '.',
argnames is ['Freetime']]).
:- public(subject/1).
:- info(subject/1, [
comment is '.',
argnames is ['Subject']]).
teach_period(Period) :-
\+ ::freetime(Period).
teach_subject(Subject) :-
::subject(Subject).
print :-
self(Self),
write('TEACHER: '), write(Self), nl,
forall(extends_object(Period, period), Period::print_teacher(Self)),
nl.
:- end_object.
:- object(nicky,
extends(teacher)).
subject(french).
subject(biology).
freetime(1).
freetime(4).
:- end_object.
:- object(brian,
extends(teacher)).
subject(maths).
subject(music).
:- end_object.
:- object(dave,
extends(teacher)).
subject(maths).
:- end_object.
:- object(clive,
extends(teacher)).
subject(french).
subject(prolog).
freetime(2).
freetime(3).
freetime(5).
:- end_object.
:- object(diane,
extends(teacher)).
subject(accountancy).
freetime(2).
freetime(4).
:- end_object.
:- object(phil,
extends(teacher)).
subject(maths).
subject('prolog++').
freetime(3).
:- end_object.

View File

@@ -0,0 +1,134 @@
:- object(timetable).
:- info([
version is 1.0,
date is 2005/5/8,
author is 'Example by LPA; adapted to Logtalk by Paulo Moura.',
comment is 'Set up & create a timetable satisfying all of the constraints.']).
:- public(setup/0).
:- info(setup/0, [
comment is 'Set up the teachers, subjects, forms & periods for this school.']).
:- public(make/0).
:- info(make/0, [
comment is 'Make the timetable according to the school setup.']).
:- public(make/1).
:- info(make/1, [
comment is 'Make with max. depth of swaps.',
argnames is ['Effort']]).
:- public(print/0).
:- info(print/0, [
comment is 'Print from different perspectives.']).
:- public(filled_entry/4).
:- info(filled_entry/4, [
comment is 'Timetable entry.',
argnames is ['Form', 'Period', 'Teacher', 'Subject']]).
:- private(entry/4).
:- dynamic(entry/4).
:- info(entry/4, [
comment is 'Timetable entry.',
argnames is ['Form', 'Period', 'Teacher', 'Subject']]).
:- uses(list).
print :-
(forms, periods, teachers, subjects)::print.
setup :-
retractall(entry(_, _, _, _)).
make :-
make(3).
make(Effort) :-
list::length(E, Effort),
forall(
(extends_object(Form, form), extends_object(Period, period)),
fill_entry(E, Form, Period, _Teacher, _Subject)).
unfilled_entry(Form, Period) :-
extends_object(Form, form),
extends_object(Period, period),
\+ filled_entry(Form, Period, _, _).
filled_entry(Form, Period, Teacher, Subject) :-
entry(Form, Period, Teacher, Subject).
fill_entry(E, Form, Period, Teacher, Subject) :-
find_entry(E, Form, Period, Teacher, Subject),
!,
assert(Form, Period, Teacher, Subject).
fill_entry(_, _, _, _, _).
find_entry(_, Form, Period, Teacher, Subject) :-
extends_object(Teacher, teacher),
Teacher::teach_period(Period),
\+ filled_entry(_, Period, Teacher, _),
extends_object(Subject, subject),
Teacher::teach_subject(Subject),
\+ filled_entry(Form, _, _, Subject).
find_entry([_| E], FormA, Period, TeacherA, SubjectA) :-
extends_object(Teacher, teacher),
Teacher::teach_period(Period),
filled_entry(FormB, Period, TeacherA, _),
extends_object(SubjectA, subject),
TeacherA::teach_subject(SubjectA),
\+ filled_entry(FormA, _, _, SubjectA),
find_entry(E, FormB, Period, TeacherB, SubjectB),
TeacherB \= TeacherA,
write('Swap teacher... '), nl,
retract(FormB, Period, TeacherA, _),
assert(FormB, Period, TeacherB, SubjectB).
find_entry([_| E], Form, PeriodA, TeacherA, SubjectA) :-
extends_object(TeacherA, teacher),
TeacherA::teach_period(PeriodA),
\+ filled_entry(_, PeriodA, TeacherA, _),
extends_object(SubjectA, subject),
TeacherA::teach_subject(SubjectA),
filled_entry(Form, PeriodB, _, SubjectA),
find_entry(E, Form, PeriodB, TeacherB, SubjectB),
SubjectA \= SubjectB,
write('Swap subject... '), nl,
retract(Form, PeriodB, _, SubjectA),
assert(Form, PeriodB, TeacherB, SubjectB).
assert(Form, Period, Teacher, Subject) :-
assertz(entry(Form, Period, Teacher, Subject)),
write('+ '),
write(Form), write(' - '),
write(Period), write(' - '),
write(Teacher), write(' - '),
write(Subject), nl.
retract(Form, Period, Teacher, Subject) :-
retract(entry(Form, Period, Teacher, Subject)),
write('- '),
write(Form), write(' - '),
write(Period), write(' - '),
write(Teacher), write(' - '),
write(Subject), nl.
:- end_object.