xref: /csrg-svn/contrib/dungeon/dsub.F (revision 35973)
1*35973SbosticC RESIDENT SUBROUTINES FOR DUNGEON
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 RSPEAK-- OUTPUT RANDOM MESSAGE ROUTINE
8*35973SbosticC
9*35973SbosticC CALLED BY--
10*35973SbosticC
11*35973SbosticC	CALL RSPEAK(MSGNUM)
12*35973SbosticC
13*35973Sbostic	SUBROUTINE RSPEAK(N)
14*35973Sbostic	IMPLICIT INTEGER(A-Z)
15*35973SbosticC
16*35973Sbostic	CALL RSPSB2(N,0,0)
17*35973Sbostic	RETURN
18*35973Sbostic	END
19*35973SbosticC RSPSUB-- OUTPUT RANDOM MESSAGE WITH SUBSTITUTABLE ARGUMENT
20*35973SbosticC
21*35973SbosticC CALLED BY--
22*35973SbosticC
23*35973SbosticC	CALL RSPSUB(MSGNUM,SUBNUM)
24*35973SbosticC
25*35973Sbostic	SUBROUTINE RSPSUB(N,S1)
26*35973Sbostic	IMPLICIT INTEGER(A-Z)
27*35973SbosticC
28*35973Sbostic	CALL RSPSB2(N,S1,0)
29*35973Sbostic	RETURN
30*35973Sbostic	END
31*35973SbosticC RSPSB2-- OUTPUT RANDOM MESSAGE WITH UP TO TWO SUBSTITUTABLE ARGUMENTS
32*35973SbosticC
33*35973SbosticC CALLED BY--
34*35973SbosticC
35*35973SbosticC	CALL RSPSB2(MSGNUM,SUBNUM1,SUBNUM2)
36*35973SbosticC
37*35973Sbostic	SUBROUTINE    RSPSB2(N,S1,S2)
38*35973Sbostic	IMPLICIT      INTEGER(A-Z)
39*35973Sbostic#ifndef PDP
40*35973Sbostic	CHARACTER*74  B1,B2,B3
41*35973Sbostic	INTEGER*2     OLDREC,NEWREC,JREC
42*35973Sbostic#endif PDP
43*35973SbosticC
44*35973SbosticC DECLARATIONS
45*35973SbosticC
46*35973Sbostic#include "gamestate.h"
47*35973SbosticC
48*35973Sbostic#ifdef PDP
49*35973Sbostic	TELFLG=.TRUE.
50*35973SbosticC
51*35973SbosticC	use C routine to access data base
52*35973SbosticC
53*35973Sbostic	call	rspsb3(N,S1,S2)
54*35973Sbostic	return
55*35973Sbostic#else
56*35973Sbostic#include "mindex.h"
57*35973Sbostic#include "io.h"
58*35973SbosticC
59*35973SbosticC CONVERT ALL ARGUMENTS FROM DICTIONARY NUMBERS (IF POSITIVE)
60*35973SbosticC TO ABSOLUTE RECORD NUMBERS.
61*35973SbosticC
62*35973Sbostic	X=N
63*35973SbosticC						!SET UP WORK VARIABLES.
64*35973Sbostic	Y=S1
65*35973Sbostic	Z=S2
66*35973Sbostic	IF(X.GT.0) X=RTEXT(X)
67*35973SbosticC						!IF >0, LOOK UP IN RTEXT.
68*35973Sbostic	IF(Y.GT.0) Y=RTEXT(Y)
69*35973Sbostic	IF(Z.GT.0) Z=RTEXT(Z)
70*35973Sbostic	X=IABS(X)
71*35973SbosticC						!TAKE ABS VALUE.
72*35973Sbostic	Y=IABS(Y)
73*35973Sbostic	Z=IABS(Z)
74*35973Sbostic	IF(X.EQ.0) RETURN
75*35973SbosticC						!ANYTHING TO DO?
76*35973Sbostic	TELFLG=.TRUE.
77*35973SbosticC						!SAID SOMETHING.
78*35973SbosticC
79*35973Sbostic	READ(UNIT=DBCH,REC=X) OLDREC,B1
80*35973SbosticC
81*35973Sbostic100	DO 150 I=1,74
82*35973Sbostic	  X1=and(X,31)+I
83*35973Sbostic	  B1(I:I)=char(xor(ichar(B1(I:I)),X1))
84*35973Sbostic150	CONTINUE
85*35973SbosticC
86*35973Sbostic200	IF(Y.EQ.0) GO TO 400
87*35973SbosticC						!ANY SUBSTITUTABLE?
88*35973Sbostic	DO 300 I=1,74
89*35973SbosticC						!YES, LOOK FOR #.
90*35973Sbostic	  IF(B1(I:I).EQ.'#') GO TO 1000
91*35973Sbostic300	CONTINUE
92*35973SbosticC
93*35973Sbostic400	DO 500 I=74,1,-1
94*35973SbosticC						!BACKSCAN FOR BLANKS.
95*35973Sbostic	  IF(B1(I:I).NE.' ') GO TO 600
96*35973Sbostic500	CONTINUE
97*35973SbosticC
98*35973Sbostic600	WRITE(OUTCH,650) (B1(J:J),J=1,I)
99*35973Sbostic#ifdef NOCC
100*35973Sbostic650	FORMAT(74A1)
101*35973Sbostic#else NOCC
102*35973Sbostic650	FORMAT(1X,74A1)
103*35973Sbostic#endif NOCC
104*35973Sbostic	X=X+1
105*35973SbosticC						!ON TO NEXT RECORD.
106*35973Sbostic	READ(UNIT=DBCH,REC=X) NEWREC,B1
107*35973Sbostic	IF(OLDREC.EQ.NEWREC) GO TO 100
108*35973SbosticC						!CONTINUATION?
109*35973Sbostic	RETURN
110*35973SbosticC						!NO, EXIT.
111*35973SbosticC
112*35973SbosticC SUBSTITUTION WITH SUBSTITUTABLE AVAILABLE.
113*35973SbosticC I IS INDEX OF # IN B1.
114*35973SbosticC Y IS NUMBER OF RECORD TO SUBSTITUTE.
115*35973SbosticC
116*35973SbosticC PROCEDURE:
117*35973SbosticC   1) COPY REST OF B1 TO B2
118*35973SbosticC   2) READ SUBSTITUTABLE OVER B1
119*35973SbosticC   3) RESTORE TAIL OF ORIGINAL B1
120*35973SbosticC
121*35973SbosticC THE IMPLICIT ASSUMPTION HERE IS THAT THE SUBSTITUTABLE STRING
122*35973SbosticC IS VERY SHORT (i.e. MUCH LESS THAN ONE RECORD).
123*35973SbosticC
124*35973Sbostic1000	K2=1
125*35973SbosticC						!TO
126*35973Sbostic	DO 1100 K1=I+1,74
127*35973SbosticC						!COPY REST OF B1.
128*35973Sbostic	  B2(K2:K2)=B1(K1:K1)
129*35973Sbostic	  K2=K2+1
130*35973Sbostic1100	CONTINUE
131*35973SbosticC
132*35973SbosticC   READ SUBSTITUTE STRING INTO B3, AND DECRYPT IT:
133*35973SbosticC
134*35973Sbostic	READ(UNIT=DBCH,REC=Y) JREC,B3
135*35973Sbostic	DO 1150 K1=1,74
136*35973Sbostic	  X1=and(Y,31)+K1
137*35973Sbostic	  B3(K1:K1)=char(xor(ICHAR(B3(K1:K1)),X1))
138*35973Sbostic1150	CONTINUE
139*35973SbosticC
140*35973SbosticC   FILL REMAINDER OF B1 WITH CHARACTERS FROM B3:
141*35973SbosticC
142*35973Sbostic	K2=1
143*35973Sbostic	DO 1180 K1=I,74
144*35973Sbostic	  B1(K1:K1)=B3(K2:K2)
145*35973Sbostic	  K2=K2+1
146*35973Sbostic1180	CONTINUE
147*35973SbosticC
148*35973SbosticC   FIND END OF SUBSTITUTE STRING IN B1:
149*35973SbosticC
150*35973Sbostic	DO 1200 J=74,1,-1
151*35973SbosticC						!ELIM TRAILING BLANKS.
152*35973Sbostic	  IF(B1(J:J).NE.' ') GO TO 1300
153*35973Sbostic1200	CONTINUE
154*35973SbosticC
155*35973SbosticC   PUT TAIL END OF B1 (NOW IN B2) BACK INTO B1 AFTER SUBSTITUTE STRING:
156*35973SbosticC
157*35973Sbostic1300	K1=1
158*35973SbosticC						!FROM
159*35973Sbostic	DO 1400 K2=J+1,74
160*35973SbosticC						!COPY REST OF B1 BACK.
161*35973Sbostic	  B1(K2:K2)=B2(K1:K1)
162*35973Sbostic	  K1=K1+1
163*35973Sbostic1400	CONTINUE
164*35973SbosticC
165*35973Sbostic	Y=Z
166*35973SbosticC						!SET UP FOR NEXT
167*35973Sbostic	Z=0
168*35973SbosticC						!SUBSTITUTION AND
169*35973Sbostic	GO TO 200
170*35973SbosticC						!RECHECK LINE.
171*35973Sbostic#endif PDP
172*35973SbosticC
173*35973Sbostic	END
174*35973SbosticC OBJACT-- APPLY OBJECTS FROM PARSE VECTOR
175*35973SbosticC
176*35973SbosticC DECLARATIONS
177*35973SbosticC
178*35973Sbostic	LOGICAL FUNCTION OBJACT(X)
179*35973Sbostic	IMPLICIT INTEGER (A-Z)
180*35973Sbostic	LOGICAL OAPPLI
181*35973Sbostic#include "parser.h"
182*35973Sbostic#include "objects.h"
183*35973SbosticC
184*35973Sbostic	OBJACT=.TRUE.
185*35973SbosticC						!ASSUME WINS.
186*35973Sbostic	IF(PRSI.EQ.0) GO TO 100
187*35973SbosticC						!IND OBJECT?
188*35973Sbostic	IF(OAPPLI(OACTIO(PRSI),0)) RETURN
189*35973SbosticC						!YES, LET IT HANDLE.
190*35973SbosticC
191*35973Sbostic100	IF(PRSO.EQ.0) GO TO 200
192*35973SbosticC						!DIR OBJECT?
193*35973Sbostic	IF(OAPPLI(OACTIO(PRSO),0)) RETURN
194*35973SbosticC						!YES, LET IT HANDLE.
195*35973SbosticC
196*35973Sbostic200	OBJACT=.FALSE.
197*35973SbosticC						!LOSES.
198*35973Sbostic	RETURN
199*35973Sbostic	END
200*35973Sbostic#ifndef PDP
201*35973SbosticC BUG-- REPORT FATAL SYSTEM ERROR
202*35973SbosticC
203*35973SbosticC CALLED BY--
204*35973SbosticC
205*35973SbosticC	CALL BUG(NO,PAR)
206*35973SbosticC
207*35973Sbostic	SUBROUTINE BUG(A,B)
208*35973Sbostic	IMPLICIT INTEGER(A-Z)
209*35973Sbostic#include "debug.h"
210*35973SbosticC
211*35973Sbostic	PRINT 100,A,B
212*35973Sbostic	IF(DBGFLG.NE.0) RETURN
213*35973Sbostic	CALL EXIT
214*35973SbosticC
215*35973Sbostic#ifdef NOCC
216*35973Sbostic100	FORMAT('PROGRAM ERROR ',I2,', PARAMETER=',I6)
217*35973Sbostic#else NOCC
218*35973Sbostic100	FORMAT(' PROGRAM ERROR ',I2,', PARAMETER=',I6)
219*35973Sbostic#endif NOCC
220*35973Sbostic	END
221*35973Sbostic#endif PDP
222*35973SbosticC NEWSTA-- SET NEW STATUS FOR OBJECT
223*35973SbosticC
224*35973SbosticC CALLED BY--
225*35973SbosticC
226*35973SbosticC	CALL NEWSTA(OBJECT,STRING,NEWROOM,NEWCON,NEWADV)
227*35973SbosticC
228*35973Sbostic	SUBROUTINE NEWSTA(O,R,RM,CN,AD)
229*35973Sbostic	IMPLICIT INTEGER(A-Z)
230*35973Sbostic#include "objects.h"
231*35973SbosticC
232*35973Sbostic	CALL RSPEAK(R)
233*35973Sbostic	OROOM(O)=RM
234*35973Sbostic	OCAN(O)=CN
235*35973Sbostic	OADV(O)=AD
236*35973Sbostic	RETURN
237*35973Sbostic	END
238*35973SbosticC QHERE-- TEST FOR OBJECT IN ROOM
239*35973SbosticC
240*35973SbosticC DECLARATIONS
241*35973SbosticC
242*35973Sbostic	LOGICAL FUNCTION QHERE(OBJ,RM)
243*35973Sbostic	IMPLICIT INTEGER (A-Z)
244*35973Sbostic#include "objects.h"
245*35973SbosticC
246*35973Sbostic	QHERE=.TRUE.
247*35973Sbostic	IF(OROOM(OBJ).EQ.RM) RETURN
248*35973SbosticC						!IN ROOM?
249*35973Sbostic	DO 100 I=1,R2LNT
250*35973SbosticC						!NO, SCH ROOM2.
251*35973Sbostic	  IF((OROOM2(I).EQ.OBJ).AND.(RROOM2(I).EQ.RM)) RETURN
252*35973Sbostic100	CONTINUE
253*35973Sbostic	QHERE=.FALSE.
254*35973SbosticC						!NOT PRESENT.
255*35973Sbostic	RETURN
256*35973Sbostic	END
257*35973SbosticC QEMPTY-- TEST FOR OBJECT EMPTY
258*35973SbosticC
259*35973SbosticC DECLARATIONS
260*35973SbosticC
261*35973Sbostic	LOGICAL FUNCTION QEMPTY(OBJ)
262*35973Sbostic	IMPLICIT INTEGER (A-Z)
263*35973Sbostic#include "objects.h"
264*35973SbosticC
265*35973Sbostic	QEMPTY=.FALSE.
266*35973SbosticC						!ASSUME LOSE.
267*35973Sbostic	DO 100 I=1,OLNT
268*35973Sbostic	  IF(OCAN(I).EQ.OBJ) RETURN
269*35973SbosticC						!INSIDE TARGET?
270*35973Sbostic100	CONTINUE
271*35973Sbostic	QEMPTY=.TRUE.
272*35973Sbostic	RETURN
273*35973Sbostic	END
274*35973SbosticC JIGSUP- YOU ARE DEAD
275*35973SbosticC
276*35973SbosticC DECLARATIONS
277*35973SbosticC
278*35973Sbostic	SUBROUTINE JIGSUP(DESC)
279*35973Sbostic	IMPLICIT INTEGER (A-Z)
280*35973Sbostic	LOGICAL YESNO,MOVETO,QHERE,F
281*35973Sbostic	INTEGER RLIST(9)
282*35973Sbostic#include "parser.h"
283*35973Sbostic#include "gamestate.h"
284*35973Sbostic#include "state.h"
285*35973Sbostic#include "io.h"
286*35973Sbostic#include "debug.h"
287*35973Sbostic#include "rooms.h"
288*35973Sbostic#include "rflag.h"
289*35973Sbostic#include "rindex.h"
290*35973Sbostic#include "objects.h"
291*35973Sbostic#include "oflags.h"
292*35973Sbostic#include "oindex.h"
293*35973Sbostic#include "advers.h"
294*35973Sbostic#include "flags.h"
295*35973SbosticC
296*35973SbosticC FUNCTIONS AND DATA
297*35973SbosticC
298*35973Sbostic	DATA RLIST/8,6,36,35,34,4,34,6,5/
299*35973SbosticC JIGSUP, PAGE 2
300*35973SbosticC
301*35973Sbostic	CALL RSPEAK(DESC)
302*35973SbosticC						!DESCRIBE SAD STATE.
303*35973Sbostic	PRSCON=1
304*35973SbosticC						!STOP PARSER.
305*35973Sbostic	IF(DBGFLG.NE.0) RETURN
306*35973SbosticC						!IF DBG, EXIT.
307*35973Sbostic	AVEHIC(WINNER)=0
308*35973SbosticC						!GET RID OF VEHICLE.
309*35973Sbostic	IF(WINNER.EQ.PLAYER) GO TO 100
310*35973SbosticC						!HIMSELF?
311*35973Sbostic	CALL RSPSUB(432,ODESC2(AOBJ(WINNER)))
312*35973SbosticC						!NO, SAY WHO DIED.
313*35973Sbostic	CALL NEWSTA(AOBJ(WINNER),0,0,0,0)
314*35973SbosticC						!SEND TO HYPER SPACE.
315*35973Sbostic	RETURN
316*35973SbosticC
317*35973Sbostic100	IF(ENDGMF) GO TO 900
318*35973SbosticC						!NO RECOVERY IN END GAME.
319*35973Sbostic	IF(DEATHS.GE.2) GO TO 1000
320*35973SbosticC						!DEAD TWICE? KICK HIM OFF.
321*35973Sbostic	IF(.NOT.YESNO(10,9,8)) GO TO 1100
322*35973SbosticC						!CONTINUE?
323*35973SbosticC
324*35973Sbostic	DO 50 J=1,OLNT
325*35973SbosticC						!TURN OFF FIGHTING.
326*35973Sbostic	  IF(QHERE(J,HERE))   OFLAG2(J)=and(OFLAG2(J),not(FITEBT))
327*35973Sbostic50	CONTINUE
328*35973SbosticC
329*35973Sbostic	DEATHS=DEATHS+1
330*35973Sbostic	CALL SCRUPD(-10)
331*35973SbosticC						!CHARGE TEN POINTS.
332*35973Sbostic	F=MOVETO(FORE1,WINNER)
333*35973SbosticC						!REPOSITION HIM.
334*35973Sbostic	EGYPTF=.TRUE.
335*35973SbosticC						!RESTORE COFFIN.
336*35973Sbostic	IF(OADV(COFFI).EQ.WINNER) CALL NEWSTA(COFFI,0,EGYPT,0,0)
337*35973Sbostic	OFLAG2(DOOR)=and(OFLAG2(DOOR),not(TCHBT))
338*35973Sbostic	OFLAG1(ROBOT)=and(or(OFLAG1(ROBOT),VISIBT),not(NDSCBT))
339*35973Sbostic	IF((OROOM(LAMP).NE.0).OR.(OADV(LAMP).EQ.WINNER))
340*35973Sbostic&		CALL NEWSTA(LAMP,0,LROOM,0,0)
341*35973SbosticC
342*35973SbosticC NOW REDISTRIBUTE HIS VALUABLES AND OTHER BELONGINGS.
343*35973SbosticC
344*35973SbosticC THE LAMP HAS BEEN PLACED IN THE LIVING ROOM.
345*35973SbosticC THE FIRST 8 NON-VALUABLES ARE PLACED IN LOCATIONS AROUND THE HOUSE.
346*35973SbosticC HIS VALUABLES ARE PLACED AT THE END OF THE MAZE.
347*35973SbosticC REMAINING NON-VALUABLES ARE PLACED AT THE END OF THE MAZE.
348*35973SbosticC
349*35973Sbostic	I=1
350*35973Sbostic	DO 200 J=1,OLNT
351*35973SbosticC						!LOOP THRU OBJECTS.
352*35973Sbostic	  IF((OADV(J).NE.WINNER).OR.(OTVAL(J).NE.0))
353*35973Sbostic&		GO TO 200
354*35973Sbostic	  I=I+1
355*35973Sbostic	  IF(I.GT.9) GO TO 400
356*35973SbosticC						!MOVE TO RANDOM LOCATIONS.
357*35973Sbostic	  CALL NEWSTA(J,0,RLIST(I),0,0)
358*35973Sbostic200	CONTINUE
359*35973SbosticC
360*35973Sbostic400	I=RLNT+1
361*35973SbosticC						!NOW MOVE VALUABLES.
362*35973Sbostic	NONOFL=RAIR+RWATER+RSACRD+REND
363*35973SbosticC						!DONT MOVE HERE.
364*35973Sbostic	DO 300 J=1,OLNT
365*35973Sbostic	  IF((OADV(J).NE.WINNER).OR.(OTVAL(J).EQ.0))
366*35973Sbostic&		GO TO 300
367*35973Sbostic250	  I=I-1
368*35973SbosticC						!FIND NEXT ROOM.
369*35973Sbostic	  IF(and(RFLAG(I),NONOFL).NE.0) GO TO 250
370*35973Sbostic	  CALL NEWSTA(J,0,I,0,0)
371*35973SbosticC						!YES, MOVE.
372*35973Sbostic300	CONTINUE
373*35973SbosticC
374*35973Sbostic	DO 500 J=1,OLNT
375*35973SbosticC						!NOW GET RID OF REMAINDER.
376*35973Sbostic	  IF(OADV(J).NE.WINNER) GO TO 500
377*35973Sbostic450	  I=I-1
378*35973SbosticC						!FIND NEXT ROOM.
379*35973Sbostic	  IF(and(RFLAG(I),NONOFL).NE.0) GO TO 450
380*35973Sbostic	  CALL NEWSTA(J,0,I,0,0)
381*35973Sbostic500	CONTINUE
382*35973Sbostic	RETURN
383*35973SbosticC
384*35973SbosticC CAN'T OR WON'T CONTINUE, CLEAN UP AND EXIT.
385*35973SbosticC
386*35973Sbostic900	CALL RSPEAK(625)
387*35973SbosticC						!IN ENDGAME, LOSE.
388*35973Sbostic	GO TO 1100
389*35973SbosticC
390*35973Sbostic1000	CALL RSPEAK(7)
391*35973SbosticC						!INVOLUNTARY EXIT.
392*35973Sbostic1100	CALL SCORE(.FALSE.)
393*35973SbosticC						!TELL SCORE.
394*35973Sbostic#ifdef PDP
395*35973SbosticC	file closed in exit routine
396*35973Sbostic#else
397*35973Sbostic	CLOSE(DBCH)
398*35973Sbostic#endif PDP
399*35973Sbostic	CALL EXIT
400*35973SbosticC
401*35973Sbostic	END
402*35973SbosticC OACTOR-	GET ACTOR ASSOCIATED WITH OBJECT
403*35973SbosticC
404*35973SbosticC DECLARATIONS
405*35973SbosticC
406*35973Sbostic	INTEGER FUNCTION OACTOR(OBJ)
407*35973Sbostic	IMPLICIT INTEGER(A-Z)
408*35973Sbostic#include "advers.h"
409*35973SbosticC
410*35973Sbostic	DO 100 I=1,ALNT
411*35973SbosticC						!LOOP THRU ACTORS.
412*35973Sbostic	  OACTOR=I
413*35973SbosticC						!ASSUME FOUND.
414*35973Sbostic	  IF(AOBJ(I).EQ.OBJ) RETURN
415*35973SbosticC						!FOUND IT?
416*35973Sbostic100	CONTINUE
417*35973Sbostic	CALL BUG(40,OBJ)
418*35973SbosticC						!NO, DIE.
419*35973Sbostic	RETURN
420*35973Sbostic	END
421*35973SbosticC PROB-		COMPUTE PROBABILITY
422*35973SbosticC
423*35973SbosticC DECLARATIONS
424*35973SbosticC
425*35973Sbostic	LOGICAL FUNCTION PROB(G,B)
426*35973Sbostic	IMPLICIT INTEGER(A-Z)
427*35973Sbostic#include "flags.h"
428*35973SbosticC
429*35973Sbostic	I=G
430*35973SbosticC						!ASSUME GOOD LUCK.
431*35973Sbostic	IF(BADLKF) I=B
432*35973SbosticC						!IF BAD, TOO BAD.
433*35973Sbostic	PROB=RND(100).LT.I
434*35973SbosticC						!COMPUTE.
435*35973Sbostic	RETURN
436*35973Sbostic	END
437*35973SbosticC RMDESC-- PRINT ROOM DESCRIPTION
438*35973SbosticC
439*35973SbosticC RMDESC PRINTS A DESCRIPTION OF THE CURRENT ROOM.
440*35973SbosticC IT IS ALSO THE PROCESSOR FOR VERBS 'LOOK' AND 'EXAMINE'.
441*35973SbosticC
442*35973Sbostic	LOGICAL FUNCTION RMDESC(FULL)
443*35973SbosticC
444*35973SbosticC FULL=	0/1/2/3=	SHORT/OBJ/ROOM/FULL
445*35973SbosticC
446*35973SbosticC DECLARATIONS
447*35973SbosticC
448*35973Sbostic	IMPLICIT INTEGER (A-Z)
449*35973Sbostic	LOGICAL LIT,RAPPLI
450*35973SbosticC	LOGICAL PROB
451*35973Sbostic#include "parser.h"
452*35973Sbostic#include "gamestate.h"
453*35973Sbostic#include "screen.h"
454*35973Sbostic#include "rooms.h"
455*35973Sbostic#include "rflag.h"
456*35973Sbostic#include "xsrch.h"
457*35973Sbostic#include "objects.h"
458*35973Sbostic#include "advers.h"
459*35973Sbostic#include "verbs.h"
460*35973Sbostic#include "flags.h"
461*35973SbosticC RMDESC, PAGE 2
462*35973SbosticC
463*35973Sbostic	RMDESC=.TRUE.
464*35973SbosticC						!ASSUME WINS.
465*35973Sbostic	IF(PRSO.LT.XMIN) GO TO 50
466*35973SbosticC						!IF DIRECTION,
467*35973Sbostic	FROMDR=PRSO
468*35973SbosticC						!SAVE AND
469*35973Sbostic	PRSO=0
470*35973SbosticC						!CLEAR.
471*35973Sbostic50	IF(HERE.EQ.AROOM(PLAYER)) GO TO 100
472*35973SbosticC						!PLAYER JUST MOVE?
473*35973Sbostic	CALL RSPEAK(2)
474*35973SbosticC						!NO, JUST SAY DONE.
475*35973Sbostic	PRSA=WALKIW
476*35973SbosticC						!SET UP WALK IN ACTION.
477*35973Sbostic	RETURN
478*35973SbosticC
479*35973Sbostic100	IF(LIT(HERE)) GO TO 300
480*35973SbosticC						!LIT?
481*35973Sbostic	CALL RSPEAK(430)
482*35973SbosticC						!WARN OF GRUE.
483*35973Sbostic	RMDESC=.FALSE.
484*35973Sbostic	RETURN
485*35973SbosticC
486*35973Sbostic300	RA=RACTIO(HERE)
487*35973SbosticC						!GET ROOM ACTION.
488*35973Sbostic	IF(FULL.EQ.1) GO TO 600
489*35973SbosticC						!OBJ ONLY?
490*35973Sbostic	I=RDESC2-HERE
491*35973SbosticC						!ASSUME SHORT DESC.
492*35973Sbostic	IF((FULL.EQ.0)
493*35973Sbostic&		.AND.(SUPERF.OR.(((and(RFLAG(HERE),RSEEN)).NE.0)
494*35973SbosticC
495*35973SbosticC  The next line means that when you request VERBOSE mode, you
496*35973SbosticC  only get long room descriptions 20% of the time. I don't either
497*35973SbosticC  like or understand this, so the mod. ensures VERBOSE works
498*35973SbosticC  all the time.			jmh@ukc.ac.uk 22/10/87
499*35973SbosticC
500*35973SbosticC&		        .AND.(BRIEFF.OR.PROB(80,80)))))       GO TO 400
501*35973Sbostic&		        .AND.BRIEFF)))       GO TO 400
502*35973Sbostic	I=RDESC1(HERE)
503*35973SbosticC						!USE LONG.
504*35973Sbostic	IF((I.NE.0).OR.(RA.EQ.0)) GO TO 400
505*35973SbosticC						!IF GOT DESC, SKIP.
506*35973Sbostic	PRSA=LOOKW
507*35973SbosticC						!PRETEND LOOK AROUND.
508*35973Sbostic	IF(.NOT.RAPPLI(RA)) GO TO 100
509*35973SbosticC						!ROOM HANDLES, NEW DESC?
510*35973Sbostic	PRSA=FOOW
511*35973SbosticC						!NOP PARSER.
512*35973Sbostic	GO TO 500
513*35973SbosticC
514*35973Sbostic400	CALL RSPEAK(I)
515*35973SbosticC						!OUTPUT DESCRIPTION.
516*35973Sbostic500	IF(AVEHIC(WINNER).NE.0) CALL RSPSUB(431,ODESC2(AVEHIC(WINNER)))
517*35973SbosticC
518*35973Sbostic600	IF(FULL.NE.2) CALL PRINCR(FULL.NE.0,HERE)
519*35973Sbostic	RFLAG(HERE)=or(RFLAG(HERE),RSEEN)
520*35973Sbostic	IF((FULL.NE.0).OR.(RA.EQ.0)) RETURN
521*35973SbosticC						!ANYTHING MORE?
522*35973Sbostic	PRSA=WALKIW
523*35973SbosticC						!GIVE HIM A SURPISE.
524*35973Sbostic	IF(.NOT.RAPPLI(RA)) GO TO 100
525*35973SbosticC						!ROOM HANDLES, NEW DESC?
526*35973Sbostic	PRSA=FOOW
527*35973Sbostic	RETURN
528*35973SbosticC
529*35973Sbostic	END
530*35973SbosticC RAPPLI-	ROUTING ROUTINE FOR ROOM APPLICABLES
531*35973SbosticC
532*35973SbosticC DECLARATIONS
533*35973SbosticC
534*35973Sbostic	LOGICAL FUNCTION RAPPLI(RI)
535*35973Sbostic	IMPLICIT INTEGER(A-Z)
536*35973Sbostic	LOGICAL RAPPL1,RAPPL2
537*35973Sbostic	DATA NEWRMS/38/
538*35973SbosticC
539*35973Sbostic	RAPPLI=.TRUE.
540*35973SbosticC						!ASSUME WINS.
541*35973Sbostic	IF(RI.EQ.0) RETURN
542*35973SbosticC						!IF ZERO, WIN.
543*35973Sbostic	IF(RI.LT.NEWRMS) RAPPLI=RAPPL1(RI)
544*35973SbosticC						!IF OLD, PROCESSOR 1.
545*35973Sbostic	IF(RI.GE.NEWRMS) RAPPLI=RAPPL2(RI)
546*35973SbosticC						!IF NEW, PROCESSOR 2.
547*35973Sbostic	RETURN
548*35973Sbostic	END
549