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