; Combat for Atari by Larry Wagner ; ; Original disassembly by Harry Dodgson ; Commented further by Nick Bensema. ; Last Update: 8/26/97 ; ; First a bit of history. Combat was included with the ; famous Atari 2600/VCS for many years. As a result, ; if you go to any thrift store, you will find crates ; of Combat cartridges, and some guy from ; rec.games.video.classic swimming through it, refusing ; to admit that Sum Guy just ran off with the mega-rare ; Chase the Chuckwagon cart with the misprinted sideways ; label that he's looking for. ; ; To fully appreciate the trouble people had to go through ; to make an Atari 2600 game, I decided to try my hand at ; picking apart a relatively simple game, Combat. This ; game works in only 2K or ROM and not even the full 128 ; bytes of RAM made available to it. As if that weren't ; enough, the program has to literally draw the screen ; every single frame, and even Combat had to resort ; to changing some graphic or other in the middle of ; a scanline. And the programmer had to walk five miles ; to work, uphill both ways! And he only got a nickel ; a day for writing code! ; ; The Atari 2600, or the VCS, or the 2600VCS, or the ; Atari VCS, or the 2600, or the VCS-2600, or the Sears ; Home Arcade System, or the Intellivision Add-On Thingy ; That Plays Atari 2600, VCS, 2600VCS, Atari VCS, 2600, ; VCS-2600, and Sears games, runs with a 6507 processof. ; This processor is exactly like the 6502 found in Apple, ; Atari, and Commodore home computers except for two ; things: 1) it has a wait state, and 2) it has only ; 13 address lines instead of 16. So, while your Apple ; II can address $0000-$FFFF, the Atari 2600 could ; only address $0000-$1FFF. That's a whopping 8K. ; The cartridge ROM accounted for anything about $1000. ; You're going to love this part. It had 128 bytes of RAM ; at $0080-$00FF, and the TIA, its video chip, which ; doubles as the 2600's entire video memory, at both ; $0000-$007F, and $0100-$017F. The first copy, along ; with the RAM, could be accessed with zero-page addresses, ; saving space on the ROM, which by the way was 2K. ; The second copy infiltrated the last 128 bytes of the ; 6507's built-in stack. In the source code, you'll see ; how this is used to the programmer's advantage. ; ; That's all I'm explaining. If you want to hear more ; on the 2600's specifications, do a web search for ; 2600 programming information, because I've already ; wasted so much of your time. ; ; I did a lot of cutting and pasting and searching ; and replacing. Be sure to check that this compiles ; to exactly 2048 bytes, and that it matches up with ; all of your uncommented source code before trying to ; modify it... if you dare! For some reason the guy ; who disassembled this didn't put $ before all the hex ; numbers... so keep in mind, hex is always implied. ; ; I also suggest you hand this to those who want to pirate ; 2600 cartridges. Not that it'll stop them, but it might ; make them feel guilty enough to seek absolution. ; ; Not having an assembler, and of course not wanting ; to try to use an emulator, I may have screwed up ; big-time on many aspects of this program. ; Forgive me if I did. ; ; Note a few things: ; ; 1. If you don't know what the BIT instruction does, ; I'll just sum up how Kaplan used it here. Kaplan ; used BIT to test bits 7 and 6 of a memory location. ; If bit 7 was set, the negative flag would be set, ; so the following BMI would cause a branch. If bit ; 6 was set, the overflow flag would be set, so the ; following BVS would cause a branch. If I find an ; assembler that does macros, I'll use those to do this. ; ; 2. I might refer to players as tanks even though they ; could just as easily be biplanes or jets. ; processor 6502 include vcs.h GAMVAR = $A3 ;Game Variation BCDvar = $81 ;Game Variation in BCD DIRECTN = $95 ;Players and missiles' current bearing. GAMSHP = $85 ;Shape of player and game type ;0 = Tank ;1 = Biplane ;2 = Jet Fighter SCROFF = $E0 ;Score pattern offsets NUMG0 = $DE ;Storage for current byte NUMG1 = $DF ;of score number graphics. TMPSTK = $D3 ;Temporary storage for stack. GUIDED = $83 ;Whether game is a guided missile game GTIMER = $86 ;Game timer. SHOWSCR = $87 ;Show/hide right player score ScanLine = $B4 ;Current scanline on the playfield. SHAPES = $BB ;Pointer to player sprites SCORE = $A1 ;Player scores in BCD. TankY0 = $A4 ;Tank 0's Y-position TankY1 = $A5 ; MissileY0 = $A6 ;Missile 0's Y-position MissileY1 = $A7 ; TEMP = $D2;"score conversion temporary" XOFFS = $B0 ;X-offset for Hmove. LORES = $B5 ;lo-res indirect addresses. HIRES = $BD ;Hi-res shape data. ;Left player's shape stored in ;all even bytes, right player's ;shape stored in all odd bytes. DIFSWCH = $D5 Color0 = $D6 ;Tank Colors. Color1 = $D7 org $1000 START ; Two bytes of housekeeping that must be done... SEI ; Disable interrupts CLD ; Clear decimal bit LDX #$FF TXS ; Set stack to beginning. ; In all truthfulness, LDX #$5D JSR ClearMem ; zero out $00 thru $A2 LDA #$10 STA SWCHB+1 ;Port B data direction register STA $88 ;and $88... JSR J11A3 MLOOP JSR NWSCR ; $1014 JSR ConSwitch JSR J1572 JSR J12DA JSR J1444 JSR J1214 JSR J12A9 JSR BCD2SCR JSR DRAW JMP MLOOP ; NWSCR INC GTIMER ; initial blanking and retrace start STA HMCLR ;Clear horizontal move registers. LDA #2 STA WSYNC STA VBLANK STA WSYNC STA WSYNC STA WSYNC STA VSYNC STA WSYNC STA WSYNC LDA #0 STA WSYNC STA VSYNC LDA #43 STA TIM64T ;set 64 clock interval. RTS ; ; Drawing the screen in the following routine. ; We start with the score, then we render the ; playfield, tanks, and missiles simultaneously. ; All in all, an average day for a VCS. ; DRAW LDA #$20 STA ScanLine ;We're assuming scanline 20. STA WSYNC STA HMOVE ;Move sprites horizontally. B105C LDA INTIM BNE B105C ;Wait for INTIM to time-out. STA WSYNC STA CXCLR ;Clear collision latches STA VBLANK ;We even have to do our own ;vertical blanking! Oh, the ;humanity! TSX STX TMPSTK ; Save stack pointer LDA #$02 STA CTRLPF ; Double, instead of reflect. LDX $DC B1070 STA WSYNC ; Skip a few scanlines... DEX BNE B1070 LDA $DC CMP #$0E BEQ B10CD ; DC is set as such so that when the score is to ; be displayed, it waits for just the right time ; to start drawing the score, but if the score is ; not to be displayed, as when the score flashes ; signifying "time's almost up", it waits for just ; the right time to start drawing the rest of the ; screen. ; ; Start by drawing the score. ; LDX #$05 ;Score is five bytes high. LDA #$00 ;Clear number graphics. STA NUMG0 ;They won't be calculated yet, STA NUMG1 ;but first time through the loop ;the game will try to draw with ;them anyway. DRWSCR STA WSYNC ;Start with a fresh scanline. LDA NUMG0 ;Take last scanline's left score, STA PF1 ;and recycle it, ;Here, we begin drawing the next scanline's ;left score, as the electron beam moves towards ;the right score's position in this scanline. LDY SCROFF+2 LDA NUMBERS,Y ;Get left digit. AND #$F0 STA NUMG0 LDY SCROFF LDA NUMBERS,Y ;Get right digit. AND #$0F ORA NUMG0 STA NUMG0 ;Left score is ready to ship. LDA NUMG1 ;Take last scanline's right score, STA PF1 ;and recycle it. LDY SCROFF+3 LDA NUMBERS,Y ;Left digit... AND #$F0 STA NUMG1 LDY SCROFF+1 LDA NUMBERS,Y ;right digit... AND SHOWSCR ;Now, we use our fresh, new ;score graphics in ;this next scanline. STA WSYNC ; *COUNT* ORA NUMG1 ;Finish calculating (0) +3 STA NUMG1 ;right score. (3) +3 LDA NUMG0 ; (6) +3 STA PF1 ; *9* +3 ;We use this time to check ;whether we're at ;the end of our loop. DEX ; (12)+2 BMI B10CD ; (14)+2 No Branch ;If so, we're out of here. Don't worry, ;the score will be cleared immediately, so ;nobody will know that we've gone past five ;bytes and are displaying garbage. INC SCROFF ; (16)+5 INC SCROFF+2 ; Get ready to draw the next INC SCROFF+1 ; line of the byte. INC SCROFF+3 LDA NUMG1 STA PF1 ; Right score is in place. JMP DRWSCR ;Go to next scanline, ; and that is how we do that... ; ; See what it takes just to display a pair of two-digit ; scores? If you think that's rough, figure out how ; they displayed those six-digit scores in the early ; 1980's. Also consider Stellar Track.... well, if ; you've seen Stellar Track, you know exactly what I'm ; talking about. Full-fledged twelve-column text. ; ; Display loop for playfield. ; B10CD LDA #$00 ; Inner Display Loop STA PF1 ; Clear the score. STA WSYNC LDA #$05 STA CTRLPF ;Reflecting playfield. LDA Color0 STA COLUP0 ;How often must THIS be done? LDA Color1 STA COLUP1 DRWFLD LDX #$1E TXS ;Very Sneaky - set stack to missle registers SEC ; This yields which line of player 0 to draw. LDA TankY0 SBC ScanLine ; A=TankY0-ScanLine AND #$FE ;Force an even number TAX ; Only sixteen bytes of sprite memory, so... AND #$F0 BEQ B10F2 ; If not valid, ; If it's not valid, blank the tank. LDA #$00 BEQ B10F4 ; Else, load the appropriate byte. B10F2 LDA HIRES,X B10F4 STA WSYNC ;---------------END OF ONE LINE------ STA GRP0 ; Just for player 0. ; Keep in mind that at this point, the stack pointer ; is set to the missile registers, and the "zero-result" ; bit of the P register is the same at the bit ENAM0/1 ; looks at. LDA MissileY1 EOR ScanLine AND #$FE PHP ; This turns the missle 1 on/off LDA MissileY0 EOR ScanLine AND #$FE PHP ; This turns the missle 0 on/off ;We've got the missile taken care of. ;Now let's see which line of the playfield to draw. LDA ScanLine ; BPL B110C ;If on the bottom half of the screen, EOR #$F8 ;reverse direction so we can mirror. B110C CMP #$20 ; BCC B1114 ;Branch if at bottom. LSR LSR LSR ;Divide by eight, TAY ;and stow it in the Y-register. ;By now, the electron beam is already at the next ;scanline, so we don't have to do a STA WSYNC. ; This yields which line of Tank 1 to draw. B1114 LDA TankY1 ;TankY1 is other player's position. SEC SBC ScanLine ;A=TankY1 - ScanLine INC ScanLine ;Increment the loop. NOP ORA #$01 ;Add bit 0, force odd number. TAX ; There are only sixteen bytes of sprite memory, so... AND #$F0 BEQ B1127 ; If tank is not ready, blank it. LDA #$00 BEQ B1129 ; Else, draw tank. B1127 LDA HIRES,X ;draw the tank B1129 BIT $82 STA GRP1 BMI B113B ;If 82 bit set to 1, skip draw. (?) LDA (LORES),Y STA PF0 LDA (LORES+2),Y STA PF1 LDA (LORES+4),Y STA PF2 B113B INC ScanLine ;One more up in the loop. LDA ScanLine EOR #$EC ;When we've reached the $ECth line, BNE DRWFLD ;we've had enough. LDX TMPSTK ; Restore stack pointer TXS ; which is NEVER USED ANYWHERE ELSE... STA ENAM0 ; Clear a bunch of registers. STA ENAM1 STA GRP0 STA GRP1 STA GRP0 ;In case GRP0 isn't COMPLETELY zeroed. STA PF0 STA PF1 STA PF2 RTS ; ; Executed immediately after NWSCR. ; ; This subroutine parses all the console switches. ; ConSwitch LDA SWCHB ;Start/Reset button.... LSR ;Shove bit 0 into carry flag, BCS B1170 ;and if it's pushed... ; Start a new game. LDA #$0F STA SHOWSCR ;Show right score. LDA #$FF ;Set all bits STA $88 ;in $88. LDA #$80 STA $DD LDX #$E6 JSR ClearMem ; zero out $89 thru $A2 BEQ ResetField ;Unconditional branch B1170 LDY #$02 LDA $DD AND $88 CMP #$F0 BCC B1182 LDA GTIMER ;GTIMER is the timer. AND #$30 BNE B1182 LDY #$0E B1182 STY $DC LDA GTIMER AND #$3F BNE B1192 STA $89 INC $DD BNE B1192 STA $88 B1192 LDA SWCHB ; Select button. ??? AND #$02 BEQ B119D STA $89 BNE CS_RTS B119D BIT $89 BMI CS_RTS INC $80 ;Go to next game. J11A3 LDX #$DF ;Clear data from current game B11A5 JSR ClearMem ; LDA #$FF STA $89 LDY $80 LDA VARDATA,Y ;Get data bits for this variation. STA GAMVAR EOR #$FF ;#$FF signifies end of variations BNE B11BB LDX #$DD BNE B11A5 ; Clear all gamewise memory and start over. B11BB LDA BCDvar ;Remember we have to increment with BCD... SED CLC ADC #1 STA BCDvar STA SCORE CLD BIT GAMVAR BPL ResetField ;if this is a plane game, INC GAMSHP ;increase GAMSHP. BVC ResetField ;if this is a jet game, INC GAMSHP ;increase GAMSHP further still. ; Branch here when game is started, too. ResetField JSR InitField ; Assuming plane game for now, we set the right player ; at a slightly higher position than the left player, ; and the position of the right player is irrelevant. LDA #50 STA TankY1 LDA #134 STA TankY0 BIT GAMVAR ;Check to see if it is a tank game. BMI CS_RTS ; If it really is a tank game.. STA TankY1 ; Right tank has same Y value, STA RESP1 ;and tank is at opposite side. LDA #$08 STA DIRECTN+1 ;and right player faces left. LDA #$20 STA HMP0 STA HMP1 STA WSYNC STA HMOVE CS_RTS RTS ; ; convert BCD scores to score pattern offset. ; This involves the horrible, horrible implications ; involved in multiplying by five. ; ; If it weren't for the geniuses at NMOS using BCD, ; this routine would be a nightmare. ; BCD2SCR LDX #$01 B11F4 LDA SCORE,X AND #$0F STA TEMP ASL ASL CLC ADC TEMP STA SCROFF,X LDA SCORE,X AND #$F0 LSR LSR STA TEMP LSR LSR CLC ADC TEMP STA SCROFF+2,X DEX BPL B11F4 RTS ; ; ; J1214 BIT GUIDED BVC B121C ;Branch if bit 6 of 83 is clear. LDA #$30 BPL B121E ;JMP. B121C LDA #$20 B121E STA $B1 ;Either $30 or $20 goes here... LDX #$03 JSR J1254 DEX ;X, I _think_, is now 2. JSR J1254 DEX ;And I _think_ it's now 1. B122A LDA $8D,X ;Velocity register AND #$08 LSR LSR STX $D1 CLC ADC $D1 TAY ; Y=($8D,X)&8 / 4 + X ; $00A8,Y is either $00A8,X or $00AA,X. LDA $00A8,Y ;We can't use zero-page? Waaah! SEC BMI B123D CLC ;^^ That's just a fancy way to ; transfer bit 7 to Carry Bit. B123D ROL ;ROL, the wave of the future. STA $00A8,Y BCC B1250 LDA $AC,X AND #$01 ASL ASL ASL ASL STA $B1 ; B1 = (AC & 1) << 4 JSR J1254 B1250 DEX ;Move to _previous_ player. BEQ B122A ;Stop if about to do player -1. :) RTS ; ; This routine will move both tanks and missiles. ; Special cases are made for missiles, which are ; otherwise treated as players 2 and 3. ; ; It doesn't change the X register, but it does ; utilize it. ; J1254 INC $AC,X LDA DIRECTN,X AND #$0F CLC ADC $B1 TAY LDA L15F7,Y ;This has offset information. STA XOFFS ;Store the X-offset. BIT $82 BVS B127A ;Branch if bit 6 of 82 is set. LDA DIRECTN,X SEC SBC #$02 AND #$03 BNE B127A LDA $AC,X AND #$03 BNE B127A ;if AC isn't set, we're go for move. LDA #$08 STA XOFFS B127A LDA XOFFS J127C STA HMP0,X ;Use this to move the tank. AND #$0F SEC SBC #$08 STA $D4 CLC ADC TankY0,X BIT GAMVAR BMI B1290 ;Branch if a plane game. ;What follows is probably a bounds check. CPX #$02 BCS B12A0 ;Branch if moving a player B1290 CMP #$DB BCS B1298 CMP #$25 BCS B12A0 B1298 LDA #$D9 BIT $D4 BMI B12A0 LDA #$28 ;#$28 if D4 is positive, #$D9 if not B12A0 STA TankY0,X ;The tank/missile is moved here. CPX #$02 BCS B12A8 ;Skip if moving a missile. STA VDELP0,X ;Vertical Delay Player X... B12A8 RTS ; ; This subroutine sets up the sprite data for each player by copying ; them into sixteen bytes of RAM. ; ; The X-register starts at 0x0E plus player number and goes down by two ; each time through the loop, until it hits zero. This way, after calling ; this subroutine twice, every even-numbered byte contains the left player ; shape, and every odd-numbered byte contains the right player shape. Since ; each player is updated every two scanlines, this saves us some math. ; ; Only the first 180 degrees of rotation has been drawn into ROM. In the ; case of the other 180 degrees, this subroutine renders a flipped version ; by doing the following: ; ; 1. It sets the TIA's reflection flag for that player, taking care of ; the horizontal aspect rather easily. ; ; 2. It copies the bytes into memory last-to-first instead of first-to- ; last, using the carry bit as a flag for which to do. ; J12A9 LDA #$01 AND GTIMER TAX LDA DIRECTN,X STA REFP0,X ;Step 1 taken care of. AND #$0F TAY ;Y = DIRECTN[X] & 0x0F. BIT GUIDED BPL B12BB ;If bit 7 is set, STY DIRECTN+2,X ;then set missile bearings(?) B12BB TXA ; X ^= 0x0E, EOR #$0E ; TAX ; TYA ASL ASL ASL CMP #$3F ;And so step 2 begins... CLC BMI B12CB ;Branch if <180 deg. SEC EOR #$47 ;and it doesn't end here. ;The EOR sets bits 0-2, and clears bit 4 ;to subtract 180 degrees from the memory ;pointer, too. B12CB TAY ;Put all the shapes where they ought to be. B12CC LDA (SHAPES),Y STA HIRES,X BCC B12D4 DEY ; Decrement instead of increment DEY ; plus cancel the upcoming INY. B12D4 INY ;More of step 2. DEX DEX ;X-=2. BPL B12CC ;Keep going until X runs out. RTS ; ; Stir the tanks. :-) ; J12DA LDA $8A SEC SBC #$02 BCC B130C ;If tank is not exploding, ;parse joystick instead. STA $8A CMP #$02 BCC B130B ;RTS if tank has ;just finished exploding. AND #$01 ;Stir the LOSER's tank. TAX ;One of these is the tank's bearings. INC DIRECTN,X LDA $D8,X STA Color0,X LDA $8A CMP #$F7 BCC B12F9 JSR J1508 B12F9 LDA $8A BPL B130B ;Don't start decrementing ;volume until halfway through. LSR LSR LSR J1300 STA AUDV0,X ;Sound effects. BOOOM! LDA #$08 STA AUDC0,X LDA L17FE,X STA AUDF0,X B130B RTS ; ; Process joysticks. ; B130C LDX #$01 LDA SWCHB ;Console switches. STA DIFSWCH ;Store switches in D5. LDA SWCHA ;Joysticks. B1316 BIT $88 BMI B131C ;Branch if bit 7 is set. LDA #$FF ;Freeze all joystick movement. B131C EOR #$FF ;Reverse all bits AND #$0F ;Keep high four bits (Right Player) ;At this point, the joystick's switches are in ;the A-register, with a bit set wherever the ;joystick is pointed. ; Bit 0 = up Bit 1 = down ; Bit 2 = left Bit 3 = right STA TEMP LDY GAMSHP LDA L170F,Y ;Account for two-dimensional array CLC ADC TEMP TAY LDA CTRLTBL,Y AND #$0F ;Get rotation from table. STA $D1 BEQ B1338 ;Branch if no turn. CMP $91,X BNE B133C ;Some speed control I'm guessing. B1338 DEC $93,X BNE B1349 B133C STA $91,X LDA #$0F STA $93,X ; Turn the tank here. LDA $D1 CLC ADC DIRECTN,X STA DIRECTN,X B1349 INC $8D,X BMI B136B LDA CTRLTBL,Y LSR LSR LSR LSR ;Get velocity from table. BIT DIFSWCH BMI B137B B1358 STA $8B,X ; Stash velocity in $8B ASL ;Multiply by two TAY ;Stash in Y. LDA L1637,Y STA $A8,X ;This is the player's ? INY LDA L1637,Y STA $AA,X LDA #$F0 STA $8D,X B136B JSR J1380 LDA SWCHA ;Joysticks.. LSR LSR LSR LSR ;Keep bottom four bits (Left Player) ASL DIFSWCH ;Use other difficulty switch. DEX BEQ B1316 ; RTS ; B137B SEC SBC GAMSHP BPL B1358 ;If GAMSHPTankShape, #>PlaneShape, #>JetShape ; Playfield address data ; ; Complex, None, Simple, Clouds PLFPNT .BYTE $75 ,$75 ,$75 ,$9A .BYTE $81 ,$99 ,$AA ,$9D .BYTE $8D ,$99 ,$B6 ,$9D ; Format of game, best guess I have so far... ; ; bits ; 1,0: TANKS PLANES ; 00 = Normal 1 vs. 1 ; 01 = Invisible 2 vs. 2 ; 10 = 3 vs. 1 ; 11 = 3 vs. Giant ; 3,2: 01 = No maze ; 10 = Simple maze or clouds ; 00 = Complex maze or no clouds ; 4: Tanks, 1 = Must bounce to score hit ; Planes, 1 = Machine Gun ; 5: 1 = Guided Missiles ; 7,6: 00 = Tanks ; 01 = Tank Pong ; 10 = Biplanes ; 11 = Jet Fighter ; (Bit 7 controls whether this is a tank or plane game) ; VARDATA .BYTE $24 ;Game 1: 0010 0100 TANK .BYTE $28 ;Game 2: 0010 1000 .BYTE $08 ;Game 3: 0000 1000 .BYTE $20 ;Game 4: 0010 0000 .BYTE $00 ;Game 5: 0000 0000 .BYTE $48 ;Game 6: 0100 1000 TANK PONG .BYTE $40 ;Game 7: 0100 0000 .BYTE $54 ;Game 8: 0101 0100 .BYTE $58 ;Game 9: 0101 1000 .BYTE $25 ;Game 10: 0010 0101 INVISIBLE TANK .BYTE $29 ;Game 11: 0010 1001 .BYTE $49 ;Game 12: 0100 1001 .BYTE $55 ;Game 13: 0101 0101 .BYTE $59 ;Game 14: 0101 1001 .BYTE $A8 ;Game 15: 1010 1000 BIPLANE .BYTE $88 ;Game 16: 1000 1000 .BYTE $98 ;Game 17: 1001 1000 .BYTE $90 ;Game 18: 1001 0000 .BYTE $A1 ;Game 19: 1010 0001 .BYTE $83 ;Game 20: 1000 0011 .BYTE $E8 ;Game 21: 1110 1000 JET FIGHTER .BYTE $C8 ;Game 22: 1100 1000 .BYTE $E0 ;Game 23: 1110 0000 .BYTE $C0 ;Game 24: 1100 0000 .BYTE $E9 ;Game 25: 1110 1001 .BYTE $E2 ;Game 26: 1110 0010 .BYTE $C1 ;Game 27: 1100 0001 ; $FF to signify end of game variations. ; Theoretically one could add up to six ; additional variations. .BYTE $FF ORG $17FC .word $f000 ; Reset L17FE .BYTE $0F, $11 ; IRQ - (used as pitch for sound generator) ; ; Recent changes: ; ; 08/05/96: Added dollar-signs to signify hex numbers. ; The original, strangely, omitted them. ; Started update list at end of document. ; Still have no clue where the joystick code ; is.... ; ; 08/12/96: Figured out some joystick code, now that ; I understand how they work. Renamed GAMSHP ; because it wasn't really "velocity", but ; really the tank type. Velocity is now ; what it should be. ; ; 10/19/96: Cracked the mystery of the joystick-port ; write. No, Tim, it's not an LED, it's for ; disabling the joystick when in game select ; mode. Thanks to AlanD for this theory. ; ; 2/21/97: Added cycle counting to score drawing section. ; I'm sure Kaplan wasn't this precise, but it ; is a bit helpful. ; ; 2/26/97: Changed year of above update to 1997. :-) ; Changed a few variable names and made some of ; my notes a bit clearer. I'm also naming some ; of those mysterious JSR's. Plus, it actually ; COMPILES with DASM. Whee! ; ; 8/26/97: Oops. Turns out Larry Wagner made Combat. Sorry.