home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Simtel MSDOS 1992 December
/
simtel1292_SIMTEL_1292_Walnut_Creek.iso
/
msdos
/
prolog
/
prolog19.arc
/
ATNBLD.PRO
< prev
next >
Wrap
Text File
|
1986-05-05
|
4KB
|
117 lines
/* PROGRAM TO BUILD PRIMARY AUGMENTED TRANSISTION NETWORK
ATNBLD.PRO
11/24/85
*/
/* Build is the entry point into the program. It requires that the
program with standard routines and the program node, which is empty, have
already been consulted. */
/* The program requests the start and terminal nodes, the paths and
transistion conditions, then establishes a node program with a name
specified by the user. */
/* Ret removes any data from memory which might iterfere with network
construction. Term([],[]) is required to prevent failure when checkint
terminal conditions. Qend identifies all nodes for which there is a path
to a terminal node. The start node is identified initially since the
program will require this path be completed before any other can be
constructed. Termnode accepts the terminal nodes. Flow accepts the
transition arcs and conditions. */
build :- batch,ret(qend),nl,ret(arc),nl,ret(term),asserta(term([],[])),
nl,print('Enter the start node: '),read(Q0),
asserta(qend(Q0)),termnode,flow(Q0).
termnode :- print('Enter the next terminal node or the word done: '),
read(QT),
not(QT=done),
termck(QT),
assertfa(node,term(QT,[])),
asserta(qend(QT)),
termnode.
termnode :- !,true.
/* Flow requests transistions from node to node and adds each arc and new
node to the database. Qendck will continue to call flow until such time as
a terminal node has been reached then allow a new path to be initiated. */
flow(Q0) :- nl,print('Transisition from ',Q0,' to ? '),read(Qnext),
print(' on condition ? '),read(Con),
con(Q0,Con),arcck(Q0,Qnext,Con),
assertfz(node,arc(Q0,Qnext,Con)),
qendck(Q0,Qnext).
con(Q0,Con) :- condition(Con).
con(Q0,Con) :- nl,print(Con,' is an invalid condition. '),
flow(Q0).
termck(Qt) :- not(term(Qt,[]));
nl,print('Terminal node ',Qt,' already entered'),nl.
arcck(Q0,Qn,Z) :- not(arc(Q0,Qn,Z));
nl,print('Arc from ',Q0,' to ',Qn,' on ',Z,' exits.').
qendck(Q0,Qnext) :- qend(Qnext),(qend(Q0);asserta(qend(Q0))),nextnode.
qendck(Q0,Qnext) :- (qend(Q0);asserta(qend(Q0))),flow(Qnext).
/* Nextnode allows a new path to be initiated or the program to be
terminated. Before termination it calls pthck to insure there is a path to
each terminal node. Checkstart prevents an isolated node from being
entered. */
nextnode :- nl,print('Enter next start node or the word done ? '),
read(Ns),
not(Ns=done),
((checkstart(Ns),
flow(Ns));nextnode).
nextnode :- pthck,
!,retract(term([],[])),
nl,print('Network completed'),
listing(arc),listing(term),
nl,print('Enter name of new ATN file '),read(S),
update(node,S).
nextnode :- nextnode.
pthck :- term(Q,[]),not(Q=[]),not(arc(_,Q,_)),
nl,print('No path to terminal node ',Q),
!,fail.
pthck :- term([],[]).
checkstart(Ns) :- qend(Ns);
nl,print(Ns,' is an invalid node '),fail.
/* Condition lists the acceptable conditions for a transistion. */
condition(verb).
condition(noun).
condition(aux).
condition(prep).
condition(aux).
condition(pp).
condition(np).