More de-FORTRANizing of the output code.
[super-star-trek.git] / moving.c
1 #include "sst.h"\r
2 \r
3 static void getcd(int, int);\r
4 \r
5 void move(void) {\r
6         double angle, deltax, deltay, bigger, x, y,\r
7         finald, finalx, finaly, stopegy;\r
8         int trbeam = 0, n, l, ix, iy, kink, kinks, iquad;\r
9 \r
10         if (inorbit) {\r
11                 prout("Helmsman Sulu- \"Leaving standard orbit.\"");\r
12                 inorbit = 0;\r
13         }\r
14 \r
15         angle = ((15.0 - direc) * 0.5235988);\r
16         deltax = -sin(angle);\r
17         deltay = cos(angle);\r
18         if (fabs(deltax) > fabs(deltay))\r
19                 bigger = fabs(deltax);\r
20         else\r
21                 bigger = fabs(deltay);\r
22                 \r
23         deltay /= bigger;\r
24         deltax /= bigger;\r
25 \r
26         /* If tractor beam is to occur, don't move full distance */\r
27         if (game.state.date+Time >= game.future[FTBEAM]) {\r
28                 trbeam = 1;\r
29                 condit = IHRED;\r
30                 dist = dist*(game.future[FTBEAM]-game.state.date)/Time + 0.1;\r
31                 Time = game.future[FTBEAM] - game.state.date + 1e-5;\r
32         }\r
33         /* Move within the quadrant */\r
34         game.quad[sectx][secty] = IHDOT;\r
35         x = sectx;\r
36         y = secty;\r
37         n = 10.0*dist*bigger+0.5;\r
38 \r
39         if (n > 0) {\r
40                 for (l = 1; l <= n; l++) {\r
41                         ix = (x += deltax) + 0.5;\r
42                         iy = (y += deltay) + 0.5;\r
43                         if (ix < 1 || ix > 10 || iy < 1 || iy > 10) {\r
44                                 /* Leaving quadrant -- allow final enemy attack */\r
45                                 /* Don't do it if being pushed by Nova */\r
46                                 if (nenhere != 0 && iattak != 2) {\r
47                                         newcnd();\r
48                                         for (l = 1; l <= nenhere; l++) {\r
49                                                 finald = sqrt((ix-game.kx[l])*(double)(ix-game.kx[l]) +\r
50                                                                           (iy-game.ky[l])*(double)(iy-game.ky[l]));\r
51                                                 game.kavgd[l] = 0.5 * (finald+game.kdist[l]);\r
52                                         }\r
53                                         if (game.state.galaxy[quadx][quady] != 1000) attack(0);\r
54                                         if (alldone) return;\r
55                                 }\r
56                                 /* compute final position -- new quadrant and sector */\r
57                                 x = 10*(quadx-1)+sectx;\r
58                                 y = 10*(quady-1)+secty;\r
59                                 ix = x+10.0*dist*bigger*deltax+0.5;\r
60                                 iy = y+10.0*dist*bigger*deltay+0.5;\r
61                                 /* check for edge of galaxy */\r
62                                 kinks = 0;\r
63                                 do {\r
64                                         kink = 0;\r
65                                         if (ix <= 0) {\r
66                                                 ix = -ix + 1;\r
67                                                 kink = 1;\r
68                                         }\r
69                                         if (iy <= 0) {\r
70                                                 iy = -iy + 1;\r
71                                                 kink = 1;\r
72                                         }\r
73                                         if (ix > 80) {\r
74                                                 ix = 161 - ix;\r
75                                                 kink = 1;\r
76                                         }\r
77                                         if (iy > 80) {\r
78                                                 iy = 161 - iy;\r
79                                                 kink = 1;\r
80                                         }\r
81                                         if (kink) kinks = 1;\r
82                                 } while (kink);\r
83 \r
84                                 if (kinks) {\r
85                                         nkinks += 1;\r
86                                         if (nkinks == 3) {\r
87                                                 /* Three strikes -- you're out! */\r
88                                                 finish(FNEG3);\r
89                                                 return;\r
90                                         }\r
91                                         prout("\nYOU HAVE ATTEMPTED TO CROSS THE NEGATIVE ENERGY BARRIER\n"\r
92                                                  "AT THE EDGE OF THE GALAXY.  THE THIRD TIME YOU TRY THIS,\n"\r
93                                                  "YOU WILL BE DESTROYED.\n");\r
94                                 }\r
95                                 /* Compute final position in new quadrant */\r
96                                 if (trbeam) return; /* Don't bother if we are to be beamed */\r
97                                 quadx = (ix+9)/10;\r
98                                 quady = (iy+9)/10;\r
99                                 sectx = ix - 10*(quadx-1);\r
100                                 secty = iy - 10*(quady-1);\r
101                                 prout("");\r
102                                 prout("Entering %s.",\r
103                                       cramlc(quadrant, quadx, quady));\r
104                                 game.quad[sectx][secty] = ship;\r
105                                 newqad(0);\r
106                                 return;\r
107                         }\r
108                         iquad = game.quad[ix][iy];\r
109                         if (iquad != IHDOT) {\r
110                                 /* object encountered in flight path */\r
111                                 stopegy = 50.0*dist/Time;\r
112                                 dist=0.1*sqrt((sectx-ix)*(double)(sectx-ix) +\r
113                                                           (secty-iy)*(double)(secty-iy));\r
114                                 switch (iquad) {\r
115                                         case IHT: /* Ram a Tholian */\r
116                                         case IHK: /* Ram enemy ship */\r
117                                         case IHC:\r
118                                         case IHS:\r
119                                         case IHR:\r
120                                                 sectx = ix;\r
121                                                 secty = iy;\r
122                                                 ram(0, iquad, sectx, secty);\r
123                                                 finalx = sectx;\r
124                                                 finaly = secty;\r
125                                                 break;\r
126                                         case IHBLANK:\r
127                                                 skip(1);\r
128                                                 prouts("***RED ALERT!  RED ALERT!");\r
129                                                 skip(1);\r
130                                                 proutn("***");\r
131                                                 crmshp();\r
132                                                 proutn(" pulled into black hole at ");\r
133                                                 prout(cramlc(sector, ix, iy));\r
134                                                 finish(FHOLE);\r
135                                                 return;\r
136                                         default:\r
137                                                 /* something else */\r
138                                                 skip(1);\r
139                                                 crmshp();\r
140                                                 if (iquad == IHWEB)\r
141                                                         proutn(" encounters Tholian web at ");\r
142                                                 else\r
143                                                         proutn(" blocked by object at ");\r
144                                                 proutn(cramlc(sector, ix,iy));\r
145                                                 prout(";");\r
146                                                 proutn("Emergency stop required ");\r
147                                                 prout("%2d units of energy.", (int)stopegy);\r
148                                                 energy -= stopegy;\r
149                                                 finalx = x-deltax+0.5;\r
150                                                 sectx = finalx;\r
151                                                 finaly = y-deltay+0.5;\r
152                                                 secty = finaly;\r
153                                                 if (energy <= 0) {\r
154                                                         finish(FNRG);\r
155                                                         return;\r
156                                                 }\r
157                                                 break;\r
158                                 }\r
159                                 goto label100;  /* sorry! */\r
160                         }\r
161                 }\r
162                 dist = 0.1*sqrt((sectx-ix)*(double)(sectx-ix) +\r
163                                                 (secty-iy)*(double)(secty-iy));\r
164                 sectx = ix;\r
165                 secty = iy;\r
166         }\r
167         finalx = sectx;\r
168         finaly = secty;\r
169 label100:\r
170         /* No quadrant change -- compute new avg enemy distances */\r
171         game.quad[sectx][secty] = ship;\r
172         if (nenhere) {\r
173                 for (l = 1; l <= nenhere; l++) {\r
174                         finald = sqrt((ix-game.kx[l])*(double)(ix-game.kx[l]) +\r
175                                                   (iy-game.ky[l])*(double)(iy-game.ky[l]));\r
176                         game.kavgd[l] = 0.5 * (finald+game.kdist[l]);\r
177                         game.kdist[l] = finald;\r
178                 }\r
179                 sortkl();\r
180                 if (game.state.galaxy[quadx][quady] != 1000 && iattak == 0)\r
181                         attack(0);\r
182                 for (l = 1 ; l <= nenhere; l++) game.kavgd[l] = game.kdist[l];\r
183         }\r
184         newcnd();\r
185         iattak = 0;\r
186         return;\r
187 }\r
188 \r
189 void dock(void) {\r
190         chew();\r
191         if (condit == IHDOCKED) {\r
192                 prout("Already docked.");\r
193                 return;\r
194         }\r
195         if (inorbit) {\r
196                 prout("You must first leave standard orbit.");\r
197                 return;\r
198         }\r
199         if (basex==0 || abs(sectx-basex) > 1 || abs(secty-basey) > 1) {\r
200                 crmshp();\r
201                 prout(" not adjacent to base.");\r
202                 return;\r
203         }\r
204         condit = IHDOCKED;\r
205         prout("Docked.");\r
206         if (energy < inenrg) energy = inenrg;\r
207         shield = inshld;\r
208         torps = intorps;\r
209         lsupres = inlsr;\r
210         if (stdamtim != 1e30 &&\r
211                 (game.future[FCDBAS] < 1e30 || isatb == 1) && iseenit == 0) {\r
212                 /* get attack report from base */\r
213                 prout("Lt. Uhura- \"Captain, an important message from the starbase:\"");\r
214                 attakreport();\r
215                 iseenit = 1;\r
216         }\r
217 }\r
218 \r
219 static void getcd(int isprobe, int akey) {\r
220         /* This program originally required input in terms of a (clock)\r
221            direction and distance. Somewhere in history, it was changed to\r
222            cartesian coordinates. So we need to convert. I think\r
223            "manual" input should still be done this way -- it's a real\r
224            pain if the computer isn't working! Manual mode is still confusing\r
225            because it involves giving x and y motions, yet the coordinates\r
226            are always displayed y - x, where +y is downward! */\r
227 \r
228         \r
229         int irowq=quadx, icolq=quady, irows, icols, itemp=0, iprompt=0, key;\r
230         double xi, xj, xk, xl;\r
231         double deltax, deltay;\r
232         int automatic = -1;\r
233 \r
234         /* Get course direction and distance. If user types bad values, return\r
235            with DIREC = -1.0. */\r
236 \r
237         direc = -1.0;\r
238         \r
239         if (landed == 1 && !isprobe) {\r
240                 prout("Dummy! You can't leave standard orbit until you");\r
241                 proutn("are back abourt the ");\r
242                 crmshp();\r
243                 prout(".");\r
244                 chew();\r
245                 return;\r
246         }\r
247         while (automatic == -1) {\r
248                 if (game.damage[DCOMPTR]) {\r
249                         if (isprobe)\r
250                                 prout("Computer damaged; manual navigation only");\r
251                         else\r
252                                 prout("Computer damaged; manual movement only");\r
253                         chew();\r
254                         automatic = 0;\r
255                         key = IHEOL;\r
256                         break;\r
257                 }\r
258                 if (isprobe && akey != -1) {\r
259                         /* For probe launch, use pre-scaned value first time */\r
260                         key = akey;\r
261                         akey = -1;\r
262                 }\r
263                 else \r
264                         key = scan();\r
265 \r
266                 if (key == IHEOL) {\r
267                         proutn("Manual or automatic- ");\r
268                         iprompt = 1;\r
269                         chew();\r
270                 }\r
271                 else if (key == IHALPHA) {\r
272                         if (isit("manual")) {\r
273                                 automatic =0;\r
274                                 key = scan();\r
275                                 break;\r
276                         }\r
277                         else if (isit("automatic")) {\r
278                                 automatic = 1;\r
279                                 key = scan();\r
280                                 break;\r
281                         }\r
282                         else {\r
283                                 huh();\r
284                                 chew();\r
285                                 return;\r
286                         }\r
287                 }\r
288                 else { /* numeric */\r
289                         if (isprobe)\r
290                                 prout("(Manual navigation assumed.)");\r
291                         else\r
292                                 prout("(Manual movement assumed.)");\r
293                         automatic = 0;\r
294                         break;\r
295                 }\r
296         }\r
297 \r
298         if (automatic) {\r
299                 while (key == IHEOL) {\r
300                         if (isprobe)\r
301                                 proutn("Target quadrant or quadrant&sector- ");\r
302                         else\r
303                                 proutn("Destination sector or quadrant&sector- ");\r
304                         chew();\r
305                         iprompt = 1;\r
306                         key = scan();\r
307                 }\r
308 \r
309                 if (key != IHREAL) {\r
310                         huh();\r
311                         return;\r
312                 }\r
313                 xi = aaitem;\r
314                 key = scan();\r
315                 if (key != IHREAL){\r
316                         huh();\r
317                         return;\r
318                 }\r
319                 xj = aaitem;\r
320                 key = scan();\r
321                 if (key == IHREAL) {\r
322                         /* both quadrant and sector specified */\r
323                         xk = aaitem;\r
324                         key = scan();\r
325                         if (key != IHREAL) {\r
326                                 huh();\r
327                                 return;\r
328                         }\r
329                         xl = aaitem;\r
330 \r
331                         irowq = xi + 0.5;\r
332                         icolq = xj + 0.5;\r
333                         irows = xk + 0.5;\r
334                         icols = xl + 0.5;\r
335                 }\r
336                 else {\r
337                         if (isprobe) {\r
338                                 /* only quadrant specified -- go to center of dest quad */\r
339                                 irowq = xi + 0.5;\r
340                                 icolq = xj + 0.5;\r
341                                 irows = icols = 5;\r
342                         }\r
343                         else {\r
344                                 irows = xi + 0.5;\r
345                                 icols = xj + 0.5;\r
346                         }\r
347                         itemp = 1;\r
348                 }\r
349                 if (irowq<1 || irowq > 8 || icolq<1 || icolq > 8 ||\r
350                         irows<1 || irows > 10 || icols<1 || icols > 10) {\r
351                                 huh();\r
352                                 return;\r
353                         }\r
354                 skip(1);\r
355                 if (!isprobe) {\r
356                         if (itemp) {\r
357                                 if (iprompt) {\r
358                                         proutn("Helmsman Sulu- \"Course locked in for %s.\"",\r
359                                                 cramlc(sector, irows, icols));\r
360                                 }\r
361                         }\r
362                         else prout("Ensign Chekov- \"Course laid in, Captain.\"");\r
363                 }\r
364                 deltax = icolq - quady + 0.1*(icols-secty);\r
365                 deltay = quadx - irowq + 0.1*(sectx-irows);\r
366         }\r
367         else { /* manual */\r
368                 while (key == IHEOL) {\r
369                         proutn("X and Y displacements- ");\r
370                         chew();\r
371                         iprompt = 1;\r
372                         key = scan();\r
373                 }\r
374                 itemp = 2;\r
375                 if (key != IHREAL) {\r
376                         huh();\r
377                         return;\r
378                 }\r
379                 deltax = aaitem;\r
380                 key = scan();\r
381                 if (key != IHREAL) {\r
382                         huh();\r
383                         return;\r
384                 }\r
385                 deltay = aaitem;\r
386         }\r
387         /* Check for zero movement */\r
388         if (deltax == 0 && deltay == 0) {\r
389                 chew();\r
390                 return;\r
391         }\r
392         if (itemp == 2 && !isprobe) {\r
393                 skip(1);\r
394                 prout("Helmsman Sulu- \"Aye, Sir.\"");\r
395         }\r
396         dist = sqrt(deltax*deltax + deltay*deltay);\r
397         direc = atan2(deltax, deltay)*1.90985932;\r
398         if (direc < 0.0) direc += 12.0;\r
399         chew();\r
400         return;\r
401 \r
402 }\r
403                 \r
404 \r
405 \r
406 void impuls(void) {\r
407         double power;\r
408 \r
409         ididit = 0;\r
410         if (game.damage[DIMPULS]) {\r
411                 chew();\r
412                 skip(1);\r
413                 prout("Engineer Scott- \"The impulse engines are damaged, Sir.\"");\r
414                 return;\r
415         }\r
416 \r
417         if (energy > 30.0) {\r
418                 getcd(FALSE, 0);\r
419                 if (direc == -1.0) return;\r
420                 power = 20.0 + 100.0*dist;\r
421         }\r
422         else\r
423                 power = 30.0;\r
424 \r
425         if (power >= energy) {\r
426                 /* Insufficient power for trip */\r
427                 skip(1);\r
428                 prout("First Officer Spock- \"Captain, the impulse engines");\r
429                 prout("require 20.0 units to engage, plus 100.0 units per");\r
430                 if (energy > 30) {\r
431                         proutn("quadrant.  We can go, therefore, a maximum of %d", \r
432                                (int)(0.01 * (energy-20.0)-0.05));\r
433                         prout(" quadrants.\"");\r
434                 }\r
435                 else {\r
436                         prout("quadrant.  They are, therefore, useless.\"");\r
437                 }\r
438                 chew();\r
439                 return;\r
440         }\r
441         /* Make sure enough time is left for the trip */\r
442         Time = dist/0.095;\r
443         if (Time >= game.state.remtime) {\r
444                 prout("First Officer Spock- \"Captain, our speed under impulse");\r
445                 prout("power is only 0.95 sectors per stardate. Are you sure");\r
446                 prout("we dare spend the time?\"");\r
447                 if (ja() == 0) return;\r
448         }\r
449         /* Activate impulse engines and pay the cost */\r
450         move();\r
451         ididit = 1;\r
452         if (alldone) return;\r
453         power = 20.0 + 100.0*dist;\r
454         energy -= power;\r
455         Time = dist/0.095;\r
456         if (energy <= 0) finish(FNRG);\r
457         return;\r
458 }\r
459 \r
460 \r
461 void warp(int i) {\r
462         int blooey=0, twarp=0, iwarp;\r
463         double power;\r
464 \r
465         if (i!=2) { /* Not WARPX entry */\r
466                 ididit = 0;\r
467                 if (game.damage[DWARPEN] > 10.0) {\r
468                         chew();\r
469                         skip(1);\r
470                         prout("Engineer Scott- \"The impulse engines are damaged, Sir.\"");\r
471                         return;\r
472                 }\r
473                 if (game.damage[DWARPEN] > 0.0 && warpfac > 4.0) {\r
474                         chew();\r
475                         skip(1);\r
476                         prout("Engineer Scott- \"Sorry, Captain. Until this damage");\r
477                         prout("  is repaired, I can only give you warp 4.\"");\r
478                         return;\r
479                 }\r
480                         \r
481                 /* Read in course and distance */\r
482                 getcd(FALSE, 0);\r
483                 if (direc == -1.0) return;\r
484 \r
485                 /* Make sure starship has enough energy for the trip */\r
486                 power = (dist+0.05)*warpfac*warpfac*warpfac*(shldup+1);\r
487 \r
488 \r
489                 if (power >= energy) {\r
490                         /* Insufficient power for trip */\r
491                         ididit = 0;\r
492                         skip(1);\r
493                         prout("Engineering to bridge--");\r
494                         if (shldup==0 || 0.5*power > energy) {\r
495                                 iwarp = pow((energy/(dist+0.05)), 0.333333333);\r
496                                 if (iwarp <= 0) {\r
497                                         prout("We can't do it, Captain. We haven't the energy.");\r
498                                 }\r
499                                 else {\r
500                                         proutn("We haven't the energy, but we could do it at warp %d", iwarp);\r
501                                         if (shldup) {\r
502                                                 prout(",");\r
503                                                 prout("if you'll lower the shields.");\r
504                                         }\r
505                                         else\r
506                                                 prout(".");\r
507                                 }\r
508                         }\r
509                         else\r
510                                 prout("We haven't the energy to go that far with the shields up.");\r
511                         return;\r
512                 }\r
513                                                 \r
514                 /* Make sure enough time is left for the trip */\r
515                 Time = 10.0*dist/wfacsq;\r
516                 if (Time >= 0.8*game.state.remtime) {\r
517                         skip(1);\r
518                         prout("First Officer Spock- \"Captain, I compute that such");\r
519                         proutn("  a trip would require approximately %2.0f",\r
520                                 100.0*Time/game.state.remtime);\r
521                         prout(" percent of our");\r
522                         prout(" remaining time.  Are you sure this is wise?\"");\r
523                         if (ja() == 0) { ididit = 0; return;}\r
524                 }\r
525         }\r
526         /* Entry WARPX */\r
527         if (warpfac > 6.0) {\r
528                 /* Decide if engine damage will occur */\r
529                 double prob = dist*(6.0-warpfac)*(6.0-warpfac)/66.666666666;\r
530                 if (prob > Rand()) {\r
531                         blooey = 1;\r
532                         dist = Rand()*dist;\r
533                 }\r
534                 /* Decide if time warp will occur */\r
535                 if (0.5*dist*pow(7.0,warpfac-10.0) > Rand()) twarp=1;\r
536 #ifdef DEBUG\r
537                 if (idebug &&warpfac==10 && twarp==0) {\r
538                         blooey=0;\r
539                         proutn("Force time warp? ");\r
540                         if (ja()==1) twarp=1;\r
541                 }\r
542 #endif\r
543                 if (blooey || twarp) {\r
544                         /* If time warp or engine damage, check path */\r
545                         /* If it is obstructed, don't do warp or damage */\r
546                         double angle = ((15.0-direc)*0.5235998);\r
547                         double deltax = -sin(angle);\r
548                         double deltay = cos(angle);\r
549                         double bigger, x, y;\r
550                         int n, l, ix, iy;\r
551                         if (fabs(deltax) > fabs(deltay))\r
552                                 bigger = fabs(deltax);\r
553                         else\r
554                                 bigger = fabs(deltay);\r
555                         \r
556                         deltax /= bigger;\r
557                         deltay /= bigger;\r
558                         n = 10.0 * dist * bigger +0.5;\r
559                         x = sectx;\r
560                         y = secty;\r
561                         for (l = 1; l <= n; l++) {\r
562                                 x += deltax;\r
563                                 ix = x + 0.5;\r
564                                 if (ix < 1 || ix > 10) break;\r
565                                 y += deltay;\r
566                                 iy = y +0.5;\r
567                                 if (iy < 1 || iy > 10) break;\r
568                                 if (game.quad[ix][iy] != IHDOT) {\r
569                                         blooey = 0;\r
570                                         twarp = 0;\r
571                                 }\r
572                         }\r
573                 }\r
574         }\r
575                                 \r
576 \r
577         /* Activate Warp Engines and pay the cost */\r
578         move();\r
579         if (alldone) return;\r
580         energy -= dist*warpfac*warpfac*warpfac*(shldup+1);\r
581         if (energy <= 0) finish(FNRG);\r
582         Time = 10.0*dist/wfacsq;\r
583         if (twarp) timwrp();\r
584         if (blooey) {\r
585                 game.damage[DWARPEN] = damfac*(3.0*Rand()+1.0);\r
586                 skip(1);\r
587                 prout("Engineering to bridge--");\r
588                 prout("  Scott here.  The warp engines are damaged.");\r
589                 prout("  We'll have to reduce speed to warp 4.");\r
590         }\r
591         ididit = 1;\r
592         return;\r
593 }\r
594 \r
595 \r
596 \r
597 void setwrp(void) {\r
598         int key;\r
599         double oldfac;\r
600         \r
601         while ((key=scan()) == IHEOL) {\r
602                 chew();\r
603                 proutn("Warp factor-");\r
604         }\r
605         chew();\r
606         if (key != IHREAL) {\r
607                 huh();\r
608                 return;\r
609         }\r
610         if (game.damage[DWARPEN] > 10.0) {\r
611                 prout("Warp engines inoperative.");\r
612                 return;\r
613         }\r
614         if (game.damage[DWARPEN] > 0.0 && aaitem > 4.0) {\r
615                 prout("Engineer Scott- \"I'm doing my best, Captain,\n"\r
616                           "  but right now we can only go warp 4.\"");\r
617                 return;\r
618         }\r
619         if (aaitem > 10.0) {\r
620                 prout("Helmsman Sulu- \"Our top speed is warp 10, Captain.\"");\r
621                 return;\r
622         }\r
623         if (aaitem < 1.0) {\r
624                 prout("Helmsman Sulu- \"We can't go below warp 1, Captain.\"");\r
625                 return;\r
626         }\r
627         oldfac = warpfac;\r
628         warpfac = aaitem;\r
629         wfacsq=warpfac*warpfac;\r
630         if (warpfac <= oldfac || warpfac <= 6.0) {\r
631                 proutn("Helmsman Sulu- \"Warp factor %do, Captain.\"", \r
632                         (int)warpfac);\r
633                 return;\r
634         }\r
635         if (warpfac < 8.00) {\r
636                 prout("Engineer Scott- \"Aye, but our maximum safe speed is warp 6.\"");\r
637                 return;\r
638         }\r
639         if (warpfac == 10.0) {\r
640                 prout("Engineer Scott- \"Aye, Captain, we'll try it.\"");\r
641                 return;\r
642         }\r
643         prout("Engineer Scott- \"Aye, Captain, but our engines may not take it.\"");\r
644         return;\r
645 }\r
646 \r
647 void atover(int igrab) {\r
648         double power, distreq;\r
649 \r
650         chew();\r
651         /* is captain on planet? */\r
652         if (landed==1) {\r
653                 if (game.damage[DTRANSP]) {\r
654                         finish(FPNOVA);\r
655                         return;\r
656                 }\r
657                 prout("Scotty rushes to the transporter controls.");\r
658                 if (shldup) {\r
659                         prout("But with the shields up it's hopeless.");\r
660                         finish(FPNOVA);\r
661                 }\r
662                 prouts("His desperate attempt to rescue you . . .");\r
663                 if (Rand() <= 0.5) {\r
664                         prout("fails.");\r
665                         finish(FPNOVA);\r
666                         return;\r
667                 }\r
668                 prout("SUCCEEDS!");\r
669                 if (imine) {\r
670                         imine = 0;\r
671                         proutn("The crystals mined were ");\r
672                         if (Rand() <= 0.25) {\r
673                                 prout("lost.");\r
674                         }\r
675                         else {\r
676                                 prout("saved.");\r
677                                 icrystl = 1;\r
678                         }\r
679                 }\r
680         }\r
681         if (igrab) return;\r
682 \r
683         /* Check to see if captain in shuttle craft */\r
684         if (icraft) finish(FSTRACTOR);\r
685         if (alldone) return;\r
686 \r
687         /* Inform captain of attempt to reach safety */\r
688         skip(1);\r
689         do {\r
690                 if (justin) {\r
691                         prouts("***RED ALERT!  READ ALERT!");\r
692                         skip(1);\r
693                         proutn("The ");\r
694                         crmshp();\r
695                         prout(" has stopped in a quadrant containing");\r
696                         prouts("   a supernova.");\r
697                         skip(2);\r
698                 }\r
699                 proutn("***Emergency automatic override attempts to hurl ");\r
700                 crmshp();\r
701                 skip(1);\r
702                 prout("safely out of quadrant.");\r
703                 game.starch[quadx][quady] = game.damage[DRADIO] > 0.0 ? game.state.galaxy[quadx][quady]+1000:1;\r
704 \r
705                 /* Try to use warp engines */\r
706                 if (game.damage[DWARPEN]) {\r
707                         skip(1);\r
708                         prout("Warp engines damaged.");\r
709                         finish(FSNOVAED);\r
710                         return;\r
711                 }\r
712                 warpfac = 6.0+2.0*Rand();\r
713                 wfacsq = warpfac * warpfac;\r
714                 prout("Warp factor set to %d", (int)warpfac);\r
715                 power = 0.75*energy;\r
716                 dist = power/(warpfac*warpfac*warpfac*(shldup+1));\r
717                 distreq = 1.4142+Rand();\r
718                 if (distreq < dist) dist = distreq;\r
719                 Time = 10.0*dist/wfacsq;\r
720                 direc = 12.0*Rand();    /* How dumb! */\r
721                 justin = 0;\r
722                 inorbit = 0;\r
723                 warp(2);\r
724                 if (justin == 0) {\r
725                         /* This is bad news, we didn't leave quadrant. */\r
726                         if (alldone) return;\r
727                         skip(1);\r
728                         prout("Insufficient energy to leave quadrant.");\r
729                         finish(FSNOVAED);\r
730                         return;\r
731                 }\r
732                 /* Repeat if another snova */\r
733         } while (game.state.galaxy[quadx][quady] == 1000);\r
734         if (game.state.remkl==0) finish(FWON); /* Snova killed remaining enemy. */\r
735 }\r
736 \r
737 void timwrp() {\r
738         int l, ll, gotit;\r
739         prout("***TIME WARP ENTERED.");\r
740         if (game.state.snap && Rand() < 0.5) {\r
741                 /* Go back in time */\r
742                 prout("You are traveling backwards in time %d stardates.",\r
743                       (int)(game.state.date-game.snapsht.date));\r
744                 game.state = game.snapsht;\r
745                 game.state.snap = 0;\r
746                 if (game.state.remcom) {\r
747                         game.future[FTBEAM] = game.state.date + expran(intime/game.state.remcom);\r
748                         game.future[FBATTAK] = game.state.date + expran(0.3*intime);\r
749                 }\r
750                 game.future[FSNOVA] = game.state.date + expran(0.5*intime);\r
751                 game.future[FSNAP] = game.state.date +expran(0.25*game.state.remtime); /* next snapshot will\r
752                                                                                                            be sooner */\r
753                 if (game.state.nscrem) game.future[FSCMOVE] = 0.2777;\r
754                 isatb = 0;\r
755                 game.future[FCDBAS] = game.future[FSCDBAS] = 1e30;\r
756                 batx = baty = 0;\r
757 \r
758                 /* Make sure Galileo is consistant -- Snapshot may have been taken\r
759                    when on planet, which would give us two Galileos! */\r
760                 gotit = 0;\r
761                 for (l = 0; l < inplan; l++) {\r
762                         if (game.state.plnets[l].known == shuttle_down) {\r
763                                 gotit = 1;\r
764                                 if (iscraft==1 && ship==IHE) {\r
765                                         prout("Checkov-  \"Security reports the Galileo has disappeared, Sir!");\r
766                                         iscraft = 0;\r
767                                 }\r
768                         }\r
769                 }\r
770                 /* Likewise, if in the original time the Galileo was abandoned, but\r
771                    was on ship earlier, it would have vanished -- lets restore it */\r
772                 if (iscraft==0 && gotit==0 && game.damage[DSHUTTL] >= 0.0) {\r
773                         prout("Checkov-  \"Security reports the Galileo has reappeared in the dock!\"");\r
774                         iscraft = 1;\r
775                 }\r
776 \r
777                 /* Revert star chart to earlier era, if it was known then*/\r
778                 if (game.damage[DRADIO]==0.0 || stdamtim > game.state.date) {\r
779                         for (l = 1; l <= 8; l++)\r
780                                 for (ll = 1; ll <= 8; ll++)\r
781                                         if (game.starch[l][ll] > 1)\r
782                                                 game.starch[l][ll]=game.damage[DRADIO]>0.0 ? game.state.galaxy[l][ll]+1000 :1;\r
783                         prout("Spock has reconstructed a correct star chart from memory");\r
784                         if (game.damage[DRADIO] > 0.0) stdamtim = game.state.date;\r
785                 }\r
786         }\r
787         else {\r
788                 /* Go forward in time */\r
789                 Time = -0.5*intime*log(Rand());\r
790                 prout("You are traveling forward in time %d stardates.", (int)Time);\r
791                 /* cheat to make sure no tractor beams occur during time warp */\r
792                 game.future[FTBEAM] += Time;\r
793                 game.damage[DRADIO] += Time;\r
794         }\r
795         newqad(0);\r
796 }\r
797 \r
798 void probe(void) {\r
799         double angle, bigger;\r
800         int key;\r
801         /* New code to launch a deep space probe */\r
802         if (nprobes == 0) {\r
803                 chew();\r
804                 skip(1);\r
805                 if (ship == IHE) \r
806                         prout("Engineer Scott- \"We have no more deep space probes, Sir.\"");\r
807                 else\r
808                         prout("Ye Faerie Queene has no deep space probes.");\r
809                 return;\r
810         }\r
811         if (game.damage[DDSP] != 0.0) {\r
812                 chew();\r
813                 skip(1);\r
814                 prout("Engineer Scott- \"The probe launcher is damaged, Sir.\"");\r
815                 return;\r
816         }\r
817         if (game.future[FDSPROB] != 1e30) {\r
818                 chew();\r
819                 skip(1);\r
820                 if (game.damage[DRADIO] != 0 && condit != IHDOCKED) {\r
821                         prout("Spock-  \"Records show the previous probe has not yet");\r
822                         prout("   reached its destination.\"");\r
823                 }\r
824                 else\r
825                         prout("Uhura- \"The previous probe is still reporting data, Sir.\"");\r
826                 return;\r
827         }\r
828         key = scan();\r
829 \r
830         if (key == IHEOL) {\r
831                 /* slow mode, so let Kirk know how many probes there are left */\r
832                 prout(nprobes==1 ? "%d probe left." : "%d probes left.", nprobes);\r
833                 proutn("Are you sure you want to fire a probe? ");\r
834                 if (ja()==0) return;\r
835         }\r
836 \r
837         isarmed = FALSE;\r
838         if (key == IHALPHA && strcmp(citem,"armed") == 0) {\r
839                 isarmed = TRUE;\r
840                 key = scan();\r
841         }\r
842         else if (key == IHEOL) {\r
843                 proutn("Arm NOVAMAX warhead?");\r
844                 isarmed = ja();\r
845         }\r
846         getcd(TRUE, key);\r
847         if (direc == -1.0) return;\r
848         nprobes--;\r
849                 angle = ((15.0 - direc) * 0.5235988);\r
850         probeinx = -sin(angle);\r
851         probeiny = cos(angle);\r
852         if (fabs(probeinx) > fabs(probeiny))\r
853                 bigger = fabs(probeinx);\r
854         else\r
855                 bigger = fabs(probeiny);\r
856                 \r
857         probeiny /= bigger;\r
858         probeinx /= bigger;\r
859         proben = 10.0*dist*bigger +0.5;\r
860         probex = quadx*10 + sectx - 1;  // We will use better packing than original\r
861         probey = quady*10 + secty - 1;\r
862         probecx = quadx;\r
863         probecy = quady;\r
864         game.future[FDSPROB] = game.state.date + 0.01; // Time to move one sector\r
865         prout("Ensign Chekov-  \"The deep space probe is launched, Captain.\"");\r
866         return;\r
867 }\r
868 \r
869 void help(void) {\r
870         /* There's more than one way to move in this game! */\r
871         double ddist, xdist, probf;\r
872         int line, l, ix, iy;\r
873 \r
874         chew();\r
875         /* Test for conditions which prevent calling for help */\r
876         if (condit == IHDOCKED) {\r
877                 prout("Lt. Uhura-  \"But Captain, we're already docked.\"");\r
878                 return;\r
879         }\r
880         if (game.damage[DRADIO] != 0) {\r
881                 prout("Subspace radio damaged.");\r
882                 return;\r
883         }\r
884         if (game.state.rembase==0) {\r
885                 prout("Lt. Uhura-  \"Captain, I'm not getting any response from Starbase.\"");\r
886                 return;\r
887         }\r
888         if (landed == 1) {\r
889                 proutn("You must be aboard the ");\r
890                 crmshp();\r
891                 prout(".");\r
892                 return;\r
893         }\r
894         /* OK -- call for help from nearest starbase */\r
895         nhelp++;\r
896         if (basex!=0) {\r
897                 /* There's one in this quadrant */\r
898                 ddist = sqrt(square(basex-sectx)+square(basey-secty));\r
899         }\r
900         else {\r
901                 ddist = 1e30;\r
902                 for (l = 1; l <= game.state.rembase; l++) {\r
903                         xdist=10.0*sqrt(square(game.state.baseqx[l]-quadx)+square(game.state.baseqy[l]-quady));\r
904                         if (xdist < ddist) {\r
905                                 ddist = xdist;\r
906                                 line = l;\r
907                         }\r
908                 }\r
909                 /* Since starbase not in quadrant, set up new quadrant */\r
910                 quadx = game.state.baseqx[line];\r
911                 quady = game.state.baseqy[line];\r
912                 newqad(1);\r
913         }\r
914         /* dematerialize starship */\r
915         game.quad[sectx][secty]=IHDOT;\r
916         proutn("Starbase in %s responds--", cramlc(quadrant, quadx, quady));\r
917         proutn("");\r
918         crmshp();\r
919         prout(" dematerializes.");\r
920         /* Give starbase three chances to rematerialize starship */\r
921         probf = pow((1.0 - pow(0.98,ddist)), 0.33333333);\r
922         for (l = 1; l <= 3; l++) {\r
923                 switch (l) {\r
924                         case 1: proutn("1st"); break;\r
925                         case 2: proutn("2nd"); break;\r
926                         case 3: proutn("3rd"); break;\r
927                 }\r
928                 proutn(" attempt to re-materialize ");\r
929                 crmshp();\r
930                 prouts(" . . . . . ");\r
931                 if (Rand() > probf) break;\r
932                 prout("fails.");\r
933         }\r
934         if (l > 3) {\r
935                 finish(FMATERIALIZE);\r
936                 return;\r
937         }\r
938         /* Rematerialization attempt should succeed if can get adj to base */\r
939         for (l = 1; l <= 5; l++) {\r
940                 ix = basex+3.0*Rand()-1;\r
941                 iy = basey+3.0*Rand()-1;\r
942                 if (ix>=1 && ix<=10 && iy>=1 && iy<=10 && game.quad[ix][iy]==IHDOT) {\r
943                         /* found one -- finish up */\r
944                         prout("succeeds.");\r
945                         sectx=ix;\r
946                         secty=iy;\r
947                         game.quad[ix][iy]=ship;\r
948                         dock();\r
949                         skip(1);\r
950                         prout("Lt. Uhura-  \"Captain, we made it!\"");\r
951                         return;\r
952                 }\r
953         }\r
954         finish(FMATERIALIZE);\r
955         return;\r
956 }\r