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

  1. /*              FINAL AUGMENTED TRANSISTION NETWORK PROGRAM
  2.  
  3.                                 ATNNEW1.PRO
  4.  
  5.                                  11/24/85
  6. */
  7.  
  8.  
  9. /*  Start is the entry into the program.  It requires that a set of
  10. standard routines has already been consulted (append in particular).  It
  11. allows the user to specify the network program, which can be build using
  12. ATNBLD.  Words is a file with the vocabulary set.  The sentences is a list
  13. of words separated by commas and enclosed in brackets.  Wordck verifies
  14. that the words are in the vocabulary set, and if not requests required
  15. data. Parse is the sentence as it is parsed.  Trans controls the flow from
  16. node to node.  */
  17.  
  18.  
  19. start :- nl,print('ATN network file? '),read(Fn),
  20.          consult(Fn),nl,
  21.          asserta(file(Fn)),
  22.          consult(words),nl,
  23.          batch,nl,print('INPUT'),nl,print('-----'),nl,
  24.          nl,print('Input sentence: '),read(S),nl,
  25.          print('The working set is ',S),wordck(S),
  26.          nl,nl,print('TRANSFERS'),nl,nl,print('---------'),nl,nl,
  27.          Parse=[],
  28.          trans(q0,Nq,Parse,S,S1).
  29.  
  30.  
  31.  
  32. wordck([])   :-   true.
  33.  
  34. wordck([H|T]) :- H(_,_),wordck(T).
  35.  
  36.  
  37. wordck([H|T]) :-  nl,print(H,' is not a recognized word '),
  38.                   nl,print(' enter verb,aux, .. '),read(Z),
  39.                   nl,print(' enter p or s or x  '),read(Z1),
  40.                   wordnew(H,Z,Z1),wordck(T).
  41.  
  42. wordnew(W,Z,Z1) :- assertfz(words,W(Z,Z1)).
  43.  
  44.  
  45. /*  Since the phrase transition network includes more specific procedures
  46. than the primary network, it is included in this program rather than in the
  47. network file consulted by start.  It could be more dynamic, but that was
  48. considered beyond the scope of this project.  */
  49.  
  50.  
  51. arc(qnp,qnp1,det).
  52. arc(qnp,qnp1,[]).
  53. arc(qnp1,qnp1,adj).
  54. arc(qnp1,qnp2,noun).
  55. arc(qpp,qnp,prep).
  56.  
  57.  
  58. /*  Trans controls the flow along the network.  If a terminal node has been
  59. reached and the entire sentence has been parsed, the agreement in number
  60. (plural or singular) between the subject and predicate is checked.  If they
  61. do not agree, this fact is displayed.  Update words creates a file
  62. WORDS.$$$ which contains the new vocabulary.
  63.  
  64. If a conditions for termination has not been met, trans checks for a
  65. transition word or a transistion phrase.  If none of these conditions are
  66. met, the sentence will not parse.
  67.  
  68. When a verb is encountered the number (singular or plural) is 'filed'.
  69. This procedure is unique for a specific network in which only one verb can
  70. be encountered.  */
  71.  
  72.  
  73. trans(Lq,_,Parse,S1,_) :- term(Lq,S1),nl,
  74.                           print('Completed ',Lq),
  75.                           nl,print(Parse),
  76.                        (  ( subj(Nbr),pred(Nbr) );
  77.                       (nl,print('The subject and predicate do not agree.')
  78.                           ) ),
  79.                           update(words),
  80.                           exec('erase words.pro'),
  81.                           exec('ren words.$$$ words.pro'),
  82.                           forget(words),
  83.                           file(Fn),
  84.                           forget(Fn),
  85.                           endclr.
  86.  
  87.  
  88. endclr :-  (not(file(_));ret(file)),(not(subj(_));ret(subj)),
  89.            (not(pred(_));ret(pred)).
  90.  
  91.  
  92. trans(Lq,Nq,Parse,[S0|S1],S1) :-  S0(Type,Nbr),
  93.                                   arc(Lq,Nq,Type),
  94.                                  ((Type=verb,asserta(pred(Nbr)));
  95.                                      not(type=verb)),
  96.                                   nl,
  97.                                   print('Transition ',Lq,' ',Nq,' ',S0,
  98.                                             ' ',Type),
  99.                                   append(Parse,[[Type],S0],P1),
  100.                                   trans(Nq,Z,P1,S1,S2).
  101.  
  102.  
  103. trans(Lq,Nq,Parse,S0,S1) :-  arc(Lq,Nq,np),
  104.                              ptrans(qnp,Nq,Lq,S0,[' '+np],Parse).
  105.  
  106.  
  107. trans(Lq,Nq,Parse,S0,S1) :-  arc(Lq,Nq,pp),
  108.                              ptrans(qpp,Nq,Lq,S0,[' '+pp],Parse).
  109.  
  110.  
  111.  
  112. trans(Lq,Nq,Parse,S0,S1) :- nl,
  113.                             print('The sentence failed at ',Lq),
  114.                             nl,print('Parsed ',Parse),
  115.                             nl,print('Left ',S0),
  116.                             endclr.
  117.  
  118.  
  119.  
  120. /*  Ptrans checks the transition of the phrase network.  It calls itself
  121. recursively until node qnp2 is reached.  Provisions are included to
  122. establish the number (plural or singular) of the subject, which is designed
  123. for a specific network in which the noun phrase in which the subject is
  124. located will be encountered before any other noun phrase.
  125.  
  126. The upon reaching qnp2 a check is made for the word 'and'.  If encountered,
  127. the number of the subject is changed to plural and a check for another noun
  128. phrase is initiated.
  129.  
  130. The spacing of the parathesis is to faciltiate reading of the code.  */
  131.  
  132.  
  133. ptrans(Bq,Nq,Lq,[S0|S1],Pr,Parse) :-  S0(Type,Nbr),
  134.                                 arc(Bq,Zq,Type),
  135.                           (
  136.                              (
  137.                                  not(Type=noun);
  138.  
  139.                                  subj(_)
  140.                                           );
  141.                                  asserta(subj(Nbr))
  142.                                                   ),
  143.                                 append(Pr,[[Type],S0],P1),
  144.                                 ptrans(Zq,Nq,Lq,S1,P1,Parse).
  145.  
  146. ptrans(Bq,Nq,Lq,S,Pr,Parse)   :-  arc(Bq,Zq,[]),
  147.                                   ptrans(Zq,Nq,Lq,S,Pr,Parse).
  148.  
  149.  
  150. ptrans(qnp2,Nq,Lq,[S0|S1],Pr,Parse) :-  S0=and,(Lq=q4;Lq=q0),
  151.                                        ( ( subj(_),retract(subj(_)) );
  152.                                          not(subj(_)) ),
  153.                                          asserta(subj(p)),
  154.                                           append(Pr,[and],P1),
  155.                                           ptrans(qnp,Nq,Lq,S1,P1,Parse).
  156.  
  157.  
  158. ptrans(qnp2,Nq,Lq,[S0|S1],Pr,Parse) :-  S0=and,
  159.                                           append(Pr,[and],P1),
  160.                                           ptrans(qnp,Nq,Lq,S1,P1,Parse).
  161.  
  162.  
  163.  
  164.  
  165. ptrans(qnp2,Nq,Lq,S0,Pr,Parse) :-  nl,
  166.                                    print('Transisiton ',Lq,' ',Nq),
  167.                                    nl,
  168.                                    print(Pr),
  169.                                    append(Parse,Pr,P1),
  170.                                    trans(Nq,Rq,P1,S0,S1).
  171.