xref: /csrg-svn/contrib/dungeon/np3.F (revision 35973)
1*35973SbosticC SYNMCH--	SYNTAX MATCHER
2*35973SbosticC
3*35973SbosticC COPYRIGHT 1980, INFOCOM COMPUTERS AND COMMUNICATIONS, CAMBRIDGE MA. 02142
4*35973SbosticC ALL RIGHTS RESERVED, COMMERCIAL USAGE STRICTLY PROHIBITED
5*35973SbosticC WRITTEN BY R. M. SUPNIK
6*35973SbosticC
7*35973SbosticC DECLARATIONS
8*35973SbosticC
9*35973SbosticC THIS ROUTINE DETAILS ON BIT 4 OF PRSFLG
10*35973SbosticC
11*35973Sbostic	LOGICAL FUNCTION SYNMCH()
12*35973Sbostic	IMPLICIT INTEGER(A-Z)
13*35973Sbostic	LOGICAL SYNEQL,TAKEIT
14*35973Sbostic#include "parser.h"
15*35973Sbostic#include "vocab.h"
16*35973Sbostic#include "debug.h"
17*35973SbosticC
18*35973SbosticC   THE FOLLOWING DATA STATEMENT WAS ORIGINALLY:
19*35973SbosticC
20*35973SbosticC	DATA R50MIN/1RA/
21*35973SbosticC
22*35973Sbostic	DATA R50MIN/1600/
23*35973SbosticC
24*35973Sbostic	SYNMCH=.FALSE.
25*35973Sbostic#ifdef debug
26*35973Sbostic	DFLAG=and(PRSFLG, 16).NE.0
27*35973Sbostic	if(dflag) write(0,*) "synflags=",sdir,sind,sstd,sflip,sdriv,svmask
28*35973Sbostic#endif
29*35973Sbostic	J=ACT
30*35973SbosticC						!SET UP PTR TO SYNTAX.
31*35973Sbostic	DRIVE=0
32*35973SbosticC						!NO DEFAULT.
33*35973Sbostic	DFORCE=0
34*35973SbosticC						!NO FORCED DEFAULT.
35*35973Sbostic	QPREP=and(OFLAG,OPREP)
36*35973Sbostic100	J=J+2
37*35973SbosticC						!FIND START OF SYNTAX.
38*35973Sbostic	IF((VVOC(J).LE.0).OR.(VVOC(J).GE.R50MIN)) GO TO 100
39*35973Sbostic	LIMIT=J+VVOC(J)+1
40*35973SbosticC						!COMPUTE LIMIT.
41*35973Sbostic	J=J+1
42*35973SbosticC						!ADVANCE TO NEXT.
43*35973SbosticC
44*35973Sbostic200	CALL UNPACK(J,NEWJ)
45*35973SbosticC						!UNPACK SYNTAX.
46*35973Sbostic#ifdef debug
47*35973Sbostic	IF(DFLAG) PRINT 60,O1,P1,DOBJ,DFL1,DFL2
48*35973Sbostic#ifdef NOCC
49*35973Sbostic60	FORMAT('SYNMCH INPUTS TO SYNEQL- ',5I7)
50*35973Sbostic#else NOCC
51*35973Sbostic60	FORMAT(' SYNMCH INPUTS TO SYNEQL- ',5I7)
52*35973Sbostic#endif NOCC
53*35973Sbostic#endif
54*35973Sbostic	SPREP=and(DOBJ,VPMASK)
55*35973Sbostic	IF(.NOT.SYNEQL(P1,O1,DOBJ,DFL1,DFL2)) GO TO 1000
56*35973Sbostic#ifdef debug
57*35973Sbostic	IF(DFLAG) PRINT 60,O2,P2,IOBJ,IFL1,IFL2
58*35973Sbostic#endif
59*35973Sbostic	SPREP=and(IOBJ,VPMASK)
60*35973Sbostic	IF(SYNEQL(P2,O2,IOBJ,IFL1,IFL2)) GO TO 6000
61*35973SbosticC
62*35973SbosticC SYNTAX MATCH FAILS, TRY NEXT ONE.
63*35973SbosticC
64*35973Sbostic	IF(O2) 3000,500,3000
65*35973SbosticC						!IF O2=0, SET DFLT.
66*35973Sbostic1000	IF(O1) 3000,500,3000
67*35973SbosticC						!IF O1=0, SET DFLT.
68*35973Sbostic500	IF((QPREP.EQ.0).OR.(QPREP.EQ.SPREP)) DFORCE=J
69*35973SbosticC						!IF PREP MCH.
70*35973Sbostic	IF((and(VFLAG,SDRIV)).NE.0) DRIVE=J
71*35973Sbostic3000	J=NEWJ
72*35973Sbostic	IF(J.LT.LIMIT) GO TO 200
73*35973SbosticC						!MORE TO DO?
74*35973SbosticC SYNMCH, PAGE 2
75*35973SbosticC
76*35973SbosticC MATCH HAS FAILED.  IF DEFAULT SYNTAX EXISTS, TRY TO SNARF
77*35973SbosticC ORPHANS OR GWIMS, OR MAKE NEW ORPHANS.
78*35973SbosticC
79*35973Sbostic#ifdef debug
80*35973Sbostic	IF(DFLAG) PRINT 20,DRIVE,DFORCE
81*35973Sbostic#ifdef NOCC
82*35973Sbostic20	FORMAT('SYNMCH, DRIVE=',2I6)
83*35973Sbostic#else NOCC
84*35973Sbostic20	FORMAT(' SYNMCH, DRIVE=',2I6)
85*35973Sbostic#endif NOCC
86*35973Sbostic#endif
87*35973Sbostic	IF(DRIVE.EQ.0) DRIVE=DFORCE
88*35973SbosticC						!NO DRIVER? USE FORCE.
89*35973Sbostic	IF(DRIVE.EQ.0) GO TO 10000
90*35973SbosticC						!ANY DRIVER?
91*35973Sbostic	CALL UNPACK(DRIVE,DFORCE)
92*35973SbosticC						!UNPACK DFLT SYNTAX.
93*35973SbosticC
94*35973SbosticC TRY TO FILL DIRECT OBJECT SLOT IF THAT WAS THE PROBLEM.
95*35973SbosticC
96*35973Sbostic	IF((and(VFLAG,SDIR).EQ.0).OR.(O1.NE.0)) GO TO 4000
97*35973SbosticC
98*35973SbosticC FIRST TRY TO SNARF ORPHAN OBJECT.
99*35973SbosticC
100*35973Sbostic	O1=and(OFLAG,OSLOT)
101*35973Sbostic	IF(O1.EQ.0) GO TO 3500
102*35973SbosticC						!ANY ORPHAN?
103*35973Sbostic	IF(SYNEQL(P1,O1,DOBJ,DFL1,DFL2)) GO TO 4000
104*35973SbosticC
105*35973SbosticC ORPHAN FAILS, TRY GWIM.
106*35973SbosticC
107*35973Sbostic3500	O1=GWIM(DOBJ,DFW1,DFW2)
108*35973SbosticC						!GET GWIM.
109*35973Sbostic#ifdef debug
110*35973Sbostic	IF(DFLAG) PRINT 30,O1
111*35973Sbostic#ifdef NOCC
112*35973Sbostic30	FORMAT('SYNMCH- DO GWIM= ',I6)
113*35973Sbostic#else NOCC
114*35973Sbostic30	FORMAT(' SYNMCH- DO GWIM= ',I6)
115*35973Sbostic#endif NOCC
116*35973Sbostic#endif debug
117*35973Sbostic	IF(O1.GT.0) GO TO 4000
118*35973SbosticC						!TEST RESULT.
119*35973Sbostic	CALL ORPHAN(-1,ACT,0,and(DOBJ,VPMASK),0)
120*35973Sbostic	CALL RSPEAK(623)
121*35973Sbostic	RETURN
122*35973SbosticC
123*35973SbosticC TRY TO FILL INDIRECT OBJECT SLOT IF THAT WAS THE PROBLEM.
124*35973SbosticC
125*35973Sbostic4000	IF((and(VFLAG,SIND).EQ.0).OR.(O2.NE.0)) GO TO 6000
126*35973Sbostic	O2=GWIM(IOBJ,IFW1,IFW2)
127*35973SbosticC						!GWIM.
128*35973Sbostic#ifdef debug
129*35973Sbostic	IF(DFLAG) PRINT 40,O2
130*35973Sbostic#ifdef NOCC
131*35973Sbostic40	FORMAT('SYNMCH- IO GWIM= ',I6)
132*35973Sbostic#else NOCC
133*35973Sbostic40	FORMAT(' SYNMCH- IO GWIM= ',I6)
134*35973Sbostic#endif NOCC
135*35973Sbostic#endif debug
136*35973Sbostic	IF(O2.GT.0) GO TO 6000
137*35973Sbostic	IF(O1.EQ.0) O1=and(OFLAG,OSLOT)
138*35973Sbostic	CALL ORPHAN(-1,ACT,O1,and(DOBJ,VPMASK),0)
139*35973Sbostic	CALL RSPEAK(624)
140*35973Sbostic	RETURN
141*35973SbosticC
142*35973SbosticC TOTAL CHOMP
143*35973SbosticC
144*35973Sbostic10000	CALL RSPEAK(601)
145*35973SbosticC						!CANT DO ANYTHING.
146*35973Sbostic	RETURN
147*35973SbosticC SYNMCH, PAGE 3
148*35973SbosticC
149*35973SbosticC NOW TRY TO TAKE INDIVIDUAL OBJECTS AND
150*35973SbosticC IN GENERAL CLEAN UP THE PARSE VECTOR.
151*35973SbosticC
152*35973Sbostic6000	IF(and(VFLAG,SFLIP).EQ.0) GO TO 5000
153*35973Sbostic	J=O1
154*35973SbosticC						!YES.
155*35973Sbostic	O1=O2
156*35973Sbostic	O2=J
157*35973SbosticC
158*35973Sbostic5000	PRSA=and(VFLAG,SVMASK)
159*35973Sbostic	PRSO=O1
160*35973SbosticC						!GET DIR OBJ.
161*35973Sbostic	PRSI=O2
162*35973SbosticC						!GET IND OBJ.
163*35973Sbostic	IF(.NOT.TAKEIT(PRSO,DOBJ)) RETURN
164*35973SbosticC						!TRY TAKE.
165*35973Sbostic	IF(.NOT.TAKEIT(PRSI,IOBJ)) RETURN
166*35973SbosticC						!TRY TAKE.
167*35973Sbostic	SYNMCH=.TRUE.
168*35973Sbostic#ifdef debug
169*35973Sbostic	IF(DFLAG) PRINT 50,SYNMCH,PRSA,PRSO,PRSI,ACT,O1,O2
170*35973Sbostic#ifdef NOCC
171*35973Sbostic50	FORMAT('SYNMCH- RESULTS ',L1,6I7)
172*35973Sbostic#else NOCC
173*35973Sbostic50	FORMAT(' SYNMCH- RESULTS ',L1,6I7)
174*35973Sbostic#endif NOCC
175*35973Sbostic#endif
176*35973Sbostic	RETURN
177*35973SbosticC
178*35973Sbostic	END
179*35973SbosticC UNPACK-	UNPACK SYNTAX SPECIFICATION, ADV POINTER
180*35973SbosticC
181*35973SbosticC DECLARATIONS
182*35973SbosticC
183*35973Sbostic	SUBROUTINE UNPACK(OLDJ,J)
184*35973Sbostic	IMPLICIT INTEGER(A-Z)
185*35973Sbostic#include "vocab.h"
186*35973Sbostic#include "parser.h"
187*35973SbosticC
188*35973Sbostic	DO 10 I=1,11
189*35973SbosticC						!CLEAR SYNTAX.
190*35973Sbostic	  SYN(I)=0
191*35973Sbostic10	CONTINUE
192*35973SbosticC
193*35973Sbostic	VFLAG=VVOC(OLDJ)
194*35973Sbostic	J=OLDJ+1
195*35973Sbostic	IF(and(VFLAG,SDIR).EQ.0) RETURN
196*35973Sbostic	DFL1=-1
197*35973SbosticC						!ASSUME STD.
198*35973Sbostic	DFL2=-1
199*35973Sbostic	IF(and(VFLAG,SSTD).EQ.0) GO TO 100
200*35973Sbostic	DFW1=-1
201*35973SbosticC						!YES.
202*35973Sbostic	DFW2=-1
203*35973Sbostic	DOBJ=VABIT+VRBIT+VFBIT
204*35973Sbostic	GO TO 200
205*35973SbosticC
206*35973Sbostic100	DOBJ=VVOC(J)
207*35973SbosticC						!NOT STD.
208*35973Sbostic	DFW1=VVOC(J+1)
209*35973Sbostic	DFW2=VVOC(J+2)
210*35973Sbostic	J=J+3
211*35973Sbostic	IF(and(DOBJ,VEBIT).EQ.0) GO TO 200
212*35973Sbostic	DFL1=DFW1
213*35973SbosticC						!YES.
214*35973Sbostic	DFL2=DFW2
215*35973SbosticC
216*35973Sbostic200	IF(and(VFLAG,SIND).EQ.0) RETURN
217*35973Sbostic	IFL1=-1
218*35973SbosticC						!ASSUME STD.
219*35973Sbostic	IFL2=-1
220*35973Sbostic	IOBJ=VVOC(J)
221*35973Sbostic	IFW1=VVOC(J+1)
222*35973Sbostic	IFW2=VVOC(J+2)
223*35973Sbostic	J=J+3
224*35973Sbostic	IF(and(IOBJ,VEBIT).EQ.0) RETURN
225*35973Sbostic	IFL1=IFW1
226*35973SbosticC						!YES.
227*35973Sbostic	IFL2=IFW2
228*35973Sbostic	RETURN
229*35973SbosticC
230*35973Sbostic	END
231*35973SbosticC SYNEQL-	TEST FOR SYNTAX EQUALITY
232*35973SbosticC
233*35973SbosticC DECLARATIONS
234*35973SbosticC
235*35973Sbostic	LOGICAL FUNCTION SYNEQL(PREP,OBJ,SPREP,SFL1,SFL2)
236*35973Sbostic	IMPLICIT INTEGER(A-Z)
237*35973Sbostic#include "objects.h"
238*35973Sbostic#include "parser.h"
239*35973SbosticC
240*35973Sbostic	IF(OBJ.EQ.0) GO TO 100
241*35973SbosticC						!ANY OBJECT?
242*35973Sbostic	SYNEQL=(PREP.EQ.and(SPREP,VPMASK)).AND.
243*35973Sbostic&		(or(and(SFL1,OFLAG1(OBJ)),
244*35973Sbostic&		  and(SFL2,OFLAG2(OBJ))).NE.0)
245*35973Sbostic	RETURN
246*35973SbosticC
247*35973Sbostic100	SYNEQL=(PREP.EQ.0).AND.(SFL1.EQ.0).AND.(SFL2.EQ.0)
248*35973Sbostic	RETURN
249*35973SbosticC
250*35973Sbostic	END
251*35973SbosticC TAKEIT-	PARSER BASED TAKE OF OBJECT
252*35973SbosticC
253*35973SbosticC DECLARATIONS
254*35973SbosticC
255*35973Sbostic	LOGICAL FUNCTION TAKEIT(OBJ,SFLAG)
256*35973Sbostic	IMPLICIT INTEGER(A-Z)
257*35973Sbostic#include "parser.h"
258*35973Sbostic	COMMON /STAR/ MBASE,STRBIT
259*35973Sbostic#include "gamestate.h"
260*35973Sbostic#include "state.h"
261*35973Sbostic#include "objects.h"
262*35973Sbostic#include "oflags.h"
263*35973Sbostic#include "advers.h"
264*35973SbosticC TAKEIT, PAGE 2
265*35973SbosticC
266*35973Sbostic	TAKEIT=.FALSE.
267*35973SbosticC						!ASSUME LOSES.
268*35973Sbostic	IF((OBJ.EQ.0).OR.(OBJ.GT.STRBIT)) GO TO 4000
269*35973SbosticC						!NULL/STARS WIN.
270*35973Sbostic	ODO2=ODESC2(OBJ)
271*35973SbosticC						!GET DESC.
272*35973Sbostic	X=OCAN(OBJ)
273*35973SbosticC						!GET CONTAINER.
274*35973Sbostic	IF((X.EQ.0).OR.(and(SFLAG,VFBIT).EQ.0)) GO TO 500
275*35973Sbostic	IF(and(OFLAG2(X),OPENBT).NE.0) GO TO 500
276*35973Sbostic	CALL RSPSUB(566,ODO2)
277*35973SbosticC						!CANT REACH.
278*35973Sbostic	RETURN
279*35973SbosticC
280*35973Sbostic500	IF(and(SFLAG,VRBIT).EQ.0) GO TO 1000
281*35973Sbostic	IF(and(SFLAG,VTBIT).EQ.0) GO TO 2000
282*35973SbosticC
283*35973SbosticC SHOULD BE IN ROOM (VRBIT NE 0) AND CAN BE TAKEN (VTBIT NE 0)
284*35973SbosticC
285*35973Sbostic	IF(SCHLST(0,0,HERE,0,0,OBJ).LE.0) GO TO 4000
286*35973SbosticC						!IF NOT, OK.
287*35973SbosticC
288*35973SbosticC ITS IN THE ROOM AND CAN BE TAKEN.
289*35973SbosticC
290*35973Sbostic	IF((and(OFLAG1(OBJ),TAKEBT).NE.0).AND.
291*35973Sbostic&		(and(OFLAG2(OBJ),TRYBT).EQ.0)) GO TO 3000
292*35973SbosticC
293*35973SbosticC NOT TAKEABLE.  IF WE CARE, FAIL.
294*35973SbosticC
295*35973Sbostic	IF(and(SFLAG,VCBIT).EQ.0) GO TO 4000
296*35973Sbostic	CALL RSPSUB(445,ODO2)
297*35973Sbostic	RETURN
298*35973SbosticC
299*35973SbosticC 1000--	IT SHOULD NOT BE IN THE ROOM.
300*35973SbosticC 2000--	IT CANT BE TAKEN.
301*35973SbosticC
302*35973Sbostic2000	IF(and(SFLAG,VCBIT).EQ.0) GO TO 4000
303*35973Sbostic1000	IF(SCHLST(0,0,HERE,0,0,OBJ).LE.0) GO TO 4000
304*35973Sbostic	CALL RSPSUB(665,ODO2)
305*35973Sbostic	RETURN
306*35973SbosticC TAKEIT, PAGE 3
307*35973SbosticC
308*35973SbosticC OBJECT IS IN THE ROOM, CAN BE TAKEN BY THE PARSER,
309*35973SbosticC AND IS TAKEABLE IN GENERAL.  IT IS NOT A STAR.
310*35973SbosticC TAKING IT SHOULD NOT HAVE SIDE AFFECTS.
311*35973SbosticC IF IT IS INSIDE SOMETHING, THE CONTAINER IS OPEN.
312*35973SbosticC THE FOLLOWING CODE IS LIFTED FROM SUBROUTINE TAKE.
313*35973SbosticC
314*35973Sbostic3000	IF(OBJ.NE.AVEHIC(WINNER)) GO TO 3500
315*35973SbosticC						!TAKE VEHICLE?
316*35973Sbostic	CALL RSPEAK(672)
317*35973Sbostic	RETURN
318*35973SbosticC
319*35973Sbostic3500	IF(((X.NE.0).AND.(OADV(X).EQ.WINNER)).OR.
320*35973Sbostic&	 ((WEIGHT(0,OBJ,WINNER)+OSIZE(OBJ)).LE.MXLOAD))
321*35973Sbostic&	 GO TO 3700
322*35973Sbostic	CALL RSPEAK(558)
323*35973SbosticC						!TOO BIG.
324*35973Sbostic	RETURN
325*35973SbosticC
326*35973Sbostic3700	CALL NEWSTA(OBJ,559,0,0,WINNER)
327*35973SbosticC						!DO TAKE.
328*35973Sbostic	OFLAG2(OBJ)=or(OFLAG2(OBJ),TCHBT)
329*35973Sbostic	CALL SCRUPD(OFVAL(OBJ))
330*35973Sbostic	OFVAL(OBJ)=0
331*35973SbosticC
332*35973Sbostic4000	TAKEIT=.TRUE.
333*35973SbosticC						!SUCCESS.
334*35973Sbostic	RETURN
335*35973SbosticC
336*35973Sbostic	END
337*35973SbosticC
338*35973SbosticC GWIM- GET WHAT I MEAN IN AMBIGOUS SITUATIONS
339*35973SbosticC
340*35973SbosticC DECLARATIONS
341*35973SbosticC
342*35973Sbostic	INTEGER FUNCTION GWIM(SFLAG,SFW1,SFW2)
343*35973Sbostic	IMPLICIT INTEGER(A-Z)
344*35973Sbostic	LOGICAL TAKEIT,NOCARE
345*35973Sbostic#include "parser.h"
346*35973Sbostic	COMMON /STAR/ MBASE,STRBIT
347*35973Sbostic#include "gamestate.h"
348*35973Sbostic#include "objects.h"
349*35973Sbostic#include "oflags.h"
350*35973Sbostic#include "advers.h"
351*35973SbosticC GWIM, PAGE 2
352*35973SbosticC
353*35973Sbostic	GWIM=-1
354*35973SbosticC						!ASSUME LOSE.
355*35973Sbostic	AV=AVEHIC(WINNER)
356*35973Sbostic	NOBJ=0
357*35973Sbostic	NOCARE=and(SFLAG,VCBIT).EQ.0
358*35973SbosticC
359*35973SbosticC FIRST SEARCH ADVENTURER
360*35973SbosticC
361*35973Sbostic	IF(and(SFLAG,VABIT).NE.0)
362*35973Sbostic&		NOBJ=FWIM(SFW1,SFW2,0,0,WINNER,NOCARE)
363*35973Sbostic	IF(and(SFLAG,VRBIT).NE.0) GO TO 100
364*35973Sbostic50	GWIM=NOBJ
365*35973Sbostic	RETURN
366*35973SbosticC
367*35973SbosticC ALSO SEARCH ROOM
368*35973SbosticC
369*35973Sbostic100	ROBJ=FWIM(SFW1,SFW2,HERE,0,0,NOCARE)
370*35973Sbostic	IF(ROBJ) 500,50,200
371*35973SbosticC						!TEST RESULT.
372*35973SbosticC
373*35973SbosticC ROBJ > 0
374*35973SbosticC
375*35973Sbostic200	IF((AV.EQ.0).OR.(ROBJ.EQ.AV).OR.
376*35973Sbostic&		(and(OFLAG2(ROBJ),FINDBT).NE.0)) GO TO 300
377*35973Sbostic	IF(OCAN(ROBJ).NE.AV) GO TO 50
378*35973SbosticC						!UNREACHABLE? TRY NOBJ
379*35973Sbostic300	IF(NOBJ.NE.0) RETURN
380*35973SbosticC						!IF AMBIGUOUS, RETURN.
381*35973Sbostic	IF(.NOT.TAKEIT(ROBJ,SFLAG)) RETURN
382*35973SbosticC						!IF UNTAKEABLE, RETURN
383*35973Sbostic	GWIM=ROBJ
384*35973Sbostic500	RETURN
385*35973SbosticC
386*35973Sbostic	END
387