xref: /csrg-svn/contrib/dungeon/villns.F (revision 35973)
1*35973SbosticC TROLLP-	TROLL FUNCTION
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*35973Sbostic	LOGICAL FUNCTION TROLLP(ARG)
10*35973Sbostic	IMPLICIT INTEGER (A-Z)
11*35973Sbostic	LOGICAL QHERE,PROB
12*35973Sbostic#include "parser.h"
13*35973Sbostic#include "gamestate.h"
14*35973Sbostic#include "objects.h"
15*35973Sbostic#include "oflags.h"
16*35973Sbostic#include "oindex.h"
17*35973Sbostic#include "verbs.h"
18*35973Sbostic#include "flags.h"
19*35973SbosticC TROLLP, PAGE 2
20*35973SbosticC
21*35973Sbostic	TROLLP=.TRUE.
22*35973SbosticC						!ASSUME WINS.
23*35973Sbostic	IF(PRSA.NE.FIGHTW) GO TO 1100
24*35973SbosticC						!FIGHT?
25*35973Sbostic	IF(OCAN(AXE).EQ.TROLL) GO TO 10
26*35973SbosticC						!GOT AXE?  NOTHING.
27*35973Sbostic	I=433
28*35973SbosticC						!ASSUME CANT GET.
29*35973Sbostic	IF(.NOT.QHERE(AXE,HERE)) GO TO 1050
30*35973SbosticC						!HERE?
31*35973Sbostic	I=434
32*35973SbosticC						!YES, RECOVER.
33*35973Sbostic	CALL NEWSTA(AXE,0,0,TROLL,0)
34*35973Sbostic1050	IF(QHERE(TROLL,HERE)) CALL RSPEAK(I)
35*35973SbosticC						!IF PLAYER HERE.
36*35973Sbostic	RETURN
37*35973SbosticC
38*35973Sbostic1100	IF(PRSA.NE.DEADXW) GO TO 1200
39*35973SbosticC						!DEAD?
40*35973Sbostic	TROLLF=.TRUE.
41*35973SbosticC						!PERMIT EXITS.
42*35973Sbostic	RETURN
43*35973SbosticC
44*35973Sbostic1200	IF(PRSA.NE.OUTXW) GO TO 1300
45*35973SbosticC						!OUT?
46*35973Sbostic	TROLLF=.TRUE.
47*35973SbosticC						!PERMIT EXITS.
48*35973Sbostic	OFLAG1(AXE)=and(OFLAG1(AXE), not(VISIBT))
49*35973Sbostic	ODESC1(TROLL)=435
50*35973SbosticC						!TROLL OUT.
51*35973Sbostic	RETURN
52*35973SbosticC
53*35973Sbostic1300	IF(PRSA.NE.INXW) GO TO 1400
54*35973SbosticC						!WAKE UP?
55*35973Sbostic	TROLLF=.FALSE.
56*35973SbosticC						!FORBID EXITS.
57*35973Sbostic	OFLAG1(AXE)=or(OFLAG1(AXE),VISIBT)
58*35973Sbostic	ODESC1(TROLL)=436
59*35973SbosticC						!TROLL IN.
60*35973Sbostic	IF(QHERE(TROLL,HERE)) CALL RSPEAK(437)
61*35973Sbostic	RETURN
62*35973SbosticC
63*35973Sbostic1400	IF(PRSA.NE.FRSTQW) GO TO 1500
64*35973SbosticC						!FIRST ENCOUNTER?
65*35973Sbostic	TROLLP=PROB(33,66)
66*35973SbosticC						!33% TRUE UNLESS BADLK.
67*35973Sbostic	RETURN
68*35973SbosticC
69*35973Sbostic1500	IF((PRSA.NE.MOVEW).AND.(PRSA.NE.TAKEW).AND.(PRSA.NE.MUNGW)
70*35973Sbostic&		.AND.(PRSA.NE.THROWW).AND.(PRSA.NE.GIVEW)) GO TO 2000
71*35973Sbostic	IF(OCAPAC(TROLL).GE.0) GO TO 1550
72*35973SbosticC						!TROLL OUT?
73*35973Sbostic	OCAPAC(TROLL)=-OCAPAC(TROLL)
74*35973SbosticC						!YES, WAKE HIM.
75*35973Sbostic	OFLAG1(AXE)=or(OFLAG1(AXE),VISIBT)
76*35973Sbostic	TROLLF=.FALSE.
77*35973Sbostic	ODESC1(TROLL)=436
78*35973Sbostic	CALL RSPEAK(437)
79*35973SbosticC
80*35973Sbostic1550	IF((PRSA.NE.TAKEW).AND.(PRSA.NE.MOVEW)) GO TO 1600
81*35973Sbostic	CALL RSPEAK(438)
82*35973SbosticC						!JOKE.
83*35973Sbostic	RETURN
84*35973SbosticC
85*35973Sbostic1600	IF(PRSA.NE.MUNGW) GO TO 1700
86*35973SbosticC						!MUNG?
87*35973Sbostic	CALL RSPEAK(439)
88*35973SbosticC						!JOKE.
89*35973Sbostic	RETURN
90*35973SbosticC
91*35973Sbostic1700	IF(PRSO.EQ.0) GO TO 10
92*35973SbosticC						!NO OBJECT?
93*35973Sbostic	I=440
94*35973SbosticC						!ASSUME THROW.
95*35973Sbostic	IF(PRSA.EQ.GIVEW) I=441
96*35973SbosticC						!GIVE?
97*35973Sbostic	CALL RSPSUB(I,ODESC2(PRSO))
98*35973SbosticC						!TROLL TAKES.
99*35973Sbostic	IF(PRSO.EQ.KNIFE) GO TO 1900
100*35973SbosticC						!OBJ KNIFE?
101*35973Sbostic	CALL NEWSTA(PRSO,442,0,0,0)
102*35973SbosticC						!NO, EATS IT.
103*35973Sbostic	RETURN
104*35973SbosticC
105*35973Sbostic1900	CALL RSPEAK(443)
106*35973SbosticC						!KNIFE, THROWS IT BACK
107*35973Sbostic	OFLAG2(TROLL)=or(OFLAG2(TROLL),FITEBT)
108*35973Sbostic	RETURN
109*35973SbosticC
110*35973Sbostic2000	IF(.NOT.TROLLF.OR.(PRSA.NE.HELLOW)) GO TO 10
111*35973Sbostic	CALL RSPEAK(366)
112*35973SbosticC						!TROLL OUT.
113*35973Sbostic	RETURN
114*35973SbosticC
115*35973Sbostic10	TROLLP=.FALSE.
116*35973SbosticC						!COULDNT HANDLE IT.
117*35973Sbostic	RETURN
118*35973Sbostic	END
119*35973SbosticC CYCLOP-	CYCLOPS FUNCTION
120*35973SbosticC
121*35973SbosticC DECLARATIONS
122*35973SbosticC
123*35973Sbostic	LOGICAL FUNCTION CYCLOP(ARG)
124*35973Sbostic	IMPLICIT INTEGER (A-Z)
125*35973Sbostic#include "parser.h"
126*35973Sbostic#include "gamestate.h"
127*35973Sbostic#include "objects.h"
128*35973Sbostic#include "oflags.h"
129*35973Sbostic#include "oindex.h"
130*35973Sbostic#include "verbs.h"
131*35973Sbostic#include "flags.h"
132*35973SbosticC CYCLOP, PAGE 2
133*35973SbosticC
134*35973Sbostic	CYCLOP=.TRUE.
135*35973SbosticC						!ASSUME WINS.
136*35973Sbostic	IF(.NOT.CYCLOF) GO TO 100
137*35973SbosticC						!ASLEEP?
138*35973Sbostic	IF((PRSA.NE.ALARMW).AND.(PRSA.NE.MUNGW).AND.(PRSA.NE.HELLOW).AND.
139*35973Sbostic&		(PRSA.NE.BURNW).AND.(PRSA.NE.KILLW).AND.(PRSA.NE.ATTACW))
140*35973Sbostic&		 GO TO 10
141*35973Sbostic	CYCLOF=.FALSE.
142*35973SbosticC						!WAKE CYCLOPS.
143*35973Sbostic	CALL RSPEAK(187)
144*35973SbosticC						!DESCRIBE.
145*35973Sbostic	RVCYC=IABS(RVCYC)
146*35973Sbostic	OFLAG2(CYCLO)=and(or(OFLAG2(CYCLO),FITEBT),not(SLEPBT))
147*35973Sbostic	RETURN
148*35973SbosticC
149*35973Sbostic100	IF((PRSA.EQ.FIGHTW).OR.(PRSA.EQ.FRSTQW)) GO TO 10
150*35973Sbostic	IF(IABS(RVCYC).LE.5) GO TO 200
151*35973SbosticC						!ANNOYED TOO MUCH?
152*35973Sbostic	RVCYC=0
153*35973SbosticC						!RESTART COUNT.
154*35973Sbostic	CALL JIGSUP(188)
155*35973SbosticC						!YES, EATS PLAYER.
156*35973Sbostic	RETURN
157*35973SbosticC
158*35973Sbostic200	IF(PRSA.NE.GIVEW) GO TO 500
159*35973SbosticC						!GIVE?
160*35973Sbostic	IF((PRSO.NE.FOOD).OR.(RVCYC.LT.0)) GO TO 300
161*35973SbosticC						!FOOD WHEN HUNGRY?
162*35973Sbostic	CALL NEWSTA(FOOD,189,0,0,0)
163*35973SbosticC						!EATS PEPPERS.
164*35973Sbostic	RVCYC=MIN0(-1,-RVCYC)
165*35973SbosticC						!GETS THIRSTY.
166*35973Sbostic	RETURN
167*35973SbosticC
168*35973Sbostic300	IF(PRSO.NE.WATER) GO TO 400
169*35973SbosticC						!DRINK WHEN THIRSTY?
170*35973Sbostic	IF(RVCYC.GE.0) GO TO 350
171*35973Sbostic	CALL NEWSTA(PRSO,190,0,0,0)
172*35973SbosticC						!DRINKS AND
173*35973Sbostic	CYCLOF=.TRUE.
174*35973SbosticC						!FALLS ASLEEP.
175*35973Sbostic	OFLAG2(CYCLO)=and(or(OFLAG2(CYCLO),SLEPBT),not(FITEBT))
176*35973Sbostic	RETURN
177*35973SbosticC
178*35973Sbostic350	CALL RSPEAK(191)
179*35973SbosticC						!NOT THIRSTY.
180*35973Sbostic10	CYCLOP=.FALSE.
181*35973SbosticC						!FAILS.
182*35973Sbostic	RETURN
183*35973SbosticC
184*35973Sbostic400	I=192
185*35973SbosticC						!ASSUME INEDIBLE.
186*35973Sbostic	IF(PRSO.EQ.GARLI) I=193
187*35973SbosticC						!GARLIC IS JOKE.
188*35973Sbostic450	CALL RSPEAK(I)
189*35973SbosticC						!DISDAIN IT.
190*35973Sbostic	IF(RVCYC.LT.0) RVCYC=RVCYC-1
191*35973Sbostic	IF(RVCYC.GE.0) RVCYC=RVCYC+1
192*35973Sbostic	IF(.NOT.CYCLOF) CALL RSPEAK(193+IABS(RVCYC))
193*35973Sbostic	RETURN
194*35973SbosticC
195*35973Sbostic500	I=0
196*35973SbosticC						!ASSUME NOT HANDLED.
197*35973Sbostic	IF(PRSA.EQ.HELLOW) GO TO 450
198*35973SbosticC						!HELLO IS NO GO.
199*35973Sbostic	IF((PRSA.EQ.THROWW).OR.(PRSA.EQ.MUNGW)) I=200+RND(2)
200*35973Sbostic	IF(PRSA.EQ.TAKEW) I=202
201*35973Sbostic	IF(PRSA.EQ.TIEW) I=203
202*35973Sbostic	IF(I) 10,10,450
203*35973SbosticC						!SEE IF HANDLED.
204*35973SbosticC
205*35973Sbostic	END
206*35973SbosticC THIEFP-	THIEF FUNCTION
207*35973SbosticC
208*35973SbosticC DECLARATIONS
209*35973SbosticC
210*35973Sbostic	LOGICAL FUNCTION THIEFP(ARG)
211*35973Sbostic	IMPLICIT INTEGER (A-Z)
212*35973Sbostic	LOGICAL QHERE,PROB
213*35973Sbostic#include "parser.h"
214*35973Sbostic#include "gamestate.h"
215*35973SbosticC
216*35973SbosticC ROOMS
217*35973Sbostic#include "rindex.h"
218*35973Sbostic#include "objects.h"
219*35973Sbostic#include "oflags.h"
220*35973Sbostic#include "oindex.h"
221*35973Sbostic#include "clock.h"
222*35973Sbostic
223*35973Sbostic#include "villians.h"
224*35973Sbostic#include "verbs.h"
225*35973Sbostic#include "flags.h"
226*35973SbosticC THIEFP, PAGE 2
227*35973SbosticC
228*35973Sbostic	THIEFP=.TRUE.
229*35973SbosticC						!ASSUME WINS.
230*35973Sbostic	IF(PRSA.NE.FIGHTW) GO TO 100
231*35973SbosticC						!FIGHT?
232*35973Sbostic	IF(OCAN(STILL).EQ.THIEF) GO TO 10
233*35973SbosticC						!GOT STILLETTO?  F.
234*35973Sbostic	IF(QHERE(STILL,THFPOS)) GO TO 50
235*35973SbosticC						!CAN HE RECOVER IT?
236*35973Sbostic	CALL NEWSTA(THIEF,0,0,0,0)
237*35973SbosticC						!NO, VANISH.
238*35973Sbostic	IF(QHERE(THIEF,HERE)) CALL RSPEAK(498)
239*35973SbosticC						!IF HERO, TELL.
240*35973Sbostic	RETURN
241*35973SbosticC
242*35973Sbostic50	CALL NEWSTA(STILL,0,0,THIEF,0)
243*35973SbosticC						!YES, RECOVER.
244*35973Sbostic	IF(QHERE(THIEF,HERE)) CALL RSPEAK(499)
245*35973SbosticC						!IF HERO, TELL.
246*35973Sbostic	RETURN
247*35973SbosticC
248*35973Sbostic100	IF(PRSA.NE.DEADXW) GO TO 200
249*35973SbosticC						!DEAD?
250*35973Sbostic	THFACT=.FALSE.
251*35973SbosticC						!DISABLE DEMON.
252*35973Sbostic	OFLAG1(CHALI)=or(OFLAG1(CHALI),TAKEBT)
253*35973Sbostic	J=0
254*35973Sbostic	DO 125 I=1,OLNT
255*35973SbosticC						!CARRYING ANYTHING?
256*35973Sbostic125	  IF(OADV(I).EQ.-THIEF) J=500
257*35973Sbostic	CALL RSPEAK(J)
258*35973SbosticC						!TELL IF BOOTY REAPPEARS.
259*35973SbosticC
260*35973Sbostic	J=501
261*35973Sbostic	DO 150 I=1,OLNT
262*35973SbosticC						!LOOP.
263*35973Sbostic	  IF((I.EQ.CHALI).OR.(I.EQ.THIEF).OR.(HERE.NE.TREAS)
264*35973Sbostic&		.OR. .NOT.QHERE(I,HERE)) GO TO 135
265*35973Sbostic	  OFLAG1(I)=or(OFLAG1(I),VISIBT)
266*35973Sbostic	  CALL RSPSUB(J,ODESC2(I))
267*35973SbosticC						!DESCRIBE.
268*35973Sbostic	  J=502
269*35973Sbostic	  GO TO 150
270*35973SbosticC
271*35973Sbostic135	  IF(OADV(I).EQ.-THIEF) CALL NEWSTA(I,0,HERE,0,0)
272*35973Sbostic150	CONTINUE
273*35973Sbostic	RETURN
274*35973SbosticC
275*35973Sbostic200	IF(PRSA.NE.FRSTQW) GO TO 250
276*35973SbosticC						!FIRST ENCOUNTER?
277*35973Sbostic	THIEFP=PROB(20,75)
278*35973Sbostic	RETURN
279*35973SbosticC
280*35973Sbostic250	IF((PRSA.NE.HELLOW).OR.(ODESC1(THIEF).NE.504))
281*35973Sbostic&		GO TO 300
282*35973Sbostic	CALL RSPEAK(626)
283*35973Sbostic	RETURN
284*35973SbosticC
285*35973Sbostic300	IF(PRSA.NE.OUTXW) GO TO 400
286*35973SbosticC						!OUT?
287*35973Sbostic	THFACT=.FALSE.
288*35973SbosticC						!DISABLE DEMON.
289*35973Sbostic	ODESC1(THIEF)=504
290*35973SbosticC						!CHANGE DESCRIPTION.
291*35973Sbostic	OFLAG1(STILL)=and(OFLAG1(STILL),not(VISIBT))
292*35973Sbostic	OFLAG1(CHALI)=or(OFLAG1(CHALI),TAKEBT)
293*35973Sbostic	RETURN
294*35973SbosticC
295*35973Sbostic400	IF(PRSA.NE.INXW) GO TO 500
296*35973SbosticC						!IN?
297*35973Sbostic	IF(QHERE(THIEF,HERE)) CALL RSPEAK(505)
298*35973SbosticC						!CAN HERO SEE?
299*35973Sbostic	THFACT=.TRUE.
300*35973SbosticC						!ENABLE DEMON.
301*35973Sbostic	ODESC1(THIEF)=503
302*35973SbosticC						!CHANGE DESCRIPTION.
303*35973Sbostic	OFLAG1(STILL)=or(OFLAG1(STILL),VISIBT)
304*35973Sbostic	IF((HERE.EQ.TREAS).AND.QHERE(CHALI,HERE))
305*35973Sbostic&		OFLAG1(CHALI)=and(OFLAG1(CHALI),not(TAKEBT))
306*35973Sbostic	RETURN
307*35973SbosticC
308*35973Sbostic500	IF(PRSA.NE.TAKEW) GO TO 600
309*35973SbosticC						!TAKE?
310*35973Sbostic	CALL RSPEAK(506)
311*35973SbosticC						!JOKE.
312*35973Sbostic	RETURN
313*35973SbosticC
314*35973Sbostic600	IF((PRSA.NE.THROWW).OR.(PRSO.NE.KNIFE).OR.
315*35973Sbostic&		(and(OFLAG2(THIEF),FITEBT).NE.0)) GO TO 700
316*35973Sbostic	IF(PROB(10)) GO TO 650
317*35973SbosticC						!THREW KNIFE, 10%?
318*35973Sbostic	CALL RSPEAK(507)
319*35973SbosticC						!NO, JUST MAKES
320*35973Sbostic	OFLAG2(THIEF)=or(OFLAG2(THIEF),FITEBT)
321*35973Sbostic	RETURN
322*35973SbosticC
323*35973Sbostic650	J=508
324*35973SbosticC						!THIEF DROPS STUFF.
325*35973Sbostic	DO 675 I=1,OLNT
326*35973Sbostic	  IF(OADV(I).NE.-THIEF) GO TO 675
327*35973SbosticC						!THIEF CARRYING?
328*35973Sbostic	  J=509
329*35973Sbostic	  CALL NEWSTA(I,0,HERE,0,0)
330*35973Sbostic675	CONTINUE
331*35973Sbostic	CALL NEWSTA(THIEF,J,0,0,0)
332*35973SbosticC						!THIEF VANISHES.
333*35973Sbostic	RETURN
334*35973SbosticC
335*35973Sbostic700	IF(((PRSA.NE.THROWW).AND.(PRSA.NE.GIVEW)).OR.(PRSO.EQ.0).OR.
336*35973Sbostic&		(PRSO.EQ.THIEF)) GO TO 10
337*35973Sbostic	IF(OCAPAC(THIEF).GE.0) GO TO 750
338*35973SbosticC						!WAKE HIM UP.
339*35973Sbostic	OCAPAC(THIEF)=-OCAPAC(THIEF)
340*35973Sbostic	THFACT=.TRUE.
341*35973Sbostic	OFLAG1(STILL)=or(OFLAG1(STILL),VISIBT)
342*35973Sbostic	ODESC1(THIEF)=503
343*35973Sbostic	CALL RSPEAK(510)
344*35973SbosticC
345*35973Sbostic750	IF((PRSO.NE.BRICK).OR.(OCAN(FUSE).NE.BRICK).OR.
346*35973Sbostic&		(CTICK(CEVFUS).EQ.0)) GO TO 800
347*35973Sbostic	CALL RSPEAK(511)
348*35973SbosticC						!THIEF REFUSES BOMB.
349*35973Sbostic	RETURN
350*35973SbosticC
351*35973Sbostic800	CALL NEWSTA(PRSO,0,0,0,-THIEF)
352*35973SbosticC						!THIEF TAKES GIFT.
353*35973Sbostic	IF(OTVAL(PRSO).GT.0) GO TO 900
354*35973SbosticC						!A TREASURE?
355*35973Sbostic	CALL RSPSUB(512,ODESC2(PRSO))
356*35973Sbostic	RETURN
357*35973SbosticC
358*35973Sbostic900	CALL RSPSUB(627,ODESC2(PRSO))
359*35973SbosticC						!THIEF ENGROSSED.
360*35973Sbostic	THFENF=.TRUE.
361*35973Sbostic	RETURN
362*35973SbosticC
363*35973Sbostic10	THIEFP=.FALSE.
364*35973Sbostic	RETURN
365*35973Sbostic	END
366