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

  1. /*                 Augmented Transition Network Program
  2.  
  3.                                   ATN.PRO
  4.  
  5.                                  10/22/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,q(0,S).
  32.  
  33.  
  34.  
  35. /*  Wordck checks for the end of the set, [], then if the word is in the
  36. vocabulary.  If not, it asks for the catagory, and adds it to the file
  37. WORD.TEM which is joined with the program after it has run.*/
  38.  
  39.  
  40.  
  41.  
  42.  
  43. wordck([])   :-   !,true.
  44.  
  45. wordck([H|T]) :- word(H,Y),wordck(T).
  46.  
  47.  
  48. wordck([H|T]) :-  nl,print(H,' is not a recognized word '),
  49.                   nl,print(' enter verb,aux, .. '),read(Z),
  50.                   wordnew(H,Z),wordck(T).
  51.  
  52. wordnew(W,Z) :- assertz(word(W,Z)),open('word.tem',ar),
  53.                 nlf('word.tem'),
  54.                 printf('word.tem', 'word(', W, ',', Z, ').'),
  55.                 close('word.tem').
  56.  
  57.  
  58.  
  59.  
  60. /*  Trans checks the catagory of the current word (H) versus the catagory
  61. required to make a transistion (Z).  */
  62.  
  63.  
  64.  
  65.  
  66. trans(H,Z)   :-  word(H,X), member(X,[Z]).
  67.  
  68.  
  69. qfail(Nq,S,E)  :-  !, nl,nl,print('The sentence failed at ',Nq),nl,
  70.                  print('The sentence form to this node is ',E),nl,
  71.                  print('The rest of the sentence is ',S),qend1.
  72.  
  73.  
  74. qend(Z,E)  :-  nl,nl,print('OUTPUT'),nl,print('------'),nl,nl,
  75.                print('The sentence is:'),nl,nl,print(E),nl,nl,
  76.                print('The sentence is completed at node ',Z),qend1.
  77.  
  78.  
  79. qend1 :- open('word.tem',ar),nlf('word.tem'),
  80.          close('word.tem'),exec('ren atn.pro atn.sav'),
  81.          exec('copy atn.sav+word.tem atn.pro'),
  82.          exec('erase atn.sav'),exec('erase word.tem').
  83.  
  84.  
  85. /*    Print transfer from node to node */
  86.  
  87.  
  88.  
  89. qout(A,B,C,D,E,F) :- append(E,[C,'(',A,')'],F),
  90.                      nl, print('Transfer from node ',B,' to node ',D,
  91.                      ' by word ',A,' evaluated as a ',C).
  92.  
  93.  
  94.  
  95.  
  96. /*   Main program to check the conditions for transfer from node to node.
  97.      The first number is the number of the node, i.e. q(0.. is node 0.
  98.      The module either checks for a word type and transfers control
  99.      directly, or passes to np / pp the next node.                    */
  100.  
  101.  
  102. /*  Node 0 - aux to 4 / np to 1 / or fail          */
  103.  
  104.  
  105. q(0,[H|T])  :-  trans(H,[aux]),!,qout(H,0,[aux],4,E,F), q(4,T,F).
  106.  
  107. q(0,[H|T])  :-  np(H,T,1,[],0,[np]).
  108.  
  109. q(0,S)      :-  qfail(0,S,[]).
  110.  
  111.  
  112.  
  113.  
  114. /*  Node 1 - verb to 2 / aux to 5 / or fail    */
  115.  
  116.  
  117.  
  118. q(1,[H|T],E)  :-  trans(H,[verb]),!,qout(H,1,[verb],2,E,F), q(2,T,F).
  119.  
  120. q(1,[H|T],E)  :-  trans(H,[aux]),!, qout(H,1,[aux],5,E,F), q(5,T,F).
  121.  
  122. q(1,S,E)      :-  qfail(1,S,E).
  123.  
  124.  
  125.  
  126.  
  127. /*  Node 2 -  null to end / np to 2 / pp to 3 / or fail     */
  128.  
  129.  
  130.  
  131. q(2,H,E)      :- member(H,[[]]), !,
  132.                    qend(2,E).
  133.  
  134. q(2,[H|T],E)  :-  np(H,T,2,E,2,[np]).
  135.  
  136.  
  137. q(2,[H|T],E)  :-  pp(H,T,3,E,2,[pp]).
  138.  
  139. q(2,S,E)      :-  qfail(2,S,E).
  140.  
  141.  
  142.  
  143.  
  144. /*  Node 3 - null to end / or fail         */
  145.  
  146.  
  147. q(3,H,E)  :-
  148.                trans(H,[]), !,
  149.                qend(3,E).
  150.  
  151. q(3,S,E)      :-  qfail(3,S,E).
  152.  
  153.  
  154.  
  155.  
  156.  
  157. /*  Node 4 - np to 5 / or fail           */
  158.  
  159.  
  160.  
  161.  
  162. q(4,[H|T],E)  :-  np(H,T,5,E,4,[np]).
  163.  
  164. q(4,S,E)      :-  qfail(4,S,E).
  165.  
  166.  
  167.  
  168. /*  Node 5 - verb to 2 / or fail         */
  169.  
  170.  
  171. q(5,[H|T],E)  :-  trans(H,[verb]),!, qout(H,5,[verb],2,E,F), q(2,T,F).
  172.  
  173. q(5,S,E)      :-  qfail(5,S,E).
  174.  
  175.  
  176.  
  177.  
  178. /*  Noun phrase -  (det) (adj) (adj) .. noun        */
  179.  
  180. /*  The np1 clause is required to allow recursive calls for adj   */
  181.  
  182.  
  183.  
  184. np(H,[S|T],Nq,E,Lq,G)  :-  trans(H,[det]), !,
  185.                            append(G,['det(',H,')'],G1),
  186.                            np1([S|T],Nq,E,Lq,G1).
  187.  
  188.  
  189. np(H,Z,Nq,E,Lq,G)      :-  np1([H|Z],Nq,E,Lq,G).
  190.  
  191.  
  192.  
  193. np1([H|T],Nq,E,Lq,G)  :-  trans(H,[adj]),
  194.                           append(G,['adj(',H,')'],G1),
  195.                           np1(T,Nq,E,Lq,G1).
  196.  
  197.  
  198. np1([H|T],Nq,E,Lq,G)  :-
  199.                           trans(H,[noun]),!,nl,
  200.                           append(G,['noun(',H,')'],G1),
  201.                           append(E,G1,F),
  202.                           print('Transfer from node ',Lq,' to ',Nq),
  203.                           print(' by ',G1),q(Nq,T,F).
  204.  
  205.  
  206.  
  207.  
  208. /*  Prep phrase requires a prep followed by a np   */
  209.  
  210.  
  211.  
  212.  
  213. pp(H,[S|T],Nq,E,Lq,G)  :-  trans(H,[prep]),
  214.                            append(['prep(',H,')'],G,G1),
  215.                            np(S,T,Nq,E,Lq,G1).
  216.  
  217.  
  218.  
  219.  
  220.  
  221. /*   Word defines the vocabulary set                  */
  222.  
  223.  
  224. word(the,[det]).
  225. word(boy,[noun]).
  226. word(runs,[verb]).
  227. word(happy,[adj]).
  228. word(john,[noun]).
  229. word(can,[aux]).
  230. word(run,[verb]).
  231. word(a,[det]).
  232. word(big,[adj]).
  233. word(small,[adj]).
  234. word(girl,[noun]).
  235. word(dog,[noun]).
  236. word(on,[prep]).
  237. word(pretty,[adj]).
  238. word(fast,[adj]).
  239. word(barks,[verb]).
  240. word(to,[prep]).
  241. word([],[]).
  242.  
  243. word(giant, [noun]).
  244. word(is, [verb]).
  245.  
  246. word(giant, [noun]).
  247. word(is, [verb]).
  248. word(sleeps, [verb]).
  249.  
  250. word(mary, [noun]).
  251. word(likes, [verb]).
  252.  
  253.  
  254.  
  255.  
  256. word(fly, [verb]).
  257.  
  258.  
  259. word(rides, [verb]).
  260. word(large, [adj]).
  261. word(bike, [noun]).
  262. word(store, [noun]).
  263.  
  264.  
  265.  
  266. word(gull, [noun]).
  267. word(green, [adj]).
  268.  
  269. word(plane, [noun]).
  270. word(silver, [adj]).