Skip to navigation

Elite on the BBC Micro and NES

Elite H source

[6502 Second Processor version]

ELITE H FILE Produces the binary file ELTH.bin that gets loaded by elite-bcfs.asm.
CODE_H% = P% LOAD_H% = LOAD% + P% - CODE% \CATLOD \ These instructions are commented out in the original \DEC CTLDL+8 \ source \JSR CATLODS \INC CTLDL+8 \.CATLODS \LDA #127 \LDX #LO(CTLDL) \LDY #HI(CTLDL) \JMP OSWORD \CTLDL \EQUB 0 \EQUD &0E00 \EQUB 3 \EQUB &53 \EQUB 0 \EQUB 1 \EQUB &21 \EQUB 0
Name: MVEIT (Part 1 of 9) [Show more] Type: Subroutine Category: Moving Summary: Move current ship: Tidy the orientation vectors Deep dive: Program flow of the ship-moving routine Scheduling tasks with the main loop counter
Context: See this subroutine on its own page Variations: See code variations for this subroutine in the different versions References: This subroutine is called as follows: * BRIEF calls MVEIT * DEMON calls MVEIT * ESCAPE calls MVEIT * Main flight loop (Part 6 of 16) calls MVEIT * PAS1 calls MVEIT * TITLE calls MVEIT

This routine has multiple stages. This stage does the following: * Tidy the orientation vectors for one of the ship slots
Arguments: INWK The current ship/planet/sun's data block XSAV The slot number of the current ship/planet/sun TYPE The type of the current ship/planet/sun
.MVEIT LDA INWK+31 \ If bits 5 or 7 of ship byte #31 are set, jump to MV30 AND #%10100000 \ as the ship is either exploding or has been killed, so BNE MV30 \ we don't need to tidy its orientation vectors or apply \ tactics LDA MCNT \ Fetch the main loop counter EOR XSAV \ Fetch the slot number of the ship we are moving, EOR AND #15 \ with the loop counter and apply mod 15 to the result. BNE MV3 \ The result will be zero when "counter mod 15" matches \ the slot number, so this makes sure we call TIDY 12 \ times every 16 main loop iterations, like this: \ \ Iteration 0, tidy the ship in slot 0 \ Iteration 1, tidy the ship in slot 1 \ Iteration 2, tidy the ship in slot 2 \ ... \ Iteration 11, tidy the ship in slot 11 \ Iteration 12, do nothing \ Iteration 13, do nothing \ Iteration 14, do nothing \ Iteration 15, do nothing \ Iteration 16, tidy the ship in slot 0 \ ... \ \ and so on JSR TIDY \ Call TIDY to tidy up the orientation vectors, to \ prevent the ship from getting elongated and out of \ shape due to the imprecise nature of trigonometry \ in assembly language
Name: MVEIT (Part 2 of 9) [Show more] Type: Subroutine Category: Moving Summary: Move current ship: Call tactics routine, remove ship from scanner Deep dive: Scheduling tasks with the main loop counter
Context: See this subroutine on its own page Variations: See code variations for this subroutine in the different versions References: No direct references to this subroutine in this source file

This routine has multiple stages. This stage does the following: * Apply tactics to ships with AI enabled (by calling the TACTICS routine) * Remove the ship from the scanner, so we can move it
.MV3 LDX TYPE \ If the type of the ship we are moving is positive, BPL P%+5 \ i.e. it is not a planet (types 128 and 130) or sun \ (type 129), then skip the following instruction JMP MV40 \ This item is the planet or sun, so jump to MV40 to \ move it, which ends by jumping back into this routine \ at MV45 (after all the rotation, tactics and scanner \ code, which we don't need to apply to planets or suns) LDA INWK+32 \ Fetch the ship's byte #32 (AI flag) into A BPL MV30 \ If bit 7 of the AI flag is clear, then if this is a \ ship or missile it is dumb and has no AI, and if this \ is the space station it is not hostile, so in both \ cases skip the following as it has no tactics CPX #MSL \ If the ship is a missile, skip straight to MV26 to BEQ MV26 \ call the TACTICS routine, as we do this every \ iteration of the main loop for missiles only LDA MCNT \ Fetch the main loop counter EOR XSAV \ Fetch the slot number of the ship we are moving, EOR AND #7 \ with the loop counter and apply mod 8 to the result. BNE MV30 \ The result will be zero when "counter mod 8" matches \ the slot number mod 8, so this makes sure we call \ TACTICS 12 times every 8 main loop iterations, like \ this: \ \ Iteration 0, apply tactics to slots 0 and 8 \ Iteration 1, apply tactics to slots 1 and 9 \ Iteration 2, apply tactics to slots 2 and 10 \ Iteration 3, apply tactics to slots 3 and 11 \ Iteration 4, apply tactics to slot 4 \ Iteration 5, apply tactics to slot 5 \ Iteration 6, apply tactics to slot 6 \ Iteration 7, apply tactics to slot 7 \ Iteration 8, apply tactics to slots 0 and 8 \ ... \ \ and so on .MV26 JSR TACTICS \ Call TACTICS to apply AI tactics to this ship .MV30 JSR SCAN \ Draw the ship on the scanner, which has the effect of \ removing it, as it's already at this point and hasn't \ yet moved
Name: MVEIT (Part 3 of 9) [Show more] Type: Subroutine Category: Moving Summary: Move current ship: Move ship forward according to its speed
Context: See this subroutine on its own page References: No direct references to this subroutine in this source file

This routine has multiple stages. This stage does the following: * Move the ship forward (along the vector pointing in the direction of travel) according to its speed: (x, y, z) += nosev_hi * speed / 64
LDA INWK+27 \ Set Q = the ship's speed byte #27 * 4 ASL A ASL A STA Q LDA INWK+10 \ Set A = |nosev_x_hi| AND #%01111111 JSR FMLTU \ Set R = A * Q / 256 STA R \ = |nosev_x_hi| * speed / 64 LDA INWK+10 \ If nosev_x_hi is positive, then: LDX #0 \ JSR MVT1-2 \ (x_sign x_hi x_lo) = (x_sign x_hi x_lo) + R \ \ If nosev_x_hi is negative, then: \ \ (x_sign x_hi x_lo) = (x_sign x_hi x_lo) - R \ \ So in effect, this does: \ \ (x_sign x_hi x_lo) += nosev_x_hi * speed / 64 LDA INWK+12 \ Set A = |nosev_y_hi| AND #%01111111 JSR FMLTU \ Set R = A * Q / 256 STA R \ = |nosev_y_hi| * speed / 64 LDA INWK+12 \ If nosev_y_hi is positive, then: LDX #3 \ JSR MVT1-2 \ (y_sign y_hi y_lo) = (y_sign y_hi y_lo) + R \ \ If nosev_y_hi is negative, then: \ \ (y_sign y_hi y_lo) = (y_sign y_hi y_lo) - R \ \ So in effect, this does: \ \ (y_sign y_hi y_lo) += nosev_y_hi * speed / 64 LDA INWK+14 \ Set A = |nosev_z_hi| AND #%01111111 JSR FMLTU \ Set R = A * Q / 256 STA R \ = |nosev_z_hi| * speed / 64 LDA INWK+14 \ If nosev_y_hi is positive, then: LDX #6 \ JSR MVT1-2 \ (z_sign z_hi z_lo) = (z_sign z_hi z_lo) + R \ \ If nosev_z_hi is negative, then: \ \ (z_sign z_hi z_lo) = (z_sign z_hi z_lo) - R \ \ So in effect, this does: \ \ (z_sign z_hi z_lo) += nosev_z_hi * speed / 64
Name: MVEIT (Part 4 of 9) [Show more] Type: Subroutine Category: Moving Summary: Move current ship: Apply acceleration to ship's speed as a one-off
Context: See this subroutine on its own page References: No direct references to this subroutine in this source file

This routine has multiple stages. This stage does the following: * Apply acceleration to the ship's speed (if acceleration is non-zero), and then zero the acceleration as it's a one-off change
LDA INWK+27 \ Set A = the ship's speed in byte #24 + the ship's CLC \ acceleration in byte #28 ADC INWK+28 BPL P%+4 \ If the result is positive, skip the following \ instruction LDA #0 \ Set A to 0 to stop the speed from going negative LDY #15 \ We now fetch byte #15 from the ship's blueprint, which \ contains the ship's maximum speed, so set Y = 15 to \ use as an index CMP (XX0),Y \ If A < the ship's maximum speed, skip the following BCC P%+4 \ instruction LDA (XX0),Y \ Set A to the ship's maximum speed STA INWK+27 \ We have now calculated the new ship's speed after \ accelerating and keeping the speed within the ship's \ limits, so store the updated speed in byte #27 LDA #0 \ We have added the ship's acceleration, so we now set STA INWK+28 \ it back to 0 in byte #28, as it's a one-off change
Name: MVEIT (Part 5 of 9) [Show more] Type: Subroutine Category: Moving Summary: Move current ship: Rotate ship's location by our pitch and roll Deep dive: Rotating the universe
Context: See this subroutine on its own page References: No direct references to this subroutine in this source file

This routine has multiple stages. This stage does the following: * Rotate the ship's location in space by the amount of pitch and roll of our ship. See below for a deeper explanation of this routine
LDX ALP1 \ Fetch the magnitude of the current roll into X, so \ if the roll angle is alpha, X contains |alpha| LDA INWK \ Set P = ~x_lo (i.e. with all its bits flipped) so that EOR #%11111111 \ we can pass x_lo to MLTU2 below) STA P LDA INWK+1 \ Set A = x_hi JSR MLTU2-2 \ Set (A P+1 P) = (A ~P) * X \ = (x_hi x_lo) * alpha STA P+2 \ Store the high byte of the result in P+2, so we now \ have: \ \ P(2 1 0) = (x_hi x_lo) * alpha LDA ALP2+1 \ Fetch the flipped sign of the current roll angle alpha EOR INWK+2 \ from ALP2+1 and EOR with byte #2 (x_sign), so if the \ flipped roll angle and x_sign have the same sign, A \ will be positive, else it will be negative. So A will \ contain the sign bit of x_sign * flipped alpha sign, \ which is the opposite to the sign of the above result, \ so we now have: \ \ (A P+2 P+1) = - (x_sign x_hi x_lo) * alpha / 256 LDX #3 \ Set (A P+2 P+1) = (y_sign y_hi y_lo) + (A P+2 P+1) JSR MVT6 \ = y - x * alpha / 256 STA K2+3 \ Set K2(3) = A = the sign of the result LDA P+1 \ Set K2(1) = P+1, the low byte of the result STA K2+1 EOR #%11111111 \ Set P = ~K2+1 (i.e. with all its bits flipped) so STA P \ that we can pass K2+1 to MLTU2 below) LDA P+2 \ Set K2(2) = A = P+2 STA K2+2 \ So we now have result 1 above: \ \ K2(3 2 1) = (A P+2 P+1) \ = y - x * alpha / 256 LDX BET1 \ Fetch the magnitude of the current pitch into X, so \ if the pitch angle is beta, X contains |beta| JSR MLTU2-2 \ Set (A P+1 P) = (A ~P) * X \ = K2(2 1) * beta STA P+2 \ Store the high byte of the result in P+2, so we now \ have: \ \ P(2 1 0) = K2(2 1) * beta LDA K2+3 \ Fetch the sign of the above result in K(3 2 1) from EOR BET2 \ K2+3 and EOR with BET2, the sign of the current pitch \ rate, so if the pitch and K(3 2 1) have the same sign, \ A will be positive, else it will be negative. So A \ will contain the sign bit of K(3 2 1) * beta, which is \ the same as the sign of the above result, so we now \ have: \ \ (A P+2 P+1) = K2(3 2 1) * beta / 256 LDX #6 \ Set (A P+2 P+1) = (z_sign z_hi z_lo) + (A P+2 P+1) JSR MVT6 \ = z + K2 * beta / 256 STA INWK+8 \ Set z_sign = A = the sign of the result LDA P+1 \ Set z_lo = P+1, the low byte of the result STA INWK+6 EOR #%11111111 \ Set P = ~z_lo (i.e. with all its bits flipped) so that STA P \ we can pass z_lo to MLTU2 below) LDA P+2 \ Set z_hi = P+2 STA INWK+7 \ So we now have result 2 above: \ \ (z_sign z_hi z_lo) = (A P+2 P+1) \ = z + K2 * beta / 256 JSR MLTU2 \ MLTU2 doesn't change Q, and Q was set to beta in \ the previous call to MLTU2, so this call does: \ \ (A P+1 P) = (A ~P) * Q \ = (z_hi z_lo) * beta STA P+2 \ Set P+2 = A = the high byte of the result, so we \ now have: \ \ P(2 1 0) = (z_hi z_lo) * beta LDA K2+3 \ Set y_sign = K2+3 STA INWK+5 EOR BET2 \ EOR y_sign with BET2, the sign of the current pitch EOR INWK+8 \ rate, and z_sign. If the result is positive jump to BPL MV43 \ MV43, otherwise this means beta * z and y have \ different signs, i.e. P(2 1) and K2(3 2 1) have \ different signs, so we need to add them in order to \ calculate K2(2 1) - P(2 1) LDA P+1 \ Set (y_hi y_lo) = K2(2 1) + P(2 1) ADC K2+1 STA INWK+3 LDA P+2 ADC K2+2 STA INWK+4 JMP MV44 \ Jump to MV44 to continue the calculation .MV43 LDA K2+1 \ Reversing the logic above, we need to subtract P(2 1) SBC P+1 \ and K2(3 2 1) to calculate K2(2 1) - P(2 1), so this STA INWK+3 \ sets (y_hi y_lo) = K2(2 1) - P(2 1) LDA K2+2 SBC P+2 STA INWK+4 BCS MV44 \ If the above subtraction did not underflow, then \ jump to MV44, otherwise we need to negate the result LDA #1 \ Negate (y_sign y_hi y_lo) using two's complement, SBC INWK+3 \ first doing the low bytes: STA INWK+3 \ \ y_lo = 1 - y_lo LDA #0 \ Then the high bytes: SBC INWK+4 \ STA INWK+4 \ y_hi = 0 - y_hi LDA INWK+5 \ And finally flip the sign in y_sign EOR #%10000000 STA INWK+5 .MV44 \ So we now have result 3 above: \ \ (y_sign y_hi y_lo) = K2(2 1) - P(2 1) \ = K2 - beta * z LDX ALP1 \ Fetch the magnitude of the current roll into X, so \ if the roll angle is alpha, X contains |alpha| LDA INWK+3 \ Set P = ~y_lo (i.e. with all its bits flipped) so that EOR #&FF \ we can pass y_lo to MLTU2 below) STA P LDA INWK+4 \ Set A = y_hi JSR MLTU2-2 \ Set (A P+1 P) = (A ~P) * X \ = (y_hi y_lo) * alpha STA P+2 \ Store the high byte of the result in P+2, so we now \ have: \ \ P(2 1 0) = (y_hi y_lo) * alpha LDA ALP2 \ Fetch the correct sign of the current roll angle alpha EOR INWK+5 \ from ALP2 and EOR with byte #5 (y_sign), so if the \ correct roll angle and y_sign have the same sign, A \ will be positive, else it will be negative. So A will \ contain the sign bit of x_sign * correct alpha sign, \ which is the same as the sign of the above result, \ so we now have: \ \ (A P+2 P+1) = (y_sign y_hi y_lo) * alpha / 256 LDX #0 \ Set (A P+2 P+1) = (x_sign x_hi x_lo) + (A P+2 P+1) JSR MVT6 \ = x + y * alpha / 256 STA INWK+2 \ Set x_sign = A = the sign of the result LDA P+2 \ Set x_hi = P+2, the high byte of the result STA INWK+1 LDA P+1 \ Set x_lo = P+1, the low byte of the result STA INWK \ So we now have result 4 above: \ \ x = x + alpha * y \ \ and the rotation of (x, y, z) is done
Name: MVEIT (Part 6 of 9) [Show more] Type: Subroutine Category: Moving Summary: Move current ship: Move the ship in space according to our speed
Context: See this subroutine on its own page Variations: See code variations for this subroutine in the different versions References: This subroutine is called as follows: * MV40 calls via MV45

This routine has multiple stages. This stage does the following: * Move the ship in space according to our speed (we already moved it according to its own speed in part 3). We do this by subtracting our speed (i.e. the distance we travel in this iteration of the loop) from the other ship's z-coordinate. We subtract because they appear to be "moving" in the opposite direction to us, and the whole MVEIT routine is about moving the other ships rather than us (even though we are the one doing the moving).
Other entry points: MV45 Rejoin the MVEIT routine after the rotation, tactics and scanner code
.MV45 LDA DELTA \ Set R to our speed in DELTA STA R LDA #%10000000 \ Set A to zeroes but with bit 7 set, so that (A R) is \ a 16-bit number containing -R, or -speed LDX #6 \ Set X to the z-axis so the call to MVT1 does this: JSR MVT1 \ \ (z_sign z_hi z_lo) = (z_sign z_hi z_lo) + (A R) \ = (z_sign z_hi z_lo) - speed LDA TYPE \ If the ship type is not the sun (129) then skip the AND #%10000001 \ next instruction, otherwise return from the subroutine CMP #129 \ as we don't need to rotate the sun around its origin. BNE P%+3 \ Having both the AND and the CMP is a little odd, as \ the sun is the only ship type with bits 0 and 7 set, \ so the AND has no effect and could be removed RTS \ Return from the subroutine, as the ship we are moving \ is the sun and doesn't need any of the following
Name: MVEIT (Part 7 of 9) [Show more] Type: Subroutine Category: Moving Summary: Move current ship: Rotate ship's orientation vectors by pitch/roll Deep dive: Orientation vectors Pitching and rolling
Context: See this subroutine on its own page References: No direct references to this subroutine in this source file

This routine has multiple stages. This stage does the following: * Rotate the ship's orientation vectors according to our pitch and roll As with the previous step, this is all about moving the other ships rather than us (even though we are the one doing the moving). So we rotate the current ship's orientation vectors (which defines its orientation in space), by the angles we are "moving" the rest of the sky through (alpha and beta, our roll and pitch), so the ship appears to us to be stationary while we rotate.
LDY #9 \ Apply our pitch and roll rotations to the current JSR MVS4 \ ship's nosev vector LDY #15 \ Apply our pitch and roll rotations to the current JSR MVS4 \ ship's roofv vector LDY #21 \ Apply our pitch and roll rotations to the current JSR MVS4 \ ship's sidev vector
Name: MVEIT (Part 8 of 9) [Show more] Type: Subroutine Category: Moving Summary: Move current ship: Rotate ship about itself by its own pitch/roll Deep dive: Orientation vectors Pitching and rolling by a fixed angle
Context: See this subroutine on its own page References: No direct references to this subroutine in this source file

This routine has multiple stages. This stage does the following: * If the ship we are processing is rolling or pitching itself, rotate it and apply damping if required
LDA INWK+30 \ Fetch the ship's pitch counter and extract the sign AND #%10000000 \ into RAT2 STA RAT2 LDA INWK+30 \ Fetch the ship's pitch counter and extract the value AND #%01111111 \ without the sign bit into A BEQ MV8 \ If the pitch counter is 0, then jump to MV8 to skip \ the following, as the ship is not pitching CMP #%01111111 \ If bits 0-6 are set in the pitch counter (i.e. the \ ship's pitch is not damping down), then the C flag \ will be set by this instruction SBC #0 \ Set A = A - 0 - (1 - C), so if we are damping then we \ reduce A by 1, otherwise it is unchanged ORA RAT2 \ Change bit 7 of A to the sign we saved in RAT2, so \ the updated pitch counter in A retains its sign STA INWK+30 \ Store the updated pitch counter in byte #30 LDX #15 \ Rotate (roofv_x, nosev_x) by a small angle (pitch) LDY #9 JSR MVS5 LDX #17 \ Rotate (roofv_y, nosev_y) by a small angle (pitch) LDY #11 JSR MVS5 LDX #19 \ Rotate (roofv_z, nosev_z) by a small angle (pitch) LDY #13 JSR MVS5 .MV8 LDA INWK+29 \ Fetch the ship's roll counter and extract the sign AND #%10000000 \ into RAT2 STA RAT2 LDA INWK+29 \ Fetch the ship's roll counter and extract the value AND #%01111111 \ without the sign bit into A BEQ MV5 \ If the roll counter is 0, then jump to MV5 to skip the \ following, as the ship is not rolling CMP #%01111111 \ If bits 0-6 are set in the roll counter (i.e. the \ ship's roll is not damping down), then the C flag \ will be set by this instruction SBC #0 \ Set A = A - 0 - (1 - C), so if we are damping then we \ reduce A by 1, otherwise it is unchanged ORA RAT2 \ Change bit 7 of A to the sign we saved in RAT2, so \ the updated roll counter in A retains its sign STA INWK+29 \ Store the updated pitch counter in byte #29 LDX #15 \ Rotate (roofv_x, sidev_x) by a small angle (roll) LDY #21 JSR MVS5 LDX #17 \ Rotate (roofv_y, sidev_y) by a small angle (roll) LDY #23 JSR MVS5 LDX #19 \ Rotate (roofv_z, sidev_z) by a small angle (roll) LDY #25 JSR MVS5
Name: MVEIT (Part 9 of 9) [Show more] Type: Subroutine Category: Moving Summary: Move current ship: Redraw on scanner, if it hasn't been destroyed
Context: See this subroutine on its own page Variations: See code variations for this subroutine in the different versions References: No direct references to this subroutine in this source file

This routine has multiple stages. This stage does the following: * If the ship is exploding or being removed, hide it on the scanner * Otherwise redraw the ship on the scanner, now that it's been moved
.MV5 LDA INWK+31 \ Fetch the ship's exploding/killed state from byte #31 AND #%10100000 \ If we are exploding or removing this ship then jump to BNE MVD1 \ MVD1 to remove it from the scanner permanently LDA INWK+31 \ Set bit 4 to keep the ship visible on the scanner ORA #%00010000 STA INWK+31 JMP SCAN \ Display the ship on the scanner, returning from the \ subroutine using a tail call .MVD1 LDA INWK+31 \ Clear bit 4 to hide the ship on the scanner AND #%11101111 STA INWK+31 RTS \ Return from the subroutine
Name: MVT1 [Show more] Type: Subroutine Category: Moving Summary: Calculate (x_sign x_hi x_lo) = (x_sign x_hi x_lo) + (A R)
Context: See this subroutine on its own page References: This subroutine is called as follows: * MVEIT (Part 6 of 9) calls MVT1 * SFS2 calls MVT1 * MVEIT (Part 3 of 9) calls via MVT1-2

Add the signed delta (A R) to a ship's coordinate, along the axis given in X. Mathematically speaking, this routine translates the ship along a single axis by a signed delta. Taking the example of X = 0, the x-axis, it does the following: (x_sign x_hi x_lo) = (x_sign x_hi x_lo) + (A R) (In practice, MVT1 is only ever called directly with A = 0 or 128, otherwise it is always called via MVT-2, which clears A apart from the sign bit. The routine is written to cope with a non-zero delta_hi, so it supports a full 16-bit delta, but it appears that delta_hi is only ever used to hold the sign of the delta.) The comments below assume we are adding delta to the x-axis, though the axis is determined by the value of X.
Arguments: (A R) The signed delta, so A = delta_hi and R = delta_lo X Determines which coordinate axis of INWK to change: * X = 0 adds the delta to (x_lo, x_hi, x_sign) * X = 3 adds the delta to (y_lo, y_hi, y_sign) * X = 6 adds the delta to (z_lo, z_hi, z_sign)
Other entry points: MVT1-2 Clear bits 0-6 of A before entering MVT1
AND #%10000000 \ Clear bits 0-6 of A .MVT1 ASL A \ Set the C flag to the sign bit of the delta, leaving \ delta_hi << 1 in A STA S \ Set S = delta_hi << 1 \ \ This also clears bit 0 of S LDA #0 \ Set T = just the sign bit of delta (in bit 7) ROR A STA T LSR S \ Set S = delta_hi >> 1 \ = |delta_hi| \ \ This also clear the C flag, as we know that bit 0 of \ S was clear before the LSR EOR INWK+2,X \ If T EOR x_sign has bit 7 set, then x_sign and delta BMI MV10 \ have different signs, so jump to MV10 \ At this point, we know x_sign and delta have the same \ sign, that sign is in T, and S contains |delta_hi|, \ so now we want to do: \ \ (x_sign x_hi x_lo) = (x_sign x_hi x_lo) + (S R) \ \ and then set the sign of the result to the same sign \ as x_sign and delta LDA R \ First we add the low bytes, so: ADC INWK,X \ STA INWK,X \ x_lo = x_lo + R LDA S \ Then we add the high bytes: ADC INWK+1,X \ STA INWK+1,X \ x_hi = x_hi + S LDA INWK+2,X \ And finally we add any carry into x_sign, and if the ADC #0 \ sign of x_sign and delta in T is negative, make sure ORA T \ the result is negative (by OR'ing with T) STA INWK+2,X RTS \ Return from the subroutine .MV10 \ If we get here, we know x_sign and delta have \ different signs, with delta's sign in T, and \ |delta_hi| in S, so now we want to do: \ \ (x_sign x_hi x_lo) = (x_sign x_hi x_lo) - (S R) \ \ and then set the sign of the result according to \ the signs of x_sign and delta LDA INWK,X \ First we subtract the low bytes, so: SEC \ SBC R \ x_lo = x_lo - R STA INWK,X LDA INWK+1,X \ Then we subtract the high bytes: SBC S \ STA INWK+1,X \ x_hi = x_hi - S LDA INWK+2,X \ And finally we subtract any borrow from bits 0-6 of AND #%01111111 \ x_sign, and give the result the opposite sign bit to T SBC #0 \ (i.e. give it the sign of the original x_sign) ORA #%10000000 EOR T STA INWK+2,X BCS MV11 \ If the C flag is set by the above SBC, then our sum \ above didn't underflow and is correct - to put it \ another way, (x_sign x_hi x_lo) >= (S R) so the result \ should indeed have the same sign as x_sign, so jump to \ MV11 to return from the subroutine \ Otherwise our subtraction underflowed because \ (x_sign x_hi x_lo) < (S R), so we now need to flip the \ subtraction around by using two's complement to this: \ \ (S R) - (x_sign x_hi x_lo) \ \ and then we need to give the result the same sign as \ (S R), the delta, as that's the dominant figure in the \ sum LDA #1 \ First we subtract the low bytes, so: SBC INWK,X \ STA INWK,X \ x_lo = 1 - x_lo LDA #0 \ Then we subtract the high bytes: SBC INWK+1,X \ STA INWK+1,X \ x_hi = 0 - x_hi LDA #0 \ And then we subtract the sign bytes: SBC INWK+2,X \ \ x_sign = 0 - x_sign AND #%01111111 \ Finally, we set the sign bit to the sign in T, the ORA T \ sign of the original delta, as the delta is the STA INWK+2,X \ dominant figure in the sum .MV11 RTS \ Return from the subroutine
Name: MVS4 [Show more] Type: Subroutine Category: Moving Summary: Apply pitch and roll to an orientation vector Deep dive: Orientation vectors Pitching and rolling
Context: See this subroutine on its own page References: This subroutine is called as follows: * MVEIT (Part 7 of 9) calls MVS4

Apply pitch and roll angles alpha and beta to the orientation vector in Y. Specifically, this routine rotates a point (x, y, z) around the origin by pitch alpha and roll beta, using the small angle approximation to make the maths easier, and incorporating the Minsky circle algorithm to make the rotation more stable (though more elliptic). If that paragraph makes sense to you, then you should probably be writing this commentary! For the rest of us, there's a detailed explanation of all this in the deep dive on "Pitching and rolling".
Arguments: Y Determines which of the INWK orientation vectors to transform: * Y = 9 rotates nosev: (nosev_x, nosev_y, nosev_z) * Y = 15 rotates roofv: (roofv_x, roofv_y, roofv_z) * Y = 21 rotates sidev: (sidev_x, sidev_y, sidev_z)
.MVS4 LDA ALPHA \ Set Q = alpha (the roll angle to rotate through) STA Q LDX INWK+2,Y \ Set (S R) = nosev_y STX R LDX INWK+3,Y STX S LDX INWK,Y \ These instructions have no effect as MAD overwrites STX P \ X and P when called, but they set X = P = nosev_x_lo LDA INWK+1,Y \ Set A = -nosev_x_hi EOR #%10000000 JSR MAD \ Set (A X) = Q * A + (S R) STA INWK+3,Y \ = alpha * -nosev_x_hi + nosev_y STX INWK+2,Y \ \ and store (A X) in nosev_y, so this does: \ \ nosev_y = nosev_y - alpha * nosev_x_hi STX P \ This instruction has no effect as MAD overwrites P, \ but it sets P = nosev_y_lo LDX INWK,Y \ Set (S R) = nosev_x STX R LDX INWK+1,Y STX S LDA INWK+3,Y \ Set A = nosev_y_hi JSR MAD \ Set (A X) = Q * A + (S R) STA INWK+1,Y \ = alpha * nosev_y_hi + nosev_x STX INWK,Y \ \ and store (A X) in nosev_x, so this does: \ \ nosev_x = nosev_x + alpha * nosev_y_hi STX P \ This instruction has no effect as MAD overwrites P, \ but it sets P = nosev_x_lo LDA BETA \ Set Q = beta (the pitch angle to rotate through) STA Q LDX INWK+2,Y \ Set (S R) = nosev_y STX R LDX INWK+3,Y STX S LDX INWK+4,Y STX P \ This instruction has no effect as MAD overwrites P, \ but it sets P = nosev_y LDA INWK+5,Y \ Set A = -nosev_z_hi EOR #%10000000 JSR MAD \ Set (A X) = Q * A + (S R) STA INWK+3,Y \ = beta * -nosev_z_hi + nosev_y STX INWK+2,Y \ \ and store (A X) in nosev_y, so this does: \ \ nosev_y = nosev_y - beta * nosev_z_hi STX P \ This instruction has no effect as MAD overwrites P, \ but it sets P = nosev_y_lo LDX INWK+4,Y \ Set (S R) = nosev_z STX R LDX INWK+5,Y STX S LDA INWK+3,Y \ Set A = nosev_y_hi JSR MAD \ Set (A X) = Q * A + (S R) STA INWK+5,Y \ = beta * nosev_y_hi + nosev_z STX INWK+4,Y \ \ and store (A X) in nosev_z, so this does: \ \ nosev_z = nosev_z + beta * nosev_y_hi RTS \ Return from the subroutine
Name: MVT6 [Show more] Type: Subroutine Category: Moving Summary: Calculate (A P+2 P+1) = (x_sign x_hi x_lo) + (A P+2 P+1)
Context: See this subroutine on its own page References: This subroutine is called as follows: * MVEIT (Part 5 of 9) calls MVT6

Do the following calculation, for the coordinate given by X (so this is what it does for the x-coordinate): (A P+2 P+1) = (x_sign x_hi x_lo) + (A P+2 P+1) A is a sign bit and is not included in the calculation, but bits 0-6 of A are preserved. Bit 7 is set to the sign of the result.
Arguments: A The sign of P(2 1) in bit 7 P(2 1) The 16-bit value we want to add the coordinate to X The coordinate to add, as follows: * If X = 0, add to (x_sign x_hi x_lo) * If X = 3, add to (y_sign y_hi y_lo) * If X = 6, add to (z_sign z_hi z_lo)
Returns: A The sign of the result (in bit 7)
.MVT6 TAY \ Store argument A into Y, for later use EOR INWK+2,X \ Set A = A EOR x_sign BMI MV50 \ If the sign is negative, i.e. A and x_sign have \ different signs, jump to MV50 \ The signs are the same, so we can add the two \ arguments and keep the sign to get the result LDA P+1 \ First we add the low bytes: CLC \ ADC INWK,X \ P+1 = P+1 + x_lo STA P+1 LDA P+2 \ And then the high bytes: ADC INWK+1,X \ STA P+2 \ P+2 = P+2 + x_hi TYA \ Restore the original A argument that we stored earlier \ so that we keep the original sign RTS \ Return from the subroutine .MV50 LDA INWK,X \ First we subtract the low bytes: SEC \ SBC P+1 \ P+1 = x_lo - P+1 STA P+1 LDA INWK+1,X \ And then the high bytes: SBC P+2 \ STA P+2 \ P+2 = x_hi - P+2 BCC MV51 \ If the last subtraction underflowed, then the C flag \ will be clear and x_hi < P+2, so jump to MV51 to \ negate the result TYA \ Restore the original A argument that we stored earlier EOR #%10000000 \ but flip bit 7, which flips the sign. We do this \ because x_hi >= P+2 so we want the result to have the \ same sign as x_hi (as it's the dominant side in this \ calculation). The sign of x_hi is x_sign, and x_sign \ has the opposite sign to A, so we flip the sign in A \ to return the correct result RTS \ Return from the subroutine .MV51 LDA #1 \ Our subtraction underflowed, so we negate the result SBC P+1 \ using two's complement, first with the low byte: STA P+1 \ \ P+1 = 1 - P+1 LDA #0 \ And then the high byte: SBC P+2 \ STA P+2 \ P+2 = 0 - P+2 TYA \ Restore the original A argument that we stored earlier \ as this is the correct sign for the result. This is \ because x_hi < P+2, so we want to return the same sign \ as P+2, the dominant side RTS \ Return from the subroutine
Name: MV40 [Show more] Type: Subroutine Category: Moving Summary: Rotate the planet or sun's location in space by the amount of pitch and roll of our ship
Context: See this subroutine on its own page Variations: See code variations for this subroutine in the different versions References: This subroutine is called as follows: * MVEIT (Part 2 of 9) calls MV40

We implement this using the same equations as in part 5 of MVEIT, where we rotated the current ship's location by our pitch and roll. Specifically, the calculation is as follows: 1. K2 = y - alpha * x 2. z = z + beta * K2 3. y = K2 - beta * z 4. x = x + alpha * y See the deep dive on "Rotating the universe" for more details on the above.
.MV40 LDA ALPHA \ Set Q = -ALPHA, so Q contains the angle we want to EOR #%10000000 \ roll the planet through (i.e. in the opposite STA Q \ direction to our ship's roll angle alpha) LDA INWK \ Set P(1 0) = (x_hi x_lo) STA P LDA INWK+1 STA P+1 LDA INWK+2 \ Set A = x_sign JSR MULT3 \ Set K(3 2 1 0) = (A P+1 P) * Q \ \ which also means: \ \ K(3 2 1) = (A P+1 P) * Q / 256 \ = x * -alpha / 256 \ = - alpha * x / 256 LDX #3 \ Set K(3 2 1) = (y_sign y_hi y_lo) + K(3 2 1) JSR MVT3 \ = y - alpha * x / 256 LDA K+1 \ Set K2(2 1) = P(1 0) = K(2 1) STA K2+1 STA P LDA K+2 \ Set K2+2 = K+2 STA K2+2 STA P+1 \ Set P+1 = K+2 LDA BETA \ Set Q = beta, the pitch angle of our ship STA Q LDA K+3 \ Set K+3 to K2+3, so now we have result 1 above: STA K2+3 \ \ K2(3 2 1) = K(3 2 1) \ = y - alpha * x / 256 \ We also have: \ \ A = K+3 \ \ P(1 0) = K(2 1) \ \ so combined, these mean: \ \ (A P+1 P) = K(3 2 1) \ = K2(3 2 1) JSR MULT3 \ Set K(3 2 1 0) = (A P+1 P) * Q \ \ which also means: \ \ K(3 2 1) = (A P+1 P) * Q / 256 \ = K2(3 2 1) * beta / 256 \ = beta * K2 / 256 LDX #6 \ K(3 2 1) = (z_sign z_hi z_lo) + K(3 2 1) JSR MVT3 \ = z + beta * K2 / 256 LDA K+1 \ Set P = K+1 STA P STA INWK+6 \ Set z_lo = K+1 LDA K+2 \ Set P+1 = K+2 STA P+1 STA INWK+7 \ Set z_hi = K+2 LDA K+3 \ Set A = z_sign = K+3, so now we have: STA INWK+8 \ \ (z_sign z_hi z_lo) = K(3 2 1) \ = z + beta * K2 / 256 \ So we now have result 2 above: \ \ z = z + beta * K2 EOR #%10000000 \ Flip the sign bit of A to give A = -z_sign JSR MULT3 \ Set K(3 2 1 0) = (A P+1 P) * Q \ = (-z_sign z_hi z_lo) * beta \ = -z * beta LDA K+3 \ Set T to the sign bit of K(3 2 1 0), i.e. to the sign AND #%10000000 \ bit of -z * beta STA T EOR K2+3 \ If K2(3 2 1 0) has a different sign to K(3 2 1 0), BMI MV1 \ then EOR'ing them will produce a 1 in bit 7, so jump \ to MV1 to take this into account \ If we get here, K and K2 have the same sign, so we can \ add them together to get the result we're after, and \ then set the sign afterwards LDA K \ We now do the following sum: CLC \ ADC K2 \ (A y_hi y_lo -) = K(3 2 1 0) + K2(3 2 1 0) \ \ starting with the low bytes (which we don't keep) \ \ The CLC has no effect because MULT3 clears the C \ flag, so this instruction could be removed (as it is \ in the cassette version, for example) LDA K+1 \ We then do the middle bytes, which go into y_lo ADC K2+1 STA INWK+3 LDA K+2 \ And then the high bytes, which go into y_hi ADC K2+2 STA INWK+4 LDA K+3 \ And then the sign bytes into A, so overall we have the ADC K2+3 \ following, if we drop the low bytes from the result: \ \ (A y_hi y_lo) = (K + K2) / 256 JMP MV2 \ Jump to MV2 to skip the calculation for when K and K2 \ have different signs .MV1 LDA K \ If we get here then K2 and K have different signs, so SEC \ instead of adding, we need to subtract to get the SBC K2 \ result we want, like this: \ \ (A y_hi y_lo -) = K(3 2 1 0) - K2(3 2 1 0) \ \ starting with the low bytes (which we don't keep) LDA K+1 \ We then do the middle bytes, which go into y_lo SBC K2+1 STA INWK+3 LDA K+2 \ And then the high bytes, which go into y_hi SBC K2+2 STA INWK+4 LDA K2+3 \ Now for the sign bytes, so first we extract the sign AND #%01111111 \ byte from K2 without the sign bit, so P = |K2+3| STA P LDA K+3 \ And then we extract the sign byte from K without the AND #%01111111 \ sign bit, so A = |K+3| SBC P \ And finally we subtract the sign bytes, so P = A - P STA P \ By now we have the following, if we drop the low bytes \ from the result: \ \ (A y_hi y_lo) = (K - K2) / 256 \ \ so now we just need to make sure the sign of the \ result is correct BCS MV2 \ If the C flag is set, then the last subtraction above \ didn't underflow and the result is correct, so jump to \ MV2 as we are done with this particular stage LDA #1 \ Otherwise the subtraction above underflowed, as K2 is SBC INWK+3 \ the dominant part of the subtraction, so we need to STA INWK+3 \ negate the result using two's complement, starting \ with the low bytes: \ \ y_lo = 1 - y_lo LDA #0 \ And then the high bytes: SBC INWK+4 \ STA INWK+4 \ y_hi = 0 - y_hi LDA #0 \ And finally the sign bytes: SBC P \ \ A = 0 - P ORA #%10000000 \ We now force the sign bit to be negative, so that the \ final result below gets the opposite sign to K, which \ we want as K2 is the dominant part of the sum .MV2 EOR T \ T contains the sign bit of K, so if K is negative, \ this flips the sign of A STA INWK+5 \ Store A in y_sign \ So we now have result 3 above: \ \ y = K2 + K \ = K2 - beta * z LDA ALPHA \ Set A = alpha STA Q LDA INWK+3 \ Set P(1 0) = (y_hi y_lo) STA P LDA INWK+4 STA P+1 LDA INWK+5 \ Set A = y_sign JSR MULT3 \ Set K(3 2 1 0) = (A P+1 P) * Q \ = (y_sign y_hi y_lo) * alpha \ = y * alpha LDX #0 \ Set K(3 2 1) = (x_sign x_hi x_lo) + K(3 2 1) JSR MVT3 \ = x + y * alpha / 256 LDA K+1 \ Set (x_sign x_hi x_lo) = K(3 2 1) STA INWK \ = x + y * alpha / 256 LDA K+2 STA INWK+1 LDA K+3 STA INWK+2 \ So we now have result 4 above: \ \ x = x + y * alpha JMP MV45 \ We have now finished rotating the planet or sun by \ our pitch and roll, so jump back into the MVEIT \ routine at MV45 to apply all the other movements
Name: Checksum [Show more] Type: Subroutine Category: Copy protection Summary: Checksum the code from &1000 to &9FFF and check against S%-1
Context: See this subroutine on its own page References: This subroutine is called as follows: * S% calls Checksum

In the original source, the checksum byte at S%-1 is set by the first call to ZP in the Big Code File, though in the BeebAsm version this is populated by elite-checksum.py. The original 6502 assembly language version of the ZP routine can be found in the elite-checksum.asm file.
.Checksum SEC \ Set the C flag, so it gets included in the checksum LDY #0 \ Set Y = 0, to act as a byte counter STY V \ Set V = 0 LDX #&10 \ Set X = &10, so we start with (X Y) = &1000 LDA (SC) \ This has no effect, as A is overwritten by the next \ instruction TXA \ Set A = &10 .CHKLoop STX V+1 \ Set V(1 0) = (X 0) STY T \ Set T = Y ADC (V),Y \ Set A = A + C + contents of (V(1 0) + Y) \ = A + C + contents of ((X 0) + Y) \ = A + C + contents of (X Y) EOR T \ Set A = A EOR Y SBC V+1 \ Set A = A - (1 - C) - X DEY \ Decrement the loop counter to process the next byte BNE CHKLoop \ Loop back until we have done the whole page INX \ Increment the page counter to point to the next page CPX #&A0 \ Loop back to do the next page until X = &A0, when BCC CHKLoop \ (X Y) = &A000 CMP S%-1 \ Compare the calculated checksum in A with the checksum \ stored in S%-1 IF _REMOVE_CHECKSUMS NOP \ If we have disabled checksums, then ignore the result NOP \ of the comparison and return from the subroutine ELSE BNE Checksum \ If the checksum we just calculated does not match \ the value in location S%-1, jump to Checksum to enter \ an infinite loop, which crashes the game ENDIF RTS \ Return from the subroutine
Name: PLUT [Show more] Type: Subroutine Category: Flight Summary: Flip the coordinate axes for the four different views Deep dive: Flipping axes between space views
Context: See this subroutine on its own page Variations: See code variations for this subroutine in the different versions References: This subroutine is called as follows: * Main flight loop (Part 11 of 16) calls PLUT

This routine flips the relevant geometric axes in INWK depending on which view we are looking through (front, rear, left, right).
.PLUT LDX VIEW \ Load the current view into X: \ \ 0 = front \ 1 = rear \ 2 = left \ 3 = right BEQ PU2-1 \ If the current view is the front view, return from the \ subroutine (PU2-1 contains an RTS), as the geometry in \ INWK is already correct .PU1 DEX \ Decrement the view, so now: \ \ 0 = rear \ 1 = left \ 2 = right BNE PU2 \ If the current view is left or right, jump to PU2, \ otherwise this is the rear view, so continue on LDA INWK+2 \ Flip the sign of x_sign EOR #%10000000 STA INWK+2 LDA INWK+8 \ Flip the sign of z_sign EOR #%10000000 STA INWK+8 LDA INWK+10 \ Flip the sign of nosev_x_hi EOR #%10000000 STA INWK+10 LDA INWK+14 \ Flip the sign of nosev_z_hi EOR #%10000000 STA INWK+14 LDA INWK+16 \ Flip the sign of roofv_x_hi EOR #%10000000 STA INWK+16 LDA INWK+20 \ Flip the sign of roofv_z_hi EOR #%10000000 STA INWK+20 LDA INWK+22 \ Flip the sign of sidev_x_hi EOR #%10000000 STA INWK+22 LDA INWK+26 \ Flip the sign of roofv_z_hi EOR #%10000000 STA INWK+26 RTS \ Return from the subroutine .PU2 \ We enter this with X set to the view, as follows: \ \ 1 = left \ 2 = right LDA #0 \ Set RAT2 = 0 (left view) or -1 (right view) CPX #2 ROR A STA RAT2 EOR #%10000000 \ Set RAT = -1 (left view) or 0 (right view) STA RAT LDA INWK \ Swap x_lo and z_lo LDX INWK+6 STA INWK+6 STX INWK LDA INWK+1 \ Swap x_hi and z_hi LDX INWK+7 STA INWK+7 STX INWK+1 LDA INWK+2 \ Swap x_sign and z_sign EOR RAT \ If left view, flip sign of new z_sign TAX \ If right view, flip sign of new x_sign LDA INWK+8 EOR RAT2 STA INWK+2 STX INWK+8 LDY #9 \ Swap nosev_x_lo and nosev_z_lo JSR PUS1 \ Swap nosev_x_hi and nosev_z_hi \ If left view, flip sign of new nosev_z_hi \ If right view, flip sign of new nosev_x_hi LDY #15 \ Swap roofv_x_lo and roofv_z_lo JSR PUS1 \ Swap roofv_x_hi and roofv_z_hi \ If left view, flip sign of new roofv_z_hi \ If right view, flip sign of new roofv_x_hi LDY #21 \ Swap sidev_x_lo and sidev_z_lo \ Swap sidev_x_hi and sidev_z_hi \ If left view, flip sign of new sidev_z_hi \ If right view, flip sign of new sidev_x_hi .PUS1 LDA INWK,Y \ Swap the low x and z bytes for the vector in Y: LDX INWK+4,Y \ STA INWK+4,Y \ * For Y = 9 swap nosev_x_lo and nosev_z_lo STX INWK,Y \ * For Y = 15 swap roofv_x_lo and roofv_z_lo \ * For Y = 21 swap sidev_x_lo and sidev_z_lo LDA INWK+1,Y \ Swap the high x and z bytes for the offset in Y: EOR RAT \ TAX \ * If left view, flip sign of new z-coordinate LDA INWK+5,Y \ * If right view, flip sign of new x-coordinate EOR RAT2 STA INWK+1,Y STX INWK+5,Y \ Fall through into LOOK1 to return from the subroutine
Name: LOOK1 [Show more] Type: Subroutine Category: Flight Summary: Initialise the space view
Context: See this subroutine on its own page Variations: See code variations for this subroutine in the different versions References: This subroutine is called as follows: * MJP calls LOOK1 * TT102 calls LOOK1 * TT110 calls LOOK1 * WARP calls LOOK1 * SIGHT calls via LO2

Initialise the space view, with the direction of view given in X. This clears the upper screen and draws the laser crosshairs, if the view in X has lasers fitted. It also wipes all the ships from the scanner, so we can recalculate ship positions for the new view (they get put back in the main flight loop).
Arguments: X The space view to set: * 0 = front * 1 = rear * 2 = left * 3 = right
Other entry points: LO2 Contains an RTS
.LO2 RTS \ Return from the subroutine .LQ STX VIEW \ Set the current space view to X JSR TT66 \ Clear the top part of the screen, draw a white border, \ and set the current view type in QQ11 to 0 (space \ view) JSR SIGHT \ Draw the laser crosshairs JMP NWSTARS \ Set up a new stardust field and return from the \ subroutine using a tail call .LOOK1 LDA #0 \ Set A = 0, the type number of a space view JSR DOVDU19 \ Send a #SETVDU19 0 command to the I/O processor to \ switch to the mode 1 palette for the space view, \ which is yellow (colour 1), red (colour 2) and cyan \ (colour 3) LDY QQ11 \ If the current view is not a space view, jump up to LQ BNE LQ \ to set up a new space view CPX VIEW \ If the current view is already of type X, jump to LO2 BEQ LO2 \ to return from the subroutine (as LO2 contains an RTS) STX VIEW \ Change the current space view to X JSR TT66 \ Clear the top part of the screen, draw a white border, \ and set the current view type in QQ11 to 0 (space \ view) JSR FLIP \ Swap the x- and y-coordinates of all the stardust \ particles and redraw the stardust field JSR WPSHPS \ Wipe all the ships from the scanner and mark them all \ as not being shown on-screen \ And fall through into SIGHT to draw the laser \ crosshairs
Name: SIGHT [Show more] Type: Subroutine Category: Flight Summary: Draw the laser crosshairs
Context: See this subroutine on its own page Variations: See code variations for this subroutine in the different versions References: This subroutine is called as follows: * LOOK1 calls SIGHT
.SIGHT LDY VIEW \ Fetch the laser power for our new view LDA LASER,Y BEQ LO2 \ If it is zero (i.e. there is no laser fitted to this \ view), jump to LO2 to return from the subroutine (as \ LO2 contains an RTS) LDA #YELLOW \ Send a #SETCOL YELLOW command to the I/O processor to JSR DOCOL \ switch to colour 1, which is yellow in the space view LDA #128 \ Set QQ19 to the x-coordinate of the centre of the STA QQ19 \ screen LDA #Y-24 \ Set QQ19+1 to the y-coordinate of the centre of the STA QQ19+1 \ screen, minus 24 (because TT15 will add 24 to the \ coordinate when it draws the crosshairs) LDA #20 \ Set QQ19+2 to size 20 for the crosshairs size STA QQ19+2 JSR TT15b \ Call TT15b to draw crosshairs of size 20 just to the \ left of the middle of the screen, in the current \ colour (yellow) LDA #10 \ Set QQ19+2 to size 10 for the crosshairs size STA QQ19+2 JMP TT15b \ Call TT15b to draw crosshairs of size 10 at the same \ location, which will remove the centre part from the \ laser crosshairs, leaving a gap in the middle, and \ return from the subroutine using a tail call
Name: TT66 [Show more] Type: Subroutine Category: Drawing the screen Summary: Clear the screen and set the current view type
Context: See this subroutine on its own page Variations: See code variations for this subroutine in the different versions References: This subroutine is called as follows: * BRIEF calls TT66 * DEATH calls TT66 * DEMON calls TT66 * HALL calls TT66 * LOOK1 calls TT66 * MJP calls TT66 * MT9 calls TT66 * PAUSE calls TT66 * qv calls TT66 * TITLE calls TT66 * TRADEMODE calls TT66 * TT18 calls TT66 * TT22 calls TT66 * TT23 calls TT66

Clear the top part of the screen, draw a white border, and set the current view type in QQ11 to A.
Arguments: A The type of the new current view (see QQ11 for a list of view types)
.TT66 STA QQ11 \ Set the current view type in QQ11 to A \ Fall through into TTX66 to clear the screen and draw a \ white border
Name: TTX66 [Show more] Type: Subroutine Category: Drawing the screen Summary: Send control code 11 to the I/O processor to clear the top part of the screen and draw a white border
Context: See this subroutine on its own page Variations: See code variations for this subroutine in the different versions References: This subroutine is called as follows: * HFS2 calls TTX66 * TT18 calls TTX66 * DEATH calls via BOX

Clear the top part of the screen (the space view) and draw a white border along the top and sides.
Other entry points: BOX Just draw the border and (if this is a space view) the view name. This can be used to remove the border and view name, as it is drawn using EOR logic
.TTX66 JSR MT2 \ Switch to Sentence Case when printing extended tokens JSR PBZE \ Reset the pixel buffer size in PBUP JSR HBZE \ Reset the horizontal line buffer size in HBUP STZ LBUP \ Reset the line buffer size at LBUP STZ LSP \ Reset the ball line heap pointer at LSP LDA #%10000000 \ Set bit 7 of QQ17 to switch to Sentence Case STA QQ17 STA DTW2 \ Set bit 7 of DTW2 to indicate we are not currently \ printing a word JSR FLFLLS \ Call FLFLLS to reset the LSO block LDA #YELLOW \ Send a #SETCOL YELLOW command to the I/O processor to JSR DOCOL \ switch to colour 2, which is yellow STZ LAS2 \ Set LAS2 = 0 to stop any laser pulsing STZ DLY \ Set the delay in DLY to 0, to indicate that we are \ no longer showing an in-flight message, so any new \ in-flight messages will be shown instantly STZ de \ Clear de, the flag that appends " DESTROYED" to the \ end of the next text token, so that it doesn't LDA #11 \ Send control code 11 to OSWRCH, to instruct the I/O JSR OSWRCH \ processor to clear the top part of the screen LDX QQ22+1 \ Fetch into X the number that's shown on-screen during \ the hyperspace countdown BEQ OLDBOX \ If the counter is zero then we are not counting down \ to hyperspace, so jump to OLDBOX to skip the next \ instruction JSR ee3 \ Print the 8-bit number in X at text location (0, 1), \ i.e. print the hyperspace countdown in the top-left \ corner .OLDBOX LDA #1 \ Move the text cursor to column 1 JSR DOYC LDA QQ11 \ If this is not a space view, jump to tt66 to skip BNE tt66 \ displaying the view name LDA #11 \ Move the text cursor to row 11 JSR DOXC LDA #CYAN \ Send a #SETCOL CYAN command to the I/O processor to JSR DOCOL \ switch to colour 3, which is cyan in the space view LDA VIEW \ Load the current view into A: \ \ 0 = front \ 1 = rear \ 2 = left \ 3 = right ORA #&60 \ OR with &60 so we get a value of &60 to &63 (96 to 99) JSR TT27 \ Print recursive token 96 to 99, which will be in the \ range "FRONT" to "RIGHT" JSR TT162 \ Print a space LDA #175 \ Print recursive token 15 ("VIEW ") JSR TT27 .tt66 LDA #1 \ Move the text cursor to column 1, row 1 JSR DOXC JSR DOYC LDX #0 \ Set QQ17 = 0 to switch to ALL CAPS STX QQ17 RTS \ Return from the subroutine .BOX LDA #YELLOW \ Send a #SETCOL YELLOW command to the I/O processor to JSR DOCOL \ switch to colour 2, which is yellow LDX #0 \ Set QQ17 = 0 to switch to ALL CAPS STX QQ17 STX X1 \ Set (X1, Y1) to (0, 0) STX Y1 STX Y2 \ Set Y2 = 0 DEX \ Set X2 = 255 STX X2 JSR LL30 \ Draw a line from (X1, Y1) to (X2, Y2), so that's \ (0, 0) to (255, 0), along the very top of the screen LDA #2 \ Set X1 = X2 = 2 STA X1 STA X2 JSR BOS2 \ Call BOS2 below, which will call BOS1 twice, and then \ fall through into BOS2 again, so we effectively do \ BOS1 four times, decrementing X1 and X2 each time \ before calling LOIN, so this whole loop-within-a-loop \ mind-bender ends up drawing these four lines: \ \ (1, 0) to (1, 191) \ (0, 0) to (0, 191) \ (255, 0) to (255, 191) \ (254, 0) to (254, 191) \ \ So that's a 2-pixel wide vertical border along the \ left edge of the upper part of the screen, and a \ 2-pixel wide vertical border along the right edge .BOS2 JSR BOS1 \ Call BOS1 below and then fall through into it, which \ ends up running BOS1 twice. This is all part of the \ loop-the-loop border-drawing mind-bender explained \ above .BOS1 LDA #0 \ Set Y1 = 0 STA Y1 LDA #2*Y-1 \ Set Y2 = 2 * #Y - 1. The constant #Y is 96, the STA Y2 \ y-coordinate of the mid-point of the space view, so \ this sets Y2 to 191, the y-coordinate of the bottom \ pixel row of the space view DEC X1 \ Decrement X1 and X2 DEC X2 JMP LL30 \ Draw a line from (X1, Y1) to (X2, Y2), and return from \ the subroutine using a tail call
Name: DELAY [Show more] Type: Subroutine Category: Utility routines Summary: Wait for a specified time, in 1/50s of a second
Context: See this subroutine on its own page Variations: See code variations for this subroutine in the different versions References: This subroutine is called as follows: * BRIS calls DELAY * DEMON calls DELAY * DKS3 calls DELAY * dn2 calls DELAY * DOENTRY calls DELAY * Main game loop (Part 5 of 6) calls DELAY * MT26 calls DELAY * TT217 calls DELAY

Wait for the number of vertical syncs given in Y, so this effectively waits for Y/50 of a second (as the vertical sync occurs 50 times a second).
Arguments: Y The number of vertical sync events to wait for
.DELAY JSR WSCAN \ Call WSCAN to wait for the vertical sync, so the whole \ screen gets drawn DEY \ Decrement the counter in Y BNE DELAY \ If Y isn't yet at zero, jump back to DELAY to wait \ for another vertical sync RTS \ Return from the subroutine
Name: CLYNS [Show more] Type: Subroutine Category: Drawing the screen Summary: Clear the bottom three text rows of the mode 1 screen by sending a #clyns command to the I/O processor
Context: See this subroutine on its own page Variations: See code variations for this subroutine in the different versions References: This subroutine is called as follows: * dockEd calls CLYNS * EQSHP calls CLYNS * hm calls CLYNS * JMTB calls CLYNS * qv calls CLYNS * TITLE calls CLYNS * TT219 calls CLYNS * SCAN calls via SC5

Returns: A A is set to 0 Y Y is set to 0
Other entry points: SC5 Contains an RTS
.CLYNS LDA #%11111111 \ Set DTW2 = %11111111 to denote that we are not STA DTW2 \ currently printing a word LDA #%10000000 \ Set bit 7 of QQ17 to switch standard tokens to STA QQ17 \ Sentence Case LDA #21 \ Move the text cursor to column 1, row 21 STA YC LDA #1 STA XC LDA #clyns \ Send a #clyns command to the I/O processor to clear JSR OSWRCH \ the bottom three text rows of the top part of the JSR OSWRCH \ screen LDA #0 \ Set A = 0 TAY \ Set Y = 0 .SC5 RTS \ Return from the subroutine
Name: SCANpars [Show more] Type: Variable Category: Dashboard Summary: The scanner buffer to send with the #onescan command
Context: See this variable on its own page References: This variable is used as follows: * SCAN uses SCANpars * SCAN calls via SCANflg * SCAN calls via SCANlen * SCAN calls via SCANcol * SCAN calls via SCANx1 * SCAN calls via SCANy1

Other entry points: SCANflg The sign of the stick height (in bit 7) SCANlen The stick height for the ship on the scanner SCANcol The colour of the ship on the scanner SCANx1 The screen x-coordinate of the dot on the scanner SCANy1 The screen y-coordinate of the dot on the scanner
.SCANpars EQUB 7 \ The number of bytes to transmit with this command EQUB 0 \ The number of bytes to receive with this command .SCANflg EQUB 0 \ The sign of the stick height (in bit 7) .SCANlen EQUB 0 \ The stick height for this ship on the scanner .SCANcol EQUB 0 \ The colour of the ship on the scanner .SCANx1 EQUB 0 \ The screen x-coordinate of the dot on the scanner .SCANy1 EQUB 0 \ The screen y-coordinate of the dot on the scanner
Name: SCAN [Show more] Type: Subroutine Category: Dashboard Summary: Display the current ship on the scanner Deep dive: The 3D scanner
Context: See this subroutine on its own page Variations: See code variations for this subroutine in the different versions References: This subroutine is called as follows: * DEMON calls SCAN * ESCAPE calls SCAN * Main flight loop (Part 11 of 16) calls SCAN * MVEIT (Part 2 of 9) calls SCAN * MVEIT (Part 9 of 9) calls SCAN * WPSHPS calls SCAN

This is used both to display a ship on the scanner, and to erase it again.
Arguments: INWK The ship's data block
.SCAN LDA INWK+31 \ Fetch the ship's scanner flag from byte #31 AND #%00010000 \ If bit 4 is clear then the ship should not be shown BEQ SC5 \ on the scanner, so return from the subroutine (as SC5 \ contains an RTS) LDX TYPE \ Fetch the ship's type from TYPE into X BMI SC5 \ If this is the planet or the sun, then the type will \ have bit 7 set and we don't want to display it on the \ scanner, so return from the subroutine (as SC5 \ contains an RTS) LDA scacol,X \ Set A to the scanner colour for this ship type from \ the X-th entry in the scacol table STA SCANcol \ Store the scanner colour in SCANcol so it can be sent \ to the I/O processor with the #onescan command LDA INWK+1 \ If any of x_hi, y_hi and z_hi have a 1 in bit 6 or 7, ORA INWK+4 \ then the ship is too far away to be shown on the ORA INWK+7 \ scanner, so return from the subroutine (as SC5 AND #%11000000 \ contains an RTS) BNE SC5 \ If we get here, we know x_hi, y_hi and z_hi are all \ 63 (%00111111) or less \ Now, we convert the x_hi coordinate of the ship into \ the screen x-coordinate of the dot on the scanner, \ using the following (see the deep dive on "The 3D \ scanner" for an explanation): \ \ X1 = 123 + (x_sign x_hi) LDA INWK+1 \ Set A = x_hi CLC \ Clear the C flag so we can do addition below LDX INWK+2 \ Set X = x_sign BPL SC2 \ If x_sign is positive, skip the following EOR #%11111111 \ x_sign is negative, so flip the bits in A and add 1 ADC #1 \ to make it a negative number (bit 7 will now be set \ as we confirmed above that bits 6 and 7 are clear). So \ this gives A the sign of x_sign and gives it a value \ range of -63 (%11000001) to 0 .SC2 ADC #123 \ Set A = 123 + (x_sign x_hi) STA SCANx1 \ Store the x-coordinate in SCANx1 so it can be sent \ to the I/O processor with the #onescan command \ Next, we convert the z_hi coordinate of the ship into \ the y-coordinate of the base of the ship's stick, \ like this (see the deep dive on "The 3D scanner" for \ an explanation): \ \ SC = 220 - (z_sign z_hi) / 4 \ \ though the following code actually does it like this: \ \ SC = 255 - (35 + z_hi / 4) LDA INWK+7 \ Set A = z_hi / 4 LSR A \ LSR A \ So A is in the range 0-15 CLC \ Clear the C flag for the addition below LDX INWK+8 \ Set X = z_sign BPL SC3 \ If z_sign is positive, skip the following EOR #%11111111 \ z_sign is negative, so flip the bits in A and set the SEC \ C flag. As above, this makes A negative, this time \ with a range of -16 (%11110000) to -1 (%11111111). And \ as we are about to do an ADC, the SEC effectively adds \ another 1 to that value, giving a range of -15 to 0 .SC3 ADC #35 \ Set A = 35 + A to give a number in the range 20 to 50 EOR #%11111111 \ Flip all the bits and store in SC, so SC is in the STA SC \ range 205 to 235, with a higher z_hi giving a lower SC \ Now for the stick height, which we calculate using the \ following (see the deep dive on "The 3D scanner" for \ an explanation): \ \ A = - (y_sign y_hi) / 2 LDA INWK+4 \ Set A = y_hi / 2 LSR A CLC \ Clear the C flag LDX INWK+5 \ Set X = y_sign BMI SCD6 \ If y_sign is negative, skip the following, as we \ already have a positive value in A EOR #%11111111 \ y_sign is positive, so flip the bits in A and set the SEC \ C flag. This makes A negative, and as we are about to \ do an ADC below, the SEC effectively adds another 1 to \ that value to implement two's complement negation, so \ we don't need to add another 1 here .SCD6 \ We now have all the information we need to draw this \ ship on the scanner, namely: \ \ X1 = the screen x-coordinate of the ship's dot \ \ SC = the screen y-coordinate of the base of the \ stick \ \ A = the screen height of the ship's stick, with the \ correct sign for adding to the base of the stick \ to get the dot's y-coordinate \ \ First, though, we have to make sure the dot is inside \ the dashboard, by moving it if necessary ADC SC \ Set A = SC + A, so A now contains the y-coordinate of \ the end of the stick, plus the length of the stick, to \ give us the screen y-coordinate of the dot BPL FIXIT \ If the result has bit 0 clear, then the result has \ overflowed and is bigger than 256, so jump to FIXIT to \ set A to the maximum allowed value of 246 (this \ instruction isn't required as we test both the maximum \ and minimum below, but it might save a few cycles) CMP #194 \ If A >= 194, skip the following instruction, as 194 is BCS P%+4 \ the minimum allowed value of A LDA #194 \ A < 194, so set A to 194, the minimum allowed value \ for the y-coordinate of our ship's dot CMP #247 \ If A < 247, skip the following instruction, as 246 is BCC P%+4 \ the maximum allowed value of A .FIXIT LDA #246 \ A >= 247, so set A to 246, the maximum allowed value \ for the y-coordinate of our ship's dot STA SCANy1 \ Store the y-coordinate in SCANy1 so it can be sent \ to the I/O processor with the #onescan command SEC \ Set A = A - SC to get the stick length, by reversing SBC SC \ the ADC SC we did above. This clears the C flag if the \ result is negative (i.e. the stick length is negative) \ and sets it if the result is positive (i.e. the stick \ length is negative) \ So now we have the following: \ \ X1 = the screen x-coordinate of the ship's dot, \ clipped to fit into the dashboard \ \ Y1 = the screen y-coordinate of the ship's dot, \ clipped to fit into the dashboard \ \ SC = the screen y-coordinate of the base of the \ stick \ \ A = the screen height of the ship's stick, with the \ correct sign for adding to the base of the stick \ to get the dot's y-coordinate \ \ C = 0 if A is negative, 1 if A is positive \ \ and we can get on with drawing the dot and stick STA SCANlen \ Store the stick height in SCANlen so it can be sent \ to the I/O processor with the #onescan command ROR SCANflg \ Rotate the C flag into bit 7 of SCANflg, so bit 7 is \ the sign bit of the stick length .SC48 LDX #LO(SCANpars) \ Set (Y X) to point to the SCANpars parameter block LDY #HI(SCANpars) LDA #onescan \ Send a #onescan command to the I/O processor to draw JMP OSWORD \ the ship on the scanner, returning from the subroutine \ using a tail call
Name: WSCAN [Show more] Type: Subroutine Category: Drawing the screen Summary: Ask the I/O processor to wait for the vertical sync by sending a #wscn command to the I/O processor
Context: See this subroutine on its own page Variations: See code variations for this subroutine in the different versions References: This subroutine is called as follows: * DELAY calls WSCAN * DK4 calls WSCAN * Main flight loop (Part 13 of 16) calls WSCAN * TT16 calls WSCAN

This routine sends a #wscn command to the I/O processor to ask it to wait for the vertical sync.
.WSCpars EQUB 2 \ Transmit 2 bytes as part of this command EQUB 2 \ Receive 2 bytes as part of this command EQUW 0 \ This is unused as no parameters are transmitted along \ with this command .WSCAN PHX \ Store X and Y on the stack so we can restore them PHY \ later LDA #wscn \ Set A in preparation for sending a #wscn command LDX #LO(WSCpars) \ Set (Y X) to point to the parameter block above LDY #HI(WSCpars) JSR OSWORD \ Send a #wscn command to the I/O processor to wait for \ the vertical sync PLY \ Restore X and Y from the stack PLX RTS \ Return from the subroutine
Save ELTH.bin
PRINT "ELITE H" PRINT "Assembled at ", ~CODE_H% PRINT "Ends at ", ~P% PRINT "Code size is ", ~(P% - CODE_H%) PRINT "Execute at ", ~LOAD% PRINT "Reload at ", ~LOAD_H% PRINT "S.ELTH ", ~CODE_H%, " ", ~P%, " ", ~LOAD%, " ", ~LOAD_H% SAVE "3-assembled-output/ELTH.bin", CODE_H%, P%, LOAD%