home *** CD-ROM | disk | FTP | other *** search
/ Power-Programmierung / CD1.mdf / prolog / pdprolog / atnrev.pro < prev    next >
Text File  |  1986-05-05  |  4KB  |  150 lines

  1. /*                 Augmented Transition Network Program
  2.  
  3.                                 ATNREV.PRO
  4.  
  5.                                  11/24/85
  6. */
  7.  
  8.  
  9. /*  Standard routines for append & membership checking       */
  10.  
  11.  
  12. append([],L,L).
  13. append([Z|L1],L2,[Z|L3]) :- append(L1,L2,L3).
  14.  
  15. printstring([]).
  16. printstring([H|T]) :- put(H), printstring(T).
  17.  
  18. member(X,[X|_]).
  19. member(X,[_|Y]) :- member(X,Y).
  20.  
  21.  
  22. /*  The start module accepts a set of words, enclosed in brackets and
  23. separated by commas.  It calls wordck to verify that each of the words is
  24. in the vocuabulary set.   */
  25.  
  26.  
  27.  
  28. start :- batch,nl,print('INPUT'),nl,print('-----'),nl,
  29.          nl,print('Input sentence: '),read(S),nl,
  30.          print('The working set is ',S),wordck(S),!,
  31.          nl,nl,print('TRANSFERS'),nl,nl,print('---------'),nl,nl,
  32.          Parse=[],
  33.          trans(q0,Nq,Parse,S,S1).
  34.  
  35.  
  36. /*  Wordck checks for the end of the set, [], then if the word is in the
  37. vocabulary.  If not, it asks for the catagory, and adds it to the file
  38. WORD.TEM which is joined with the program after it has run.*/
  39.  
  40.  
  41.  
  42.  
  43.  
  44. wordck([])   :-   !,true.
  45.  
  46. wordck([H|T]) :- word(H,_,_),wordck(T).
  47.  
  48.  
  49. wordck([H|T]) :-  nl,print(H,' is not a recognized word '),
  50.                   nl,print(' enter verb,aux, .. '),read(Z),
  51.                   wordnew(H,Z),wordck(T).
  52.  
  53. wordnew(W,Z) :- assertz(word(W,Z,s)),open('word.tem',ar),
  54.                 nlf('word.tem'),
  55.                 printf('word.tem', 'word(', W, ',', Z, ').'),
  56.                 close('word.tem').
  57.  
  58.  
  59.  
  60.  
  61. /*  The arcs are defined in terms of from node, to node, condition.
  62. Terminal nodes are identified with the empty list.  Words are defined by
  63. type word name, type, and a character to be used in later examples with the
  64. number (plural or singular).  */
  65.  
  66.  
  67. arc(q0,q1,np).
  68. arc(q1,q2,verb).
  69. arc(q2,q2,np).
  70. arc(q2,q3,pp).
  71. arc(q0,q4,aux).
  72. arc(q4,q5,np).
  73. arc(q1,q5,aux).
  74. arc(q5,q2,verb).
  75.  
  76. term(q2,[]).
  77. term(q3,[]).
  78.  
  79.  
  80. word(boy,noun,s).
  81. word(boys,noun,pl).
  82. word(run,verb,pl).
  83. word(runs,verb,s).
  84. word(the,det,s).
  85.  
  86. arc(qnp,qnp1,det).
  87. arc(qnp,qnp1,_).
  88. arc(qnp1,qnp1,adj).
  89. arc(qnp1,qnp2,noun).
  90. arc(qpp,qnp,prep).
  91.  
  92.  
  93. /*  Trans recursively checks the conditions for transistion from the last
  94. node (Lq) to the next node (Nq).  Phrases are specifically treated as pp or
  95. np in order to allow the type of phrase to be identified in the parsed
  96. sentence.  */
  97.  
  98.  
  99.  
  100.  
  101. trans(Lq,_,Parse,S1,_) :- term(Lq,S1),nl,
  102.                           print('Completed ',Lq),
  103.                           nl,print(Parse).
  104.  
  105.  
  106. trans(Lq,Nq,Parse,[S0|S1],S1) :-  word(S0,Type,Nbr),
  107.                                   arc(Lq,Nq,Type),
  108.                                   nl,
  109.                                   print('Transition ',Lq,' ',Nq,' ',S0,
  110.                                             ' ',Type),
  111.                                   append(Parse,[[Type],S0],P1),
  112.                                   !,
  113.                                   trans(Nq,Z,P1,S1,S2).
  114.  
  115.  
  116. trans(Lq,Nq,Parse,S0,S1) :-  arc(Lq,Nq,np),
  117.                              ptrans(qnp,Nq,Lq,S0,[np],Parse).
  118.  
  119.  
  120. trans(Lq,Nq,Parse,S0,S1) :-  arc(Lq,Nq,pp),
  121.                              ptrans(qpp,Nq,Lq,S0,[pp],Parse).
  122.  
  123.  
  124.  
  125. trans(Lq,Nq,Parse,S0,S1) :- !,nl,
  126.                             print('The sentence failed at ',Lq),
  127.                             nl,print('Parsed ',Parse),
  128.                             nl,print('Left ',S0).
  129.  
  130. /*  Ptrans checks the transistion of the phrase network.  The first clause
  131. calls itself recursively until node qnp2 has been reached, which concludes
  132. the transistion.  Success results in trans being called  with the new node.
  133. Failure returns the trans with conditions unchanged.  */
  134.  
  135.  
  136.  
  137. ptrans(Bq,Nq,Lq,[S0|S1],Pr,Parse) :-  word(S0,Type,Nbr),
  138.                                 arc(Bq,Zq,Type),
  139.                                 append(Pr,[[Type],S0],P1),
  140.                                 !,
  141.                                 ptrans(Zq,Nq,Lq,S1,P1,Parse).
  142.  
  143. ptrans(qnp2,Nq,Lq,S0,Pr,Parse) :-  nl,
  144.                                    print('Transisiton ',Lq,' ',Nq),
  145.                                    nl,
  146.                                    print(Pr),
  147.                                    append(Parse,Pr,P1),
  148.                                    !,
  149.                                    trans(Nq,Rq,P1,S0,S1).
  150.