% Items and their dependencies are coded using the two
% predicate 'item'.
% Each item is either of the form:
% item( item number, description, sl([positive support],[negative]) ).
% which says that the given item is dependent on the positive list
% being true and the negative list all false,
% or:
% item( item number, description, unknown ).
% which says that the item has not been given a support list and its
% truth is unknown. This is different from the empty support list
% 'sl([],[])', which says that the item does not depend on anything
% - it is a fact.
%
% In the book the items in the support list are given a + or - sign
% to say whether the item depends on their truth or falsity.
% However, in this Prolog representation, this is assumed from which
% list they are in.
item( 1, 'it is winter', sl([],[]) ).
item( 2, 'it is cold', sl([1],[3]) ).
item( 3, 'it is warm', unknown ).
% Before starting the truth maintenance procedure an easier
% to use dependency representation is constructed.
% For each pair X, Y where X depends on Y, a Prolog term
% is asserted tms_dep(X,Y,true) if it is a positive dependency
% and tms_dep(X,Y,false) if it is a negative dependency.
% This would be a very verbose representation to write, but
% is easier to use in Prolog than the list based representation.
% tms_clear_dep - removes and existing dependency information
% tms_build_dep - actually builds the new representation
% tms_build_dep_2 - runs through a list of items adding a dependency
% for each
tms_clear_dep :-
retractall(tms_dep(X,Y,PorN)),
assertz(tms_dep(-1,-2,null)). % null entry so that
% tms_dep always exists
tms_build_dep :-
item(Item,Desc,sl(Pos,Neg)),
tms_build_dep_2(Item,Pos,true),
tms_build_dep_2(Item,Neg,false),
fail.
tms_build_dep.
tms_build_dep_2(Item,[],PorN).
tms_build_dep_2(Item,[First|Rest],TorF) :-
assertz(tms_dep(Item,First,TorF)),
tms_build_dep_2(Item,Rest,TorF).
% tms_update completely rebuilds the truth values
% by setting everything to false and then setting
% the given facts to true using tms_do_set.
% (N.B. given facts = empty support list - 'sl([],[])')
% The setting of facts to true uses 'tms_do_set'
% which chases dependencies setting other items to
% true or false appropriately.
% At the end the whole system will be at a consistent truth state.
tms_update :- retractall(is_true(X,Y)), !,
tms_set_all_false,
tms_set_facts_true.
tms_set_all_false:-
item(Item,Desc,SL),
assertz(is_true(Item,false)),
fail.
tms_set_all_false.
tms_set_facts_true:-
item(Item,Desc,sl([],[])),
tms_do_set(Item,true),
fail.
tms_set_facts_true.
% tms_do_set sets the relevant item to be either true or false
% dependent on the second argument.
% If there is no change, then tms_do_set simply succeeds and does
% nothing.
% If there is a change, then this may have altered the truth of
% other items. In this case tms_do_dep is called to check and,
% if necessary, to update any dependent items
tms_do_set(Item,TorF) :-
tms_is_true(Item,TorF),!. % do nothing if no change
tms_do_set(Item,TorF) :-
tms_is_true(Item,NotTorF),
retract(is_true(Item,NotTorF)),
fail. % remove old fact if set
tms_do_set(Item,TorF) :-
assertz(is_true(Item,TorF)),
!, % end of sequential part
tms_do_dep(Item,TorF).
% tms_do_dep is called when an item changes its truth.
% It checks to see if any dependents of the item should change
% their truth. This can happen for two reasons.
% (i) If an item now agrees with a dependency then the dependent
% item MAY become true, but all other dependents must also be
% checked by calling tms_recheck
% (ii) If the item now disagrees witha dependency, the dependent
% item MUST become false. No other checking is necessary.
tms_do_dep(Item,TorF) :-
tms_dep(X,Item,DepTorF), % item now agrees with dependency
tms_do_dep2(X,TorF,DepTorF),
fail.
tms_do_dep(Item,TorF).
tms_do_dep2(X,TorF,TorF) :- % item now agrees with dependency
tms_recheck(X). % X may now be true, check it
tms_do_dep2(X,TorF,NotTorF) :-
\+ TorF = NotTorF, % item now disagrees with dependency
tms_do_set(X,false). % X must therefore be false
% An item must be false if any of its dependent items disagree.
% That is if the item is dependent on another item X and
% either X is false and is a positive dependent
% or X is true and is a negative dependent
tms_is_true(X,Y) :- clause(is_true(X,Y),_). % use clause to avoid predicate existence errors if there is no matching term
tms_is_false(Item) :-
tms_dep(Item,X,TorF),
tms_is_true(X,NotTorF),
\+ TorF = NotTorF.
% tms_recheck looks at dependencies to see if an Item
% which used to be false has now become true
tms_recheck(Item) :-
tms_is_true(Item,true). % if it is true already do nothing
tms_recheck(Item) :-
tms_is_true(Item,false),
\+ tms_is_false(Item), % are any dependencies wrong?
tms_do_set(Item,true). % if not it must be true!
% tms_init and tms_set are the predicates that you use to interact
% with the truth maintenance system.
% tms_init should be called when you start and subsequently
% if you want to reset the system.
% tms_set can only be used to set the truth of falsehood of any item
% which has an 'unknown' value. Other values are calculated using
% the dependencies in the support lists.
tms_init :- tms_clear_dep, fail.
tms_init :- tms_build_dep, fail.
tms_init :- tms_update.
tms_set(Desc,TorF) :-
item(Item,Desc,unknown),!,
tms_do_set(Item,TorF).
tms_set(Desc,TorF) :-
item(Item,Desc,sl(Pos,Neg)),
write(['Item ',Item,': ',Desc,' has support list, cannot be set true or false']), nl,
fail.
% tms_list prints the truth/falsity of all items
tms_list:- item(Item,Desc,SL),
tms_is_true(Item,TorF),
write([Item,': ',Desc,' - ',TorF]), nl,
fail.
tms_list.