Skip to navigation

Revs on the BBC Micro

Revs C source

Name: GetColour (Part 1 of 3) [Show more] Type: Subroutine Category: Screen buffer Summary: Calculate the colour of a specific pixel byte in the screen buffer
Context: See this subroutine on its own page References: This subroutine is called as follows: * DrawObjectEdge (Part 4 of 5) calls GetColour * FillAfterObject calls GetColour

Arguments: Y The track line number of the pixel byte to check blockNumber The dash data block number of the pixel byte to check (Q P) The address of the dash data block containing the pixel byte we want to check
Returns: A The colour of this pixel byte in the screen buffer
IF _ACORNSOFT OR _4TRACKS .GetColour CPY horizonLine \ If Y <= horizonLine then the byte we want to check is BCC gcol1 \ below the horizon, so jump to gcol1 to work out the BEQ gcol1 \ byte's colour LDA horizonLine \ Set A to the track line number of the horizon JSR SetMarker+3 \ Call SetMarker+3 to insert a marker value at the \ horizon line LDA colourPalette+1 \ Otherwise the byte is in the sky, so set A to logical \ colour 1 (blue) from the colour palette RTS \ Return from the subroutine .gcol1 LDA #0 \ Set T = 0, to use for storing the results of the STA T \ following comparisons LDA blockNumber \ Set A to the block number containing the pixel byte \ that we want to check CMP leftVergeStart,Y \ If A >= leftVergeStart for this track line, rotate a ROL T \ 1 into T, otherwise rotate a 0 into T CMP leftTrackStart,Y \ If A >= leftTrackStart for this track line, rotate a ROL T \ 1 into T, otherwise rotate a 0 into T CMP rightVergeStart,Y \ If A >= rightVergeStart for this track line, rotate a ROL T \ 1 into T, otherwise rotate a 0 into T CMP rightGrassStart,Y \ If A >= rightGrassStart for this track line, rotate a LDA T \ 1 into the result, otherwise rotate a 0, and copy the ROL A \ results from all four comparisons into A, so we have: \ \ * Bit 0: 1 if blockNumber >= rightGrassStart \ 0 if blockNumber < rightGrassStart \ \ * Bit 1: 1 if blockNumber >= rightVergeStart \ 0 if blockNumber < rightVergeStart \ \ * Bit 2: 1 if blockNumber >= leftTrackStart \ 0 if blockNumber < leftTrackStart \ \ * Bit 3: 1 if blockNumber >= leftVergeStart \ 0 if blockNumber < leftVergeStart BNE gcol7 \ If A is non-zero, then the block number containing the \ pixel we want to check is greater than at least one \ of the verge edges, so jump to gcol7 \ If we get here then blockNumber is less than all the \ track verge block numbers LDA backgroundColour,Y \ Set A to the background colour for the track line \ containing the pixel we want to check AND #%11101100 \ Extract the following bits: \ \ * Bits 5-7 and 2: records which routine set this \ colour \ \ * Bit 3: contains the verge type that was being \ drawn when this colour was set \ \ * 0 = leftVergeStart, rightVergeStart \ \ * 1 = leftTrackStart, rightGrassStart CMP #%01000000 \ If this colour matches these bits: BEQ gcol2 \ \ * Bits 5-7 and 2 = %010 0 \ \ * Bit 3 = 0 \ \ then the colour was set by UpdateBackground to the \ value in backgroundRight when drawing leftVergeStart \ or rightVergeStart, so jump to gcol2 CMP #%10001000 \ If this colour matches these bits: BEQ gcol2 \ \ * Bits 5-7 and 2 = %100 0 \ \ * Bit 3 = 1 \ \ then the colour was set by UpdateBackground to the \ value in backgroundLeft when drawing leftTrackStart \ or rightGrassStart, so jump to gcol2 CMP #%00000100 \ If this colour matches these bits: BEQ gcol2 \ \ * Bits 5-7 and 2 = %000 1 \ \ * Bit 3 = 0 \ \ then the colour was set by SetVergeBackground when \ drawing leftVergeStart or rightVergeStart, so jump to \ gcol2 LDA rightGrassStart,Y \ Set A to the block number containing the right edge of \ the right verge BPL gcol3 \ If A is positive then jump to gcol3 BMI gcol4 \ Jump to gcol4 to return the background colour for this \ track line as the pixel's colour (this BMI is \ effectively a JMP, as we just passed through a BPL) .gcol2 LDA backgroundColour,Y \ Set A to the background colour for the track line \ containing the pixel we want to check AND #%00010000 \ If bit 4 of the background colour is set, then the BNE gcol3 \ verge being drawn when the colour was set was \ rightVergeStart or rightGrassStart, so jump to gcol3 JSR gcol8 \ Call gcol8 to process the left verge JMP gcol4 \ Jump to gcol4 to return the background colour for this \ track line as the pixel's colour .gcol3 JSR gcol12 \ Call gcol12 to process the right verge .gcol4 LDA backgroundColour,Y \ Set A to the background colour for the track line \ containing the pixel we want to check AND #%00000011 \ Extract the colour number from bits 0-1 of A into X TAX LDA colourPalette,X \ Set A to logical colour X from the colour palette RTS \ Return from the subroutine .gcol5 LDA colourPalette \ Set A to logical colour 0 (black) from the colour \ palette RTS \ Return from the subroutine .gcol6 LDA colourPalette+3 \ Set A to logical colour 3 (green) from the colour \ palette RTS \ Return from the subroutine .gcol7 \ If we get here then the block number containing the \ pixel we want to check is greater than at least one \ of the verge edges, and we have the following: \ \ * Bit 0: 1 if blockNumber >= rightGrassStart \ 0 if blockNumber < rightGrassStart \ \ * Bit 1: 1 if blockNumber >= rightVergeStart \ 0 if blockNumber < rightVergeStart \ \ * Bit 2: 1 if blockNumber >= leftTrackStart \ 0 if blockNumber < leftTrackStart \ \ * Bit 3: 1 if blockNumber >= leftVergeStart \ 0 if blockNumber < leftVergeStart LSR A \ If blockNumber >= rightGrassStart, jump to gcol6 to BCS gcol6 \ return from the subroutine with the colour green LSR A \ If blockNumber >= rightVergeStart, jump to gcol12 BCS gcol12 LSR A \ If blockNumber >= leftTrackStart, jump to gcol5 to BCS gcol5 \ return from the subroutine with the colour black \ If we get here then blockNumber >= leftVergeStart, as \ we only jump to gcol7 if at least one of the four bits \ is set, so by a process of elimination, it must be \ bit 3
Name: GetColour (Part 2 of 3) [Show more] Type: Subroutine Category: Screen buffer Summary: Process the left verge
Context: See this subroutine on its own page References: No direct references to this subroutine in this source file
.gcol8 CPY vergeTopLeft \ If Y >= vergeTopLeft, jump to gcol6 to return from the BCS gcol6 \ subroutine with the colour green LDX leftSegment,Y \ Set X to the index within the track segment list of \ the segment for the left verge on this track line BMI gcol14 \ If bit 7 of X is set, then this entry in the \ rightSegment table was filled in by MapSegmentsToLines \ for a segment that doesn't have an entry in the track \ segment list, in which case the index of the last \ valid entry is captured in bits 0-6, so jump to gcol14 \ to clear bit 7 of X and return the colour of the verge \ mark for the segment beyond segment X JSR SetMarker \ Call SetMarker to insert a &AA marker into the screen \ buffer at the left verge .gcol9 LDA (P),Y \ If the current byte in the screen buffer is non-zero, BNE gcol11 \ then it is not empty, so jump to gcol11 LDA leftTrackStart,Y \ Set A to the block number containing the right edge of \ the left verge BMI gcol10 \ If bit 7 of A is set then the block number is still in \ its initialised form, so jump to gcol10 CMP blockNumber \ Set the C flag if A >= blockNumber, which contains the \ dash data block number for the current edge DEY \ Decrease the track line in Y BCS gcol9 \ If A >= blockNumber, loop back to gcol9 INY \ Increment the track line in Y .gcol10 JSR SetMarker+6 \ Call SetMarker+6 to insert a marker byte into the Y-th \ byte of the dash data block, but only if the Y-th \ entry is zero and blockOffset <= Y < V .gcol11 LDY V \ Set Y = V JMP gcol13 \ Jump to gcol13 to return the colour of the verge mark \ for the segment beyond segment X
Name: GetColour (Part 3 of 3) [Show more] Type: Subroutine Category: Screen buffer Summary: Process the right verge
Context: See this subroutine on its own page References: No direct references to this subroutine in this source file
.gcol12 CPY vergeTopRight \ If Y >= vergeTopRight, jump to gcol6 to return from BCS gcol6 \ the subroutine with the colour green LDX rightSegment,Y \ Set X to the index within the track segment list of \ the segment for the right verge on this track line BMI gcol14 \ If bit 7 of X is set, then this entry in the \ rightSegment table was filled in by MapSegmentsToLines \ for a segment that doesn't have an entry in the track \ segment list, in which case the index of the last \ valid entry is captured in bits 0-6, so jump to gcol14 \ to clear bit 7 of X and return the colour of the verge \ mark for the segment beyond segment X JSR SetMarker \ Call SetMarker to insert a &AA marker into the screen \ buffer at the right verge .gcol13 LDA vergeDataRight-1,X \ Set A to entry X - 1 from vergeDataRight, which \ contains the colour of the verge for the segment \ beyond segment X AND #%00000011 \ Extract the colour number from bits 0-1 of A into X TAX LDA colourPalette,X \ Set A to logical colour X from the colour palette RTS \ Return from the subroutine .gcol14 TXA \ Clear bit 7 of X AND #%01111111 TAX BPL gcol13 \ Jump to gcol13 (this BPL is effectively a JMP as we \ just cleared bit 7 of A) ENDIF
Name: SetMarker [Show more] Type: Subroutine Category: Screen buffer Summary: Insert a marker value into a dash data block
Context: See this subroutine on its own page References: This subroutine is called as follows: * GetColour (Part 2 of 3) calls SetMarker * GetColour (Part 3 of 3) calls SetMarker * GetColour (Part 1 of 3) calls via SetMarker+3 * GetColour (Part 2 of 3) calls via SetMarker+6

This routine inserts a marker value (&AA) into the current dash data block at a specified track line, but only if the current value in the dash data block is zero, and only if the track line is in the specified range. If the routine is called via SetMarker, then it works like this: * A is set to the pitch angle (track line) of the X-th entry in the verge buffer * The A-th byte in the dash data block at (Q P) is set to the marker &AA if blockOffset <= A < Y and it is currently zero If the routine is called via SetMarker+3, then it works like this: * The A-th byte in the dash data block at (Q P) is set to the marker &AA if blockOffset <= A < Y and it is currently zero If the routine is called via SetMarker+6, then it works like this: * The Y-th byte in the dash data block at (Q P) is set to the marker &AA if blockOffset <= Y < V and it is currently zero
Arguments: Y A track line number X Index of an entry in the verge buffer (SetMarker only)
Other entry points: SetMarker+3 Use the value of A passed to the routine SetMarker+6 Use Y and V in place of A and Y
IF _ACORNSOFT OR _4TRACKS .SetMarker LDA yVergeRight,X \ Set A to the pitch angle of the X-th entry in the \ verge buffer (i.e. the track line number of the \ X-th entry) \ We join the subroutine here if we call SetMarker+3 STY V \ Set V to the track line number in Y TAY \ Set Y to the track line number in A \ We join the subroutine here if we call SetMarker+6 CPY V \ If Y >= V, jump to setm1 to return from the BCS setm1 \ subroutine with Y = V CPY blockOffset \ If Y < blockOffset, jump to setm1 to return from the BCC setm1 \ subroutine with Y = V LDA (P),Y \ If the Y-th byte in the dash data block is non-zero, BNE setm1 \ then it is not empty, so jump to setm1 to return from \ the subroutine with Y = V LDA #&AA \ Set the Y-th byte in the dash data block to &AA, to STA (P),Y \ act as a marker that gets picked up in the drawing \ routine .setm1 LDY V \ Restore Y to the track line number of the pixel byte \ to check, so it's unchanged by the call for calls to \ SetMarker and SetMarker+3 RTS \ Return from the subroutine ENDIF
Name: GetColourSup [Show more] Type: Subroutine Category: Screen buffer Summary: Calculate the colour of a specific pixel byte in the screen buffer
Context: See this subroutine on its own page References: This subroutine is called as follows: * DrawObjectEdge (Part 4 of 5) calls GetColourSup * FillAfterObjectSup calls GetColourSup

Arguments: Y The track line number of the pixel byte to check blockNumber The dash data block number of the pixel byte to check
Returns: A The colour of this pixel byte in the screen buffer
IF _SUPERIOR OR _REVSPLUS .GetColourSup CPY horizonLine \ If Y <= horizonLine then the byte we want to check is BCC scol1 \ below the horizon, so jump to scol1 to work out the BEQ scol1 \ byte's colour LDA colourPalette+1 \ Otherwise the byte is in the sky, so set A to logical \ colour 1 (blue) from the colour palette RTS \ Return from the subroutine .scol1 LDA blockNumber \ Set A to the block number containing the pixel byte \ that we want to check CMP rightGrassStart,Y \ If A >= rightGrassStart for this track line, then the BCS scol3 \ pixel byte is in the grass to the right of the track, \ so jump to scol3 to return colour 3 (green) CMP rightVergeStart,Y \ If A >= rightVergeStart for this track line, then the BCS scol5 \ pixel byte is on the right track verge, so jump to \ scol5 to work out its colour CMP leftTrackStart,Y \ If A >= leftTrackStart for this track line, then the BCS scol2 \ pixel byte is on the track, so jump to scol2 to return \ colour 0 (black) CMP leftVergeStart,Y \ If A >= leftVergeStart for this track line, then the BCS scol4 \ pixel byte is on the left track verge, so jump to \ scol4 to work out its colour LDA backgroundColour,Y \ If we get here then the byte is to the left of the \ left track verge, so set A to the background colour of \ this track line so we can extract the colour from bits \ 0-1 below BCC scol7 \ Jump to scol7 to return the pixel byte for the colour \ in A (this BCC is effectively a JMP as we just passed \ through a BCS) .scol2 LDA colourPalette \ Set A to logical colour 0 (black) from the colour \ palette RTS \ Return from the subroutine .scol3 LDA colourPalette+3 \ Set A to logical colour 3 (green) from the colour \ palette RTS \ Return from the subroutine .scol4 \ If we get here then the pixel byte is on the left \ track verge CPY vergeTopLeft \ If the track line in Y >= vergeTopLeft, jump to scol3 BCS scol3 \ to return colour 3 (green) LDA leftSegment,Y \ Set A to the index within the track segment list of \ the segment for the left verge on this track line JMP scol6 \ Jump to scol6 .scol5 \ If we get here then the pixel byte is on the right \ track verge CPY vergeTopRight \ If the track line in Y >= vergeTopRight, jump to scol3 BCS scol3 \ to return colour 3 (green) LDA rightSegment,Y \ Set A to the index within the track segment list of \ the segment for the right verge on this track line .scol6 AND #%01111111 \ Clear bit 7 of A TAX \ Set X to A LDA vergeDataRight-1,X \ Set A to entry X - 1 from vergeDataRight, which \ contains the colour of the verge mark for the segment \ beyond segment X .scol7 AND #%00000011 \ Extract the colour number from bits 0-1 of A into X TAX LDA colourPalette,X \ Set A to logical colour X from the colour palette RTS \ Return from the subroutine ENDIF
Name: AssistSteering [Show more] Type: Subroutine Category: Tactics Summary: Apply computer assisted steering (CAS) when configured Deep dive: Tactics of the non-player drivers Computer assisted steering (CAS)
Context: See this subroutine on its own page References: This subroutine is called as follows: * ProcessDrivingKeys (Part 1 of 6) calls AssistSteering * ProcessDrivingKeys (Part 2 of 6) calls via AssistSteeringKeys

This routine applies computer assisted steering (CAS) to the joystick and keyboard, but only if it is enabled and we are already steering (if we are not steering, then there is no steering to assist). Jumps back to: * keys11 (joystick, CAS not enabled) * keys7 (joystick, CAS enabled, joystick is hardly steering) * keys10 (keyboard, or joystick with CAS applied)
Arguments: (U T) The amount of steering currently being applied by the steering wheel: * For joystick, contains the scaled joystick x-coordinate as a sign-magnitude number with the sign in bit 0 (1 = left, 0 = right) * For keyboard, contains a signed 16-bit number, negative if bit 0 of steeringLo is set (left), positive if bit 0 of steeringLo is clear (right) (A T) Same as (U T) V For keyboard only: * V = 1 if ";" is being pressed (steer right) * V = 2 if "L" is being pressed (steer left) * V = 0 if neither is being pressed
Returns: A A is set to steeringLo (U T) The new amount of steering to apply, adjusted to add computer assisted steering, as a sign-magnitude number
Other entry points: AssistSteeringKeys For keyboard-controlled steering
IF _SUPERIOR OR _REVSPLUS .AssistSteering JSR GetSteeringAssist \ Set X = configAssist, set the C flag to bit 7 of \ directionFacing, and update the computer assisted \ steering (CAS) indicator on the dashboard BNE asst2 \ If CAS is enabled, jump to asst2 to skip the following \ instruction and apply CAS, otherwise we jump to keys11 \ to return to the ProcessDrivingKeys routine .asst1 JMP keys11 \ Return to the ProcessDrivingKeys routine at keys11 .asst2 BCS asst1 \ If bit 7 of directionFacing is set, then our car is \ facing backwards, so jump to asst1 to jump to keys11 \ in the ProcessDrivingKeys routine, as CAS only works \ when driving forwards CMP #5 \ If A >= 5, then the joystick is currently applying BCS asst4 \ some steering, so jump to asst4 to continue applying \ CAS \ Otherwise the joystick is not being used for steering \ at the moment, so there is no steering to assist and \ we don't apply CAS JMP keys7 \ Return to the ProcessDrivingKeys routine at keys7 to \ apply no joystick steering .AssistSteeringKeys JSR GetSteeringAssist \ Set X = configAssist, set the C flag to bit 7 of \ directionFacing, and update the CAS indicator on the \ dashboard BEQ asst3 \ If CAS is not enabled, jump to asst3 to set A and jump \ to keys10 in the ProcessDrivingKeys routine BCS asst3 \ If bit 7 of directionFacing is set, then our car is \ facing backwards, so jump to asst3 to jump to keys10 \ in the ProcessDrivingKeys routine, as CAS only works \ when driving forwards LDA V \ Set A = V BNE asst5 \ If A is non-zero, then one of the steering keys is \ being held down, so jump to asst5 to continue applying \ CAS \ Otherwise the keyboard is not being used for steering \ at the moment, so there is no steering to assist and \ we don't apply CAS .asst3 JMP asst13 \ Jump to asst13 to set A to steeringLo and return to \ the ProcessDrivingKeys routine at keys210 .asst4 \ If we get here then the joystick is being used for \ steering, and (A T) contains the scaled joystick \ x-coordinate as a sign-magnitude number with the \ sign in bit 0 (1 = left, 0 = right) LDA T \ Set the C flag to the inverse of the joystick EOR #1 \ x-coordinate's sign bit from bit 0 (i.e. 0 = left, LSR A \ 1 = right) LDA #3 \ Set A to 3 (if the C flag is set, i.e. right) or 2 (if SBC #0 \ the C flag is clear, i.e. left) .asst5 \ If we get here, then either the joystick or keyboard \ is being used for steering, and we have the following: \ \ * A = 2 if we are steering left \ \ We now set X as a flag for the steering direction, so \ we can use A for other purposes LDX #50 \ Set X = 50 to use as the value for steering left CMP #2 \ If A = 2 then we are steering left, so jump to asst6 BEQ asst6 \ to skip the following instruction LDX #10 \ Set X = 10 to use as the value for steering right \ So we now have the following that we can use to check \ which direction we are steering: \ \ * X = 10 if we are steering right \ \ * X = 50 if we are steering left .asst6 \ We now spend the rest of the routine calculating the \ amount of computer assisted steering (CAS) to apply, \ returning the result in the sign-magnitude number \ (U T) \ \ First, we set the following if we are steering right: \ \ (W V) = (steeringHi steeringLo) + 256 \ \ or the following if we are steering left: \ \ (W V) = (steeringHi steeringLo) - 256 \ \ by first converting (steeringHi steeringLo) from a \ sign-magnitude number to a signed 16-bit number and \ then doing the addition or subtraction LDA steeringLo \ Set V = steeringLo STA V LSR A \ Set the C flag to the sign of steeringLo LDA steeringHi \ Set A = steeringHi \ \ So (A V) = (steeringHi steeringLo) BCC asst7 \ If the C flag is clear then (steeringHi steeringLo) is \ positive, so jump to asst7 as (A V) already has the \ correct sign \ Otherwise (steeringHi steeringLo) is negative, so we \ need to negate (A V) LDA #0 \ Set (A V) = 0 - (A V) SEC \ SBC V \ starting with the low bytes STA V LDA #0 \ And then the high bytes SBC steeringHi .asst7 CLC \ Set (A V) = (A V) + 256 ADC #1 \ = (steeringHi steeringLo) + 256 CPX #50 \ If X <> 50, then we are steering right, so jump to BNE asst8 \ asst8 SBC #2 \ X = 50, so we are steering left, so set: \ \ (A V) = (A V) - 2 * 256 \ = (steeringHi steeringLo) + 256 - 2 * 256 \ = (steeringHi steeringLo) - 256 .asst8 STA W \ Set (W V) = (A V) \ \ So if we are steering right, we have: \ \ (W V) = (steeringHi steeringLo) + 256 \ \ and if we are steering left we have: \ \ (W V) = (steeringHi steeringLo) - 256 LDA xVergeRightLo,X \ Set (A T) = X-th (xVergeRightHi xVergeRightLo) - (W V) SEC \ SBC V \ starting with the low bytes STA T LDA xVergeRightHi,X \ And then the high bytes SBC W PHP \ Store the sign flag for X-th xVergeRight - (W V) on \ the stack, so we can retrieve it below JSR Absolute16Bit \ Set (A T) = |A T| \ = |X-th xVergeRight - (W V)| STA V \ Set (V T) = (A T) \ = |X-th xVergeRight - (W V)| LDY playerSegmentIndex \ Set Y to the index of the player's segment in the \ track segment buffer LDA #60 \ Set A = 60 - playerSpeedHi SEC SBC playerSpeedHi BPL asst9 \ If the result is positive, jump to asst9 to skip the \ following instruction LDA #0 \ Set A = 0, so A is always positive, and is zero if we \ are currently doing more than 60, so: \ \ A = max(0, 60 - playerSpeedHi) .asst9 ASL A \ Set U = 32 * A * 2 ADC #32 \ = 32 + max(0, 60 - playerSpeedHi) * 2 STA U \ \ So U is 32 if we are doing more than 60, and higher \ with lower speeds LDA segmentSteering,Y \ Fetch the carSteering value to steer round the corner \ for the player's track segment AND #%01111111 \ Zero the driving direction in bit 7 CMP #64 \ If A < 64, jump to asst10 to skip the following BCC asst10 \ instruction LDA #2 \ A >= 64, i.e. bit 6 is set, so set A = 2 .asst10 CMP #8 \ If A < 8, jump to asst11 to skip the following BCC asst11 \ instruction LDA #7 \ A >= 8, so set A = 7, i.e. A = min(A, 7) .asst11 \ By now A is between 0 and 7, and is set to 2 if bit 6 \ of segmentSteering was set ASL A \ Set A = A * 16 ASL A \ ASL A \ So A is in the range 0 to 112 ASL A CMP U \ If A < U, jump to asst12 to skip the following BCC asst12 \ instruction STA U \ A >= U, so set U = A, i.e. set U = max(U, A) .asst12 JSR Multiply8x16 \ Set (U T) = U * (V T) / 256 \ = U * |X-th xVergeRight - (W V)| / 256 LDA U \ Set (A T) = (U T) \ = U * |X-th xVergeRight - (W V)| / 256 PLP \ Retrieve the sign of the X-th xVergeRight - (W V) \ calculation that we stored above JSR Absolute16Bit \ Set the sign of (A T) to that of X-th xVergeRight - \ (W V), so we now have: \ \ (A T) = U * (X-th xVergeRight - (W V)) / 256 STA U \ Set (U T) = (A T) \ = U * (X-th xVergeRight - (W V)) / 256 LDA T \ Clear bit 0 of (U T) AND #%11111110 STA T LDA steeringLo \ Set the C flag to the sign in bit 0 of steeringLo LSR A BCS asst13 \ If the C flag is set, jump to asst13 to skip the \ following instruction JSR Negate16Bit+2 \ Set (A T) = -(U T) STA U \ Set (U T) = (A T) \ = -(U T) .asst13 LDA steeringLo \ Set A = steeringLo to return from the subroutine JMP keys10 \ Return to the ProcessDrivingKeys routine at keys10 ENDIF
Name: SetSteeringLimit [Show more] Type: Subroutine Category: Keyboard Summary: Apply a maximum limit to the amount of steering
Context: See this subroutine on its own page References: This subroutine is called as follows: * ProcessDrivingKeys (Part 2 of 6) calls SetSteeringLimit

Arguments: C flag The result of CMP steeringHi
Returns: (A T) A is set to |steeringHi steeringLo|
IF _SUPERIOR OR _REVSPLUS .SetSteeringLimit BCC slim1 \ Before calling this routine, we did a CMP steeringHi, \ so if A < steeringHi, jump to slim1 to return from \ the subroutine LDA steeringLo \ Set T = steeringLo with bit 0 cleared AND #%11111110 STA T LDA steeringHi \ Set A = steeringHi, so (A T) = (steeringHi steeringLo) \ with the sign bit in bit 0 cleared .slim1 RTS \ Return from the subroutine ENDIF
Name: SetPlayerDriftSup [Show more] Type: Subroutine Category: Car geometry Summary: Record player drift, but only if the player is not in the first three segments of a track section
Context: See this subroutine on its own page References: This subroutine is called as follows: * MovePlayerOnTrack calls SetPlayerDriftSup

This routine is only present in the Superior Software release. In the Acornsoft release, this routine consists of a single ROR playerDrift instruction, so the Superior Software version differs as follows: * Acornsoft sets the playerDrift flag if A >= 22 * Superior sets the playerDrift flag if A >= 22 and objSectionSegmt for the player is >= 3 So the Superior version does not record drift in the first three segments of a new track section.
IF _SUPERIOR OR _REVSPLUS .SetPlayerDriftSup BCC drif1 \ If the C flag is clear, jump to drif1 to skip the \ following LDA objSectionSegmt,X \ Set A = objSectionSegmt, which keeps track of the \ player's segment number in the current track section CMP #3 \ If A < 3, clear the C flag, if A >= 3, set the C \ flag .drif1 ROR playerDrift \ Store the C flag in bit 7 of playerDrift, so this will \ be set if the original A >= 22 and if the second \ A >= 3 RTS \ Return from the subroutine NOP \ This instruction is unused, and is included to pad out \ the code ENDIF
Name: DrawObject [Show more] Type: Subroutine Category: Drawing objects Summary: Draw an object of a specific type
Context: See this subroutine on its own page References: This subroutine is called as follows: * DrawCarOrSign calls DrawObject * DrawCornerMarkers calls DrawObject

This routine is used to draw objects such as road signs, corner markers and cars.
Arguments: objectType The type of object to draw (0 to 12) scaleUp The scale factor for this object (i.e. its size) colourPalette The colour palette to use for drawing the object X Driver number: * 0-19 = map logical colour 1 according to the driver number in X: * Drivers 0, 4, 8, 12, 16 map to colour 0 (black) * Drivers 1, 5, 9, 13, 17 map to colour 1 (red) * Drivers 2, 6, 10, 14, 18 map to colour 2 (white) * Drivers 2, 7, 11, 15, 19 map to colour 3 (green) * 20-22 = this is the four-object car, which is the closest car in front of us, so map logical colour 1 according to the number of the driver in front of us (using the same logic as above) * 23 = stick with the palette in colourPalette
Returns: colourPalette Gets reset back to the default palette
.DrawObject STX T \ Store the driver number in T \ We start by copying the four bytes from the standard \ colour palette in colourPalette to the object colour \ palette in objectPalette, as we use the latter to draw \ the object LDX #3 \ Set up a counter in X for copying the four palette \ bytes .dobj1 LDA colourPalette,X \ Copy the X-th byte of colourPalette to the X-th byte STA objectPalette,X \ of objectPalette DEX \ Decrement the loop counter BPL dobj1 \ Loop back until we have copied all four bytes LDA #%11110000 \ Map logical colour 2 in the colour palette to physical STA colourPalette+2 \ colour 1 (white in the track view), which sets it back \ to the default value \ \ This only has an effect when we call DrawObject from \ DrawCornerMarkers, which changes the value of colour 2 \ in colourPalette (all other calls to DrawObject leave \ the colour palette alone) \ We now set the palette differently, depending on the \ driver number in A: \ \ * 0-19 = map logical colour 1 to physical colour \ A mod 4 \ \ * 20-22 = map logical colour 1 to physical colour \ (number of the driver in front) mod 4 \ \ * 23 = don't change the palette, i.e. use the \ palette from colourPalette LDA T \ Set A = T, so A contains the driver number CMP #23 \ If A = 23, jump to dobj3 to skip the following palette BEQ dobj3 \ changes CMP #20 \ If A < 20, jump to dobj2 to map logical colour 1 to BCC dobj2 \ physical colour A mod 4, in other words: \ \ * Drivers 0, 4, 8, 12, 16 map to colour 0 (black) \ * Drivers 1, 5, 9, 13, 17 map to colour 1 (red) \ * Drivers 2, 6, 10, 14, 18 map to colour 2 (white) \ * Drivers 2, 7, 11, 15, 19 map to colour 3 (green) \ If we get here then A is 20, 21 or 22, which is the \ four-object car, so we map logical colour 1 to the \ number of the driver in front of us, mod 4 LDX positionAhead \ Set X to the position of the driver in front of us LDA driversInOrder,X \ Set A the number of the driver in front of us, so we \ map logical colour 1 to physical colour A mod 4 .dobj2 AND #3 \ Set X = A mod 4 TAX LDA colourPalette,X \ Map logical colour 1 in the object palette to logical STA objectPalette+1 \ colour X from the colour palette .dobj3 LDX #0 \ Set scaleDown = 0, so the object's scaffold is not STX scaleDown \ scaled down (as 2^scaleDown = 2^0 = 1) LDA scaleUp \ Set A = scaleUp, so A contains the object size, which \ we can also interpret as the object distance CMP horizonTrackWidth \ If A >= horizonTrackWidth, then the object is closer BCS dobj4 \ than the horizon line, so jump to dobj4 to skip the \ following instruction and set lowestTrackLine to 0 (so \ the whole object is drawn) LDX horizonLine \ Otherwise the object is further away than the horizon \ line, so set X to the track line number of the \ horizon, so the parts of the object below this line do \ not get drawn (as they are below the horizon line, so \ presumably hidden by a hill) .dobj4 STX lowestTrackLine \ Set lowestTrackLine = X, so the object gets cut off at \ the horizon line when scaleUp < horizonTrackWidth CMP #64 \ If A >= 64, i.e. scaleUp >= 64, jump to dobj5 to skip BCS dobj5 \ the following \ Otherwise we can alter the values of scaleUp and \ scaleDown to be more accurate but without fear of \ overflow, by multiplying both scale factors by 4 \ (as we know 4 * scaleUp is < 256) ASL A \ Set scaleUp = A * 4 ASL A \ = scaleUp * 4 STA scaleUp LDA #2 \ Set scaleDown = 2, so the object's scaffold is scaled STA scaleDown \ down by 2^scaleDown = 2^2 = 4 \ \ So the overall scaling of the scaffold is the same, \ but we retain more accuracy .dobj5 LDX objectType \ Set X to the type of object we're going to draw \ If the object type is 10, 11 or 12, then it's one of \ the turn signs (chicane, left or right turn), so we \ draw this as two objects, starting with a blank white \ sign (object type 9) and then the sign contents \ (object 10, 11 or 12) \ \ We only draw the sign contents if our car is facing \ forwards, so the back of the sign is blank CPX #10 \ If X < 10, jump to dobj6 to skip the following BCC dobj6 \ instruction LDX #9 \ Set X = 9, so we first draw an object of type 9 for \ the blank white sign, before drawing another object of \ type objectType .dobj6 STX thisObjectType \ Store X in thisObjectType, so we can check it again \ below in case we need to draw two objects LDA scaffoldIndex,X \ Set QQ to the index of the first scaffold entry in STA QQ \ objectScaffold for object type X LDA scaffoldIndex+1,X \ Set II to the index of the first scaffold entry in STA II \ objectScaffold for object type X + 1 (so the last \ entry for object type X will be index II - 1) LDA objectIndex,X \ Set QQ to the index of the first entry in the object STA MM \ data tables for object type X (so MM will point to the \ first entry for this object in the objectTop, \ objectBottom, objectLeft, objectRight and objectColour \ tables) JSR ScaleObject \ Scale the object's scaffold by the scaleUp and \ scaleDown factors, storing the results in the \ scaledScaffold table BCS dobj7 \ If the call to ScaleObject set the C flag then the \ scaling process overflowed, in which case we do not \ draw the object, so jump to dobj7 to return from the \ subroutine JSR DrawObjectEdges \ Draw the scaled object in the screen buffer by drawing \ all the object's edges LDX objectType \ Set X to the type of object we are drawing, in case we \ need to draw a second object LDA thisObjectType \ If the object we just drew is not an object of type 9, CMP #9 \ then this is not a two-part road sign object, so jump BNE dobj7 \ to dobj7 to return from the subroutine \ Otherwise we just drew an object of type 9, for the \ blank white sign, so now we draw a second object for \ the sign's contents, but only if our car is facing \ forwards (if we are facing backwards, then we see the \ back of the sign, which is blank) LDA directionFacing \ If bit 7 of directionFacing is clear, then our car is BPL dobj6 \ facing forwards, so loop back to draw the contents of \ the sign in object type objectType .dobj7 RTS \ Return from the subroutine
Name: ScaleObject [Show more] Type: Subroutine Category: Drawing objects Summary: Scale an object's scaffold by the scale factors in scaleUp and scaleDown Deep dive: Scaling objects with scaffolds
Context: See this subroutine on its own page References: This subroutine is called as follows: * DrawObject calls ScaleObject

This routine is used when drawing objects such as road signs, corner markers and cars. It takes the values from the objectScaffold table, which contain an object's scaffold (i.e. all the essential measurements that we need to build the object), and scales them according to the values of scaleUp and scaleDown. As only scaffold measurements are used when drawing an object, this routine scales the whole object, according to the two scale factors. The value in scaleUp is the numerator of the scale factor, which scales the scaffold up, so bigger values of scaleUp give bigger objects. The value in scaleDown is the denominator of the scale factor, which scales the scaffold down, so bigger values of scaleDown give smaller objects.
Arguments: QQ Index of the first objectScaffold entry for this object II Index of the last objectScaffold entry for this object (where the last entry is index II - 1) scaleUp Numerator scale factor scaleDown Denominator scale factor
Returns: C flag Denotes whether the scaling was successful: * Clear if we manage to scale the scaffold * Set if the scaling of any individual scaffold measurements overflows, in which case we do not draw the object scaledScaffold The scaled scaffold scaledScaffold+8 The scaled scaffold, with each measurement negated
.ScaleObject LDA scaleUp \ Set scaleRange = scaleUp STA scaleRange LSR A \ Set scaleRange+1 = scaleUp >> 1 STA scaleRange+1 \ = scaleUp / 2 LSR A \ Set scaleRange+2 = scaleUp >> 2 STA scaleRange+2 \ = scaleUp / 4 LSR A \ Set scaleRange+3 = scaleUp >> 3 STA scaleRange+3 \ = scaleUp / 8 LSR A \ Set scaleRange+4 = scaleUp >> 4 STA scaleRange+4 \ = scaleUp / 16 LSR A \ Set scaleRange+5 = scaleUp >> 5 STA scaleRange+5 \ = scaleUp / 32 \ So scaleRange + n contains scaleUp / 2^n LDY QQ \ We now loop through the objectScaffold table from \ entry QQ to entry II - 1, so set a loop counter in Y \ to act as an index LDX #0 \ Set W = 0, to be used as an index as we populate the STX W \ scaledScaffold table, incrementing by one byte for \ each loop .prep1 LDA objectScaffold,Y \ Set A to the Y-th scaffold measurement BPL prep2 \ If bit 7 of A is clear, jump to prep2 to do the \ calculation that only uses bits 0-2 of A \ If we get here, bit 7 of A is set, so now we do the \ following calculation, where the value of A from the \ objectScaffold table is %1abbbccc: \ \ A = a * scaleUp/2 + scaleUp/2^b-2 + scaleUp/2^c-2 \ --------------------------------------------- \ 2^scaleDown \ \ = scaleUp * (a/2 + 1/2^b-2 + 1/2^c-2) \ ----------------------------------- \ 2^scaleDown \ \ scaleUp \ = ----------- * (a/2 + 1/2^b-2 + 1/2^c-2) \ 2^scaleDown \ \ scaleUp \ = ----------- * scaffold \ 2^scaleDown \ \ We then store this as the next entry in scaledScaffold \ \ Note that b and c are always in the range 3 to 7, so \ they look up the values we stored in scaleRange above AND #%00000111 \ Set X = bits 0-2 of A TAX \ = %ccc \ = c LDA scaleRange-2,X \ Set T = entry X-2 in scaleRange STA T \ = scaleUp / 2^X-2 \ = scaleUp / 2^c-2 LDA objectScaffold,Y \ Set A to the Y-th scaffold measurement STA U LSR A \ Set X = bits 3-5 of A LSR A \ = %bbb LSR A \ = b AND #%00000111 TAX LDA scaleRange-2,X \ Set A = entry X-2 in scaleRange + T CLC \ = scaleUp / 2^X-2 + scaleUp / 2^c-2 ADC T \ = scaleUp / 2^b-2 + scaleUp / 2^c-2 BIT U \ If bit 6 of U is clear, jump to prep3 BVC prep3 CLC \ If bit 6 of U is set: ADC scaleRange+1 \ \ A = A + scaleRange+1 \ = A + scaleUp / 2 JMP prep3 \ Jump to prep3 .prep2 \ If we get here, bit 7 of the Y-th objectScaffold is \ clear, so we do the following calculation, where \ A is %00000ccc: \ \ A = scaleUp / 2^c-2 \ --------------- \ 2^scaleDown \ \ = scaleUp * 1/2^c-2 \ ----------------- \ 2^scaleDown \ \ = scaleUp \ ----------- * 1/2^c-2 \ 2^scaleDown \ \ scaleUp \ = ----------- * scaffold \ 2^scaleDown \ \ We then store this as the next entry in scaledScaffold TAX \ Set A = entry c-2 in scaleRange LDA scaleRange-2,X \ = scaleUp / 2^c-2 .prep3 LDX scaleDown \ If scaleDown = 0 then the scale factor is 2^scaleDown BEQ prep5 \ = 2^0 = 1, so jump to prep5 to skip the division \ We now shift A right by X places, which is the same as \ dividing by 2^X = 2^scaleDown .prep4 LSR A \ Set A = A >> 1 DEX \ Decrement the shift counter BNE prep4 \ Loop back until we have shifted A right by X places, \ and the C flag contains the last bit shifted out from \ bit 0 of A ADC #0 \ Set A = A + C to round the result of the division to \ the nearest integer .prep5 LDX W \ Set X to W, the index into the tables we are building STA scaledScaffold,X \ Store A in the X-th byte of scaledScaffold EOR #&FF \ Set A = ~A BPL prep6 \ If bit 7 of A is clear, i.e. it was set before the \ EOR, then the result of the scaling was >= 128, which \ is an overflow of the scaling \ \ If the scaling overflows, then the object is too big \ to be drawn, so we jump to prep6 to return from the \ subroutine with the C flag set, so we do not draw this \ object and ignore all the values calculated here CLC \ Store -A in the X-th byte of scaledScaffold+8 ADC #1 STA scaledScaffold+8,X INC W \ Increment the index counter INY \ Increment the loop counter CPY II \ Loop back until Y has looped through QQ to II - 1 BNE prep1 CLC \ Clear the C flag to indicate a successful scaling RTS \ Return from the subroutine .prep6 SEC \ Set the C flag to indicate that scaling overflowed and \ the object should not be drawn RTS \ Return from the subroutine
Name: DrawObjectEdges [Show more] Type: Subroutine Category: Drawing objects Summary: Draw all the parts of an object by drawing edges into the screen buffer Deep dive: Creating objects from edges
Context: See this subroutine on its own page References: This subroutine is called as follows: * DrawObject calls DrawObjectEdges

This routine is used to draw road signs, corner markers and cars. They are drawn as edges - specifically the left and right edges - into the screen buffer in the dash data blocks.
Arguments: MM The index of the first entry in the object data tables for this this object (i.e. the index of the data for the object's first part) xPixelCoord The pixel x-coordinate of the centre of the object yPixelCoord The object's y-coordinate (for the centre of the object) in terms of track lines, so 80 is the top of the track view and 0 is the bottom of the track view lowestTrackLine Hide any part of the object that's below the specified track line (typically used to stop an object from being drawn below the horizon) * 0 = draw the whole object * Non-zero = only draw the part of the object that's above this track line
.DrawObjectEdges LDY MM \ Set Y to the index of this object data in the object \ data tables \ We now work our way through the data for this object, \ drawing one part at a time, using thisObjectIndex and \ Y as the loop counter as we loop through each part \ \ Note that most object parts are defined by one set of \ object data, so they correspond to two edges (left and \ right), but object types 2 and 4 contain four-edge \ object parts, which are defined by two sets of data, \ and therefore two loop iterations .drob1 LDA colourPalette \ Set rightOfEdge to logical colour 0 in the standard STA rightOfEdge \ colour palette, so the fill colour to the left of the \ first edge is set to a default of black when we call \ DrawObjectEdge below LDA #0 \ Set prevEdgeInByte = 0 to indicate that the first edge STA prevEdgeInByte \ is not sharing a pixel byte with the previous edge (as \ there isn't a previous edge) STA edgePixelMask \ Set edgePixelMask = 0 to pass to DrawObjectEdge below \ as there is no previous edge, so there should be no \ mask for the previous edge in the same pixel byte LDX objectTop,Y \ Set A to the scaled scaffold for the top of this part LDA scaledScaffold,X \ of the object CLC \ Set A = A + yPixelCoord ADC yPixelCoord \ \ so A is now the track line of the top of the object BMI drob9 \ If A > 128, then the top of this object part is well \ above the track view, so jump to drob9 to move on to \ the next object part as this one doesn't fit on-screen CMP #80 \ If A >= 80, set A = 79, as the maximum track line at BCC drob2 \ the very top of the track view is 79 LDA #79 .drob2 STA topTrackLine \ Store A in N as the number of the top track line, to \ send to DrawObjectEdge below LDX objectBottom,Y \ Set A to the scaled scaffold for the bottom of this LDA scaledScaffold,X \ part of the object CLC \ Set A = A + yPixelCoord ADC yPixelCoord \ \ so A is now the track line of the bottom of the object BMI drob3 \ If A < 0, then the bottom of this object part is lower \ than the bottom of the track view, so jump to drob3 to \ set A = lowestTrackLine, so we only draw the object \ down to the lowest line allowed CMP lowestTrackLine \ If A >= lowestTrackLine, jump to drob4 to skip the BCS drob4 \ following .drob3 \ If we get here then either the bottom track line in A \ is negative or A < lowestTrackLine, both of which are \ below the lowest level that we want to draw, so we \ cut off the bottom of the object to fit LDA lowestTrackLine \ Set A = lowestTrackLine, so the minimum track line \ number is set to lowestTrackLine and we only draw the \ object down to the lowest line allowed NOP \ These instructions have no effect - presumably they NOP \ are left over from changes during development .drob4 CMP topTrackLine \ If A >= N, then the bottom track line for this object BCS drob9 \ in A is higher than the top track line in N, so jump \ to drob9 to move on to the next object part as there \ is nothing to draw for this part \ We now set up the parameters to pass to DrawObjectEdge \ below, to draw the left and right edges STA bottomTrackLine \ Set bottomTrackLine = A as the bottom track line LDX objectLeft,Y \ Set thisEdge to the scaled scaffold for the left edge LDA scaledScaffold,X \ of this part of the object, to pass to DrawObjectEdge STA thisEdge LDX objectRight,Y \ Set nextEdge to the scaled scaffold for the right LDA scaledScaffold,X \ edge of this part of the object, to pass to STA nextEdge \ DrawObjectEdge LDA objectColour,Y \ Set A to the colour data for this object part STA colourData \ Set colourData to the colour data for this object part STY thisObjectIndex \ Store the current index into the object data in \ thisObjectIndex LDY #1 \ Draw the left edge of this object part JSR DrawObjectEdge .drob5 BIT colourData \ If bit 7 is set in the colour data for this object BMI drob10 \ part, then this is a four-edge object part, so \ jump to drob10 to draw the extra two edges before \ returning here (with bit 7 of colourData clear) to \ draw the fourth edge LDA #0 \ Set A = 0 to send to DrawObjectEdge as the fill colour \ to the right, as there is no fill to the right of the \ object LDY #2 \ Draw the right edge of this object part JSR DrawObjectEdge BIT colourData \ If bit 6 is set in the colour data for this object BVS drob7 \ part, then this indicates that this is the last part \ of this object, so jump to drob7 to return from the \ subroutine as we have now drawn the whole object LDY thisObjectIndex \ Otherwise we need to move on to the next part, so set \ Y to the loop counter .drob6 INY \ Increment the loop counter to point to the data for \ the next object part JMP drob1 \ Loop back to drob1 to process the next object part .drob7 RTS \ Return from the subroutine .drob8 \ We get here when we come across data that forms the \ second and third stages of a four-edge object part, \ so we now need to skip that data as we have already \ processed it AND #%01000000 \ If bit 6 of A is set, i.e. 64 + x, jump to drob7 to BNE drob7 \ return from the subroutine, as we have just drawn the \ last part of the object we wanted to draw INY \ Increment the loop counter to point to the data for \ the next object part .drob9 LDA objectColour,Y \ Set A to the colour data for this object part BMI drob8 \ If bit 7 of A is set, i.e. 128 + x, jump to drob8 to \ skip this bit of data and move on to the next, as this \ contains the data for the second and third edges of a \ four-edge object part, and this will already have \ been processed in drob10 AND #%01000000 \ If bit 6 of A is set, i.e. 64 + x, jump to drob7 to BNE drob7 \ return from the subroutine, as we have just drawn the \ last part of the object we wanted to draw BEQ drob6 \ Jump to drob6 to move on to the next object part (this \ BEQ is effectively a JMP as we just passed through a \ BNE) .drob10 \ If we get here then the colour data for this object \ part has bit 7 set, so this is a four-edge object \ part and we need to draw the second and third edges \ \ The second and third edges are defined in the next bit \ of object data, as follows: \ \ * Second edge: nextEdge = objectLeft \ colourData = objectRight \ \ * Third edge: nextEdge = objectTop \ colourData = objectColour LDY thisObjectIndex \ Set Y to the loop counter INY \ Increment the loop counter to point to the next bit of STY thisObjectIndex \ object data (which contains the data for the second \ and third edges) LDX objectLeft,Y \ Set nextEdge to the scaled data from objectLeft for LDA scaledScaffold,X \ this object part, to pass to DrawObjectEdge STA nextEdge LDA objectRight,Y \ Set colourData to the data from objectRight for this STA colourData \ object part, to pass to DrawObjectEdge LDY #0 \ Draw the second edge of the four-edge object part JSR DrawObjectEdge LDY thisObjectIndex \ Set Y to the index into the object data LDX objectTop,Y \ Set nextEdge to the scaled data from objectTop for LDA scaledScaffold,X \ this object part, to pass to DrawObjectEdge STA nextEdge LDA objectColour,Y \ Set colourData to the data from objectColour for this STA colourData \ object part, to pass to DrawObjectEdge LDY #0 \ Draw the third edge of the four-edge object part JSR DrawObjectEdge JMP drob5 \ Loop back to drob5 to draw the fourth edge, with \ colourData set to the colour data from the third edge, \ which does not have bit 7 set
Name: GetObjYawAngle (Part 1 of 4) [Show more] Type: Subroutine Category: 3D objects Summary: Calculate an object's yaw angle Deep dive: Pitch and yaw angles
Context: See this subroutine on its own page References: This subroutine is called as follows: * BuildRoadSign calls GetObjYawAngle * GetObjectAngles calls via GetObjYawAngle-2 * GetSectionAngles (Part 3 of 3) calls via GetObjYawAngle-2 * GetSegmentYawAngle calls via GetObjYawAngle-2

Arguments: X The offset of the variable to use for the object's 3D coordinates * &F4 = xHelmetCoord * &FA = xCoord1 * &FD = xCoord2 Y The offset of the second variable to use: * 0 = xPlayerCoord * 6 = xRoadSignCoord
Returns: (JJ II) The yaw angle of the object (J I) max(|x-delta|, |z-delta|) (H G) min(|x-delta|, |z-delta|) M The smaller yaw angle of the object, where 0 to 255 represents 0 to 45 degrees X X is preserved
Other entry points: GetObjYawAngle-2 Use xPlayerCoord (Y = 0)
LDY #0 \ Use xPlayerCoord for the second variable when calling \ the routine via GetObjYawAngle-2 .GetObjYawAngle \ The vectors used in this routine are configured by the \ values of X and Y, but for the purposes of simplicity, \ the comments will assume the following: \ \ * X = &FD, xCoord2 \ \ * Y = 0, xPlayerCoord LDA xSegmentCoordILo,X \ Set (VV PP) = xCoord2 - xPlayerCoord SEC \ SBC xPlayerCoordHi,Y \ starting with the low bytes STA PP LDA xSegmentCoordIHi,X \ And then the high bytes SBC xPlayerCoordTop,Y STA VV \ Let's call this difference in x-coordinates x-delta, \ so: \ \ (VV PP) = x-delta BPL rotn1 \ If (VV PP) is positive, jump to rotn1 to skip the \ following LDA #0 \ Set (VV PP) = 0 - (VV PP) SEC \ SBC PP \ starting with the low bytes STA PP LDA #0 \ And then the high bytes SBC VV \ So (VV PP) is now positive, in other words: \ \ (VV PP) = |x-delta| .rotn1 STA SS \ Set (SS PP) = (VV PP) \ = |x-delta| LDA zSegmentCoordILo,X \ Set (GG RR) = zCoord2 - zPlayerCoord SEC \ SBC zPlayerCoordHi,Y \ starting with the low bytes STA RR LDA zSegmentCoordIHi,X \ And then the high bytes SBC zPlayerCoordTop,Y STA GG \ Let's call this difference in z-coordinates z-delta, \ so: \ \ (GG RR) = z-delta BPL rotn2 \ If (GG RR) is positive, jump to rotn2 to skip the \ following LDA #0 \ Set (GG RR) = 0 - (GG RR) SEC \ SBC RR \ starting with the low bytes STA RR LDA #0 \ And then the high bytes SBC GG \ So (GG RR) is now positive, in other words: \ \ (GG RR) = |z-delta| .rotn2 STA UU \ Set (UU RR) = (GG RR) \ = |z-delta| \ At this point we have the following: \ \ (SS PP) = |x-delta| \ \ (UU RR) = |z-delta| \ \ We now compare these two 16-bit values, starting with \ the high bytes, and then the low bytes (if the high \ bytes are the same) CMP SS \ If UU < SS, then (UU RR) < (SS PP), so jump to rotn3 BCC rotn3 BNE rotn4 \ If UU <> SS, i.e. UU > SS, then (UU RR) > (SS PP), so \ jump to rotn4 with the C flag clear \ The high bytes are equal, so now we compare the low \ bytes LDA RR \ If RR >= PP, then (UU RR) >= (SS PP), so jump to rotn4 CMP PP \ with the C flag set BCS rotn4 \ Otherwise (UU RR) < (SS PP), so fall through into \ rotn3 .rotn3 \ If we get here then (UU RR) < (SS PP), so: \ \ |z-delta| < |x-delta| LDA UU \ Set (H G) = (UU RR) STA H \ = |z-delta| LDA RR \ STA G \ and (H G) contains the smaller value LDA PP \ Set (J I) = (SS PP) STA I \ = |x-delta| LDA SS \ STA J \ and (J I) contains the larger value JMP rotn6 \ Jump to rotn6 .rotn4 \ If we get here then (UU RR) >= (SS PP), so: \ \ |z-delta| >= |x-delta| PHP \ Store the status flags on the stack, and in particular \ the Z flag, which will be set if the two match, \ i.e. if |z-delta| = |x-delta| \ \ In other words, a BEQ would branch with these flags LDA SS \ Set (H G) = (SS PP) STA H \ = |x-delta| LDA PP \ STA G \ and (H G) contains the smaller value LDA RR \ Set (J I) = (UU RR) STA I \ = |z-delta| LDA UU \ STA J \ and (J I) contains the larger value PLP \ Retrieve the status flags we stored above BEQ rotn9 \ If (UU RR) = (SS PP), jump to rotn9 JMP rotn14 \ Jump to rotn14
Name: GetObjYawAngle (Part 2 of 4) [Show more] Type: Subroutine Category: 3D objects Summary: Calculate yaw angle for when |x-delta| > |z-delta| Deep dive: Pitch and yaw angles
Context: See this subroutine on its own page References: No direct references to this subroutine in this source file
.rotn5 \ This part is called from below, if we want to scale \ the division ASL RR \ Set (UU RR) = (UU RR) << 1 ROL UU .rotn6 \ If we get here, then: \ \ * (J I) = (A PP) = |x-delta| \ \ * VV is the high byte of x-delta \ \ * (H G) = (UU RR) = |z-delta| \ \ * GG is the high byte of z-delta \ \ * |x-delta| > |z-delta| \ \ We now do the following division so we can use \ trigonometry to calculate the yaw angle: \ \ |z-delta| / |x-delta| \ \ To get started, we shift both 16-bit values to the \ left as far as possible, which we can do without \ affecting the result as we are going to divide the two \ values, so any mutual shifts will cancel each other \ out in the division \ \ Once that's done, we can drop the low bytes and just \ divide the high bytes, which retains as much accuracy \ as possible while avoiding the need for full 16-bit \ division \ \ So we keep shifting left until we get a 1 in bit 7 of \ (A PP), as that's the larger of the two values ASL PP \ Set (A PP) = (A PP) << 1 ROL A BCC rotn5 \ If we just shifted a 0 out of the high byte of (A PP), \ then we can keep shifting, so loop back to rotn6 to \ keep shifting both values ROR A \ We just shifted a 1 out of bit 7 of A, so reverse the \ shift so A contains the correct high byte (we don't \ care about the low byte any more) \ So by this point, (A PP) and (UU RR) have both been \ scaled by the same number of shifts STA V \ Set V = A, the high byte of the scaled |x-delta| LDA RR \ Set T = RR, the low byte of the scaled |z-delta|, to STA T \ use for rounding the result in Divide8x8 LDA UU \ Set A = UU, the high byte of the scaled |z-delta| CMP V \ If A = V then the high bytes of the scaled values BEQ rotn9 \ match, so jump to rotn9, which deals with the case \ when the xVector and zVector values are equal \ We have scaled both values, so now for the division of \ the high bytes JSR Divide8x8 \ Set T = 256 * A / V \ = 256 * |z-delta| / |x-delta| \ \ using the lower byte of the |z-delta| numerator for \ rounding LDA #0 \ Set II = 0 to use as the low byte for the final yaw STA II \ angle LDY T \ Set A = arctanY(T) LDA arctanY,Y \ = arctanY(|z-delta| / |x-delta|) \ \ So this is the yaw angle of the object STA M \ Store the yaw angle in M, to return from the \ subroutine LSR A \ Set (JJ II) = (A 0) >> 3 ROR II \ = A * 256 / 8 LSR A \ = A * 32 ROR II \ = arctanY(|z-delta| / |x-delta|) * 32 LSR A ROR II STA JJ LDA VV \ If VV and GG have different signs, then so do x-delta EOR GG \ and z-delta, so jump to rotn7 BMI rotn7 LDA #0 \ Negate (JJ II) SEC \ SBC II \ starting with the low bytes STA II LDA #0 \ And then the high bytes SBC JJ STA JJ .rotn7 LDA #64 \ Set A = 64, to add to the high byte below BIT VV \ If x-delta is positive, jump to rotn8 to skip the BPL rotn8 \ following instruction \ If we get here then x-delta is negative LDA #&C0 \ Set A = -64, to add to the high byte below .rotn8 CLC \ Set (JJ II) = (JJ II) + (A 0) ADC JJ \ STA JJ \ which is one of the following: \ \ (JJ II) = (JJ II) + 64 * 256 \ \ (JJ II) = (JJ II) - 64 * 256 \ \ depending on the sign of x-delta RTS \ Return from the subroutine
Name: GetObjYawAngle (Part 3 of 4) [Show more] Type: Subroutine Category: 3D objects Summary: Calculate yaw angle for when |x-delta| = |z-delta| Deep dive: Pitch and yaw angles
Context: See this subroutine on its own page References: No direct references to this subroutine in this source file
.rotn9 \ If we get here, then: \ \ * VV is the high byte of x-delta \ \ * GG is the high byte of z-delta \ \ * |x-delta| = |z-delta| LDA #255 \ Set M = 255, to represent a yaw angle of 45 degrees STA M LDA #0 \ Set II = 0 to use as the low byte for the final yaw STA II \ angle BIT VV \ If x-delta is positive, jump to rotn11 BPL rotn11 \ If we get here then x-delta is negative BIT GG \ If z-delta is positive, jump to rotn10 BPL rotn10 \ If we get here then both x-delta and z-delta are \ negative LDA #&A0 \ Set (JJ II) = -96 * 256 STA JJ RTS \ Return from the subroutine .rotn10 \ If we get here then x-delta is negative and y-delta \ is positive LDA #&E0 \ Set (JJ II) = -32 * 256 STA JJ RTS \ Return from the subroutine .rotn11 \ If we get here then x-delta is positive BIT GG \ If z-delta is positive, jump to rotn12 BPL rotn12 \ If we get here then x-delta is positive and y-delta \ is negative LDA #&60 \ Set (JJ II) = 96 * 256 STA JJ RTS \ Return from the subroutine .rotn12 \ If we get here then both x-delta and z-delta are \ positive LDA #&20 \ Set (JJ II) = 32 * 256 STA JJ RTS \ Return from the subroutine
Name: GetObjYawAngle (Part 4 of 4) [Show more] Type: Subroutine Category: 3D objects Summary: Calculate yaw angle for when |x-delta| < |z-delta| Deep dive: Pitch and yaw angles
Context: See this subroutine on its own page References: No direct references to this subroutine in this source file
.rotn13 \ This part is called from below, if we want to scale \ the division ASL PP \ Set (SS PP) = (SS PP) << 1 ROL SS .rotn14 \ If we get here, then: \ \ * (H G) = (SS PP) = |x-delta| \ \ * VV is the high byte of x-delta \ \ * (J I) = (A RR) = |z-delta| \ \ * GG is the high byte of z-delta \ \ * |x-delta| < |z-delta| \ \ We now do the following division so we can use \ trigonometry to calculate the yaw angle: \ \ |x-delta| / |z-delta| \ \ To get started, we shift both 16-bit values to the \ left as far as possible, which we can do without \ affecting the result as we are going to divide the two \ values, so any mutual shifts will cancel each other \ out in the division \ \ Once that's done, we can drop the low bytes and just \ divide the high bytes, which retains as much accuracy \ as possible while avoiding the need for full 16-bit \ division \ \ So we keep shifting left until we get a 1 in bit 7 of \ (A RR), as that's the larger of the two values ASL RR \ Set (A RR) = (A RR) << 1 ROL A BCC rotn13 \ If we just shifted a 0 out of the high byte of (A RR), \ then we can keep shifting, so loop back to rotn13 to \ keep shifting both values ROR A \ We just shifted a 1 out of bit 7 of A, so reverse the \ shift so A contains the correct high byte (we don't \ care about the low byte any more) \ So by this point, (A RR) and (SS PP) have both been \ scaled by the same number of shifts STA V \ Set V = A, the high byte of the scaled |z-delta| LDA PP \ Set T = PP, the low byte of the scaled |x-delta|, to STA T \ use for rounding the result in Divide8x8 LDA SS \ Set A = SS, the high byte of the scaled |x-delta| CMP V \ If A = V then the high bytes of the scaled values BEQ rotn9 \ match, so jump to rotn9, which deals with the case \ when the xVector and zVector values are equal \ We have scaled both values, so now for the division of \ the high bytes JSR Divide8x8 \ Set T = 256 * A / V \ = 256 * |x-delta| / |z-delta| \ \ using the lower byte of the |x-delta| numerator for \ rounding LDA #0 \ Set II = 0 to use as the low byte for the final yaw STA II \ angle LDY T \ Set A = arctanY(T) LDA arctanY,Y \ = arctanY(|x-delta| / |z-delta|) \ \ So this is the yaw angle of the object STA M \ Store the yaw angle in M, to return from the \ subroutine LSR A \ Set (JJ II) = (A 0) >> 3 ROR II \ = A * 256 / 8 LSR A \ = A * 32 ROR II \ = arctanY(|x-delta| / |z-delta|) * 32 LSR A ROR II STA JJ LDA VV \ If VV and GG have different signs, then so do x-delta EOR GG \ and z-delta, so jump to rotn15 BPL rotn15 LDA #0 \ Negate (JJ II) SEC \ SBC II \ starting with the low bytes STA II LDA #0 \ And then the high bytes SBC JJ STA JJ .rotn15 LDA #0 \ Set A = 0, to add to the high byte below BIT GG \ If z-delta is positive, jump to rotn16 to skip the BPL rotn16 \ following instruction \ If we get here then z-delta is negative LDA #&80 \ Set A = -128, to add to the high byte below .rotn16 CLC \ Set (JJ II) = (JJ II) + (A 0) ADC JJ \ STA JJ \ which is one of the following: \ \ (JJ II) = (JJ II) \ \ (JJ II) = (JJ II) - 128 * 256 \ \ depending on the sign of z-delta RTS \ Return from the subroutine
Name: GetObjPitchAngle [Show more] Type: Subroutine Category: 3D objects Summary: Calculate an object's pitch angle Deep dive: Pitch and yaw angles
Arguments: X The offset of the variable to use for the object's 3D coordinates * &F4 = yHelmetCoord * &FA = yCoord1 * &FD = yCoord2 Y The offset of the second variable to use: * 0 = yPlayerCoord * 6 = yRoadSignCoord (L K) The result from GetObjectDistance, which is called between GetObjYawAngle and GetObjPitchAngle
Returns: LL The pitch angle of the object A The pitch angle of the object (same as LL) scaleUp The scale up factor for the object scaleDown The scale down factor for the object C flag Is the object visible on-screen: * Clear if the object is on-screen * Set if it isn't on-screen N flag Set according to the y-coordinate, so a BPL following the call will branch if the y-coordinate is positive
Other entry points: GetObjPitchAngle-2 Use yPlayerCoord (Y = 0)
LDY #0 \ Use xPlayerCoord for the second variable when calling \ the routine via GetObjPitchAngle-2 .GetObjPitchAngle \ The vectors used in this routine are configured by the \ values of X and Y, but for the purposes of simplicity, \ the comments will assume the following: \ \ * X = &FD, yCoord2 \ \ * Y = 0, yPlayerCoord LDA ySegmentCoordILo,X \ Set (WW QQ) = yCoord2 - yPlayerCoord SEC \ SBC yPlayerCoordHi,Y \ starting with the low bytes STA QQ LDA ySegmentCoordIHi,X \ And then the high bytes SBC yPlayerCoordTop,Y STA WW \ Let's call this difference in y-coordinates y-delta, \ so: \ \ (WW QQ) = (A QQ) = y-delta BPL pang1 \ If (A QQ) is positive, jump to pang1 to skip the \ following LDA #0 \ Set (A QQ) = 0 - (WW QQ) SEC \ SBC QQ \ starting with the low bytes STA QQ LDA #0 \ And then the high bytes SBC WW \ So (A QQ) is now positive, in other words: \ \ (A QQ) = |y-delta| .pang1 LSR A \ Set (A QQ) = (A QQ) >> 3 ROR QQ \ = |y-delta| / 8 LSR A ROR QQ LSR A ROR QQ STA TT \ Set (TT QQ) = (A QQ) \ = |y-delta| / 8 \ We now compare the two 16-bit values in (A QQ) and \ (L K) CMP L \ If A < L, then (A QQ) < (L K), so jump to pang3 BCC pang3 BNE pang2 \ If A <> L, i.e. A > L, then (A QQ) > (L K), so jump \ to pang2 to return from the subroutine with the C flag \ set \ The high bytes are equal, so now we compare the low \ bytes LDA QQ \ If QQ < K, then (A QQ) < (L K), so jump to pang3 CMP K BCC pang3 .pang2 \ If we get here then (A QQ) >= (L K), so: \ \ |y-delta| / 8 >= (L K) SEC \ Set the C flag RTS \ Return from the subroutine .pang3 LDY #0 \ Set Y = 0, which we use to count the number of shifts \ in the following calculation LDA L \ Set (A K) = (L K) JMP pang5 \ Jump to pang5 .pang4 \ This part is called from below, if we want to scale \ the division ASL QQ \ Set (TT QQ) = (TT QQ) << 1 ROL TT INY \ Increment Y .pang5 \ If we get here, then: \ \ * (TT QQ) = |y-delta| / 8 \ \ * WW is the high byte of y-delta \ \ * (A K) = |x-delta| \ \ * |x-delta| > |y-delta| / 8 \ \ * Y = 0 \ \ We now do the following division so we can use \ trigonometry to calculate the pitch angle: \ \ (|y-delta| / 8) / |x-delta| \ \ To get started, we shift both 16-bit values to the \ left as far as possible, which we can do without \ affecting the result as we are going to divide the two \ values, so any mutual shifts will cancel each other \ out in the division \ \ We count the number of shifts we do in Y \ \ Once that's done, we can drop the low bytes and just \ divide the high bytes, which retains as much accuracy \ as possible while avoiding the need for full 16-bit \ division \ \ So we keep shifting left until we get a 1 in bit 7 of \ (A K), as that's the larger of the two values ASL K \ Set (A K) = (A K) << 1 ROL A BCC pang4 \ If we just shifted a 0 out of the high byte of (A K), \ then we can keep shifting, so loop back to rotn6 to \ keep shifting both values ROR A \ We just shifted a 1 out of bit 7 of A, so reverse the \ shift so A contains the correct high byte (we don't \ care about the low byte any more) \ So by this point, (A K) and (TT QQ) have both been \ scaled by the same number of shifts STA V \ Set V = A, the high byte of the scaled |x-delta|, \ which we know is at least 128 (as bit 7 is set) STY scaleDown \ Set scaleDown to the number of shifts in Y TAY \ Set scaleUp = 256 / (1 + (A - 128) / 128) LDA divideX-128,Y \ = 256 / (1 + (|x-delta| - 128) / 128) STA scaleUp \ \ We know that A contains the scaled-up |x-delta|, which \ ranges from 128 (when x-delta is small) to 256 (when \ x-delta is large), so scaleUp contains the reciprocal \ of this, i.e. 1/|x-delta|, scaled into the range 256 \ to 128 LDA QQ \ Set T = QQ, the low byte of the scaled |y-delta|, to STA T \ use for rounding the result in Divide8x8 LDA TT \ Set A = TT, the high byte of the scaled |y-delta| JSR Divide8x8 \ Set T = 256 * A / V \ = 256 * (|y-delta| / 8) / |x-delta| \ \ using the lower byte of the |y-delta| numerator for \ rounding LDA T \ If T >= 128, jump to pang8 to return from the CMP #128 \ subroutine with the C flag set BCS pang8 BIT WW \ If y-delta is positive, jump to pang6 to skip the BPL pang6 \ following and add 60 to T LDA #60 \ Set A = 60 - T SEC SBC T JMP pang7 \ Jump to pang7 .pang6 CLC \ Set A = T + 60 ADC #60 .pang7 SEC \ Set LL = A - playerPitchAngle SBC playerPitchAngle STA LL CLC \ Clear the C flag to indicate success .pang8 RTS \ Return from the subroutine
Name: GetSectionAngles (Part 1 of 3) [Show more] Type: Subroutine Category: Track geometry Summary: Get the yaw and pitch angles for the inner and outer track sections Deep dive: Data structures for the track calculations The track verges
Context: See this subroutine on its own page References: This subroutine is called as follows: * GetTrackAndMarkers calls GetSectionAngles

This routine does the following: * Part 1: If we have fetched a new track section since the last call, shuffle the track section list along by one so we can insert the new section * Part 1: Go through the track section list and apply spin to each valid entry (for both the right and left track section), skipping the entry pointed to by the sectionListPointer * Update the entry at sectionListPointer as follows: * Part 2: Calculate the track section number for this entry, relative to the front segment in the track segment buffer * Part 3: Store the yaw and pitch angles for this section in the xVergeRight/Left and yVergeRight/Left tables
Returns: xVergeRight Updated yaw angles for the entries in the track section list (i.e. indexes 0 to 5) for the right verge xVergeLeft Updated yaw angles for the entries in the track section list (i.e. indexes 0 to 5) for the left verge yVergeRight Updated pitch angles for the entries in the track section list (i.e. indexes 0 to 5) for the right verge yVergeLeft Updated pitch angles for the entries in the track section list (i.e. indexes 0 to 5) for the left verge horizonLine Updated to cater for the pitch angles of the updated track sections horizonListIndex Updated to the index of the track section that contains the horizon (i.e. the index within the track section list)
Other entry points: GetSectionAngles-1 Contains an RTS
.GetSectionAngles LDA newSectionFetched \ If newSectionFetched = 0, then we have not fetched a BEQ gsec1 \ new track section since the last call, so jump to \ gsec1 to skip the following call to ShuffleSectionList JSR ShuffleSectionList \ Shuffle the track section list along by one so we can \ insert the new section, updating sectionListValid and \ sectionListPointer accordingly LDA #0 \ Reset newSectionFetched to 0 so we don't call the STA newSectionFetched \ ShuffleSectionList routine again until the next new \ section has been fetched .gsec1 LDY sectionListStart \ If sectionListStart = 6, then the track section list CPY #6 \ is zero-length, so return from the subroutine (as BEQ GetSectionAngles-1 \ GetSectionAngles-1 contains an RTS) \ \ This never happens with the Silverstone track, as for \ this track, sectionListStart is in the range 2 to 5 \ (as sectionListSize is in the range 1 to 4) LDY sectionListValid \ If sectionListValid = 6 then there are no valid CPY #6 \ entries in the track section list, so jump to gsec4 to BEQ gsec4 \ skip the spinning process (as we only apply spin to \ valid sections in the list) \ Otherwise we now loop from Y = sectionListValid up to \ 5 to work through the valid entries in the list, \ applying the yaw angle spin to each one, and skipping \ entry number sectionListPointer as we are going to \ update that entry below .gsec2 CPY sectionListPointer \ If Y = sectionListPointer, jump to gsec3 to move on to BEQ gsec3 \ the next entry in the list, as we are going to update \ this entry below STY T \ Store Y in T so we can retrieve it below when applying \ spin to the left verge TYA \ Set Y = Y + 40 CLC \ ADC #40 \ So Y now points to the section for the right verge TAY JSR SpinTrackSection \ Apply the car's current spin to the right verge track \ section in Y: \ \ * Reset vergeDataRight to zero \ \ * Subtract spinYawAngle from the yaw angles in \ xVergeRightLo, xVergeRightHi \ \ * Subtract spinPitchAngle from the pitch angle in \ yVergeRight \ \ * Update horizonListIndex and horizonLine LDY T \ Retrieve the original value of Y that we stored above JSR SpinTrackSection \ Apply the car's current spin to the left verge track \ section in T: \ \ * Reset vergeDataLeft to zero \ \ * Subtract spinYawAngle from the yaw angles in \ xVergeLeftLo, xVergeLeftHi \ \ * Subtract spinPitchAngle from the pitch angle in \ yVergeLeft \ \ * Update horizonListIndex and horizonLine .gsec3 INY \ Increment the loop counter in Y CPY #6 \ Loop back until we have updated all the valid entries BCC gsec2 \ in the track section list
Name: GetSectionAngles (Part 2 of 3) [Show more] Type: Subroutine Category: Track geometry Summary: Calculate the track section number for this track section entry Deep dive: Data structures for the track calculations The track verges
Context: See this subroutine on its own page References: No direct references to this subroutine in this source file

This part of the routine calculates the number of the track section that we want to update, i.e. the section at entry sectionListPointer in the list.
.gsec4 LDA #6 \ Set A = (6 - sectionListPointer) * 8 SEC \ SBC sectionListPointer \ This calculates the following: ASL A \ ASL A \ * A = 1 * 8 for entry #5 ASL A \ * A = 2 * 8 for entry #4 \ * A = 3 * 8 for entry #3 \ * A = 4 * 8 for entry #2 \ * A = 5 * 8 for entry #1 \ * A = 6 * 8 for entry #0 BIT directionFacing \ If bit 7 of directionFacing is clear, then we are BPL gsec5 \ facing forwards, so jump to gsec5 \ If we get here then we are facing backwards STA T \ Set T = A LDA objTrackSection+23 \ Set Y to the number * 8 of the track section for the \ front segment of the track segment buffer CLC \ Set A = A + 8 - T ADC #8 \ = frontSection * 8 + 8 - T SEC \ = (frontSection + 1 - (T / 8)) * 8 SBC T \ \ So A contains: \ \ * (frontSection - 0) * 8 for entry #5 \ * (frontSection - 1) * 8 for entry #4 \ * (frontSection - 2) * 8 for entry #3 \ * (frontSection - 3) * 8 for entry #2 \ * (frontSection - 4) * 8 for entry #1 \ * (frontSection - 5) * 8 for entry #0 \ \ So A now contains the correct section number for \ entry number sectionListPointer BCS gsec6 \ If the subtraction didn't underflow, jump to gsec6 ADC trackSectionCount \ The subtraction underflowed, so add the total number \ of track sections * 8 given in trackSectionCount to \ wrap round to the correct section number (we know the \ C flag is clear as we just passed through a BCS) JMP gsec6 \ Jump to gsec6 .gsec5 \ If we get here then we are facing forwards CLC \ Set A = A + number * 8 of track section for the ADC objTrackSection+23 \ front segment \ = A + frontSection * 8 \ \ So A contains: \ \ * (1 + frontSection) * 8 for entry #5 \ * (2 + frontSection) * 8 for entry #4 \ * (3 + frontSection) * 8 for entry #3 \ * (4 + frontSection) * 8 for entry #2 \ * (5 + frontSection) * 8 for entry #1 \ * (6 + frontSection) * 8 for entry #0 \ \ So A now contains the correct section number for \ entry number sectionListPointer CMP trackSectionCount \ If A < trackSectionCount then A is a valid section BCC gsec6 \ number, so jump to gsec6 SBC trackSectionCount \ The addition took us past the highest track section \ number, so subtract the total number of track sections \ * 8 given in trackSectionCount to bring it down to the \ correct section number (we know the C flag is set as \ we just passed through a BCC)
Name: GetSectionAngles (Part 3 of 3) [Show more] Type: Subroutine Category: Track geometry Summary: Calculate the yaw and pitch angles for the track section entry that we want to update Deep dive: Data structures for the track calculations The track verges
Context: See this subroutine on its own page References: No direct references to this subroutine in this source file

This part of the routine sets the yaw and pitch angles for this track section in the xVergeRight/Left and yVergeRight/Left tables.
.gsec6 TAY \ Set Y = the section number * 8 that we calculated in \ part 3 STY thisSectionNumber \ Store the section number * 8 in thisSectionNumber, so \ we can retrieve it below when looping back LDX sectionListPointer \ Set X = sectionListPointer, to use as a counter in the \ two loops below \ We run the following section twice, once for the inner \ track section coordinates with X = sectionListPointer, \ and a second time for the outer track section \ coordinates with X = sectionListPointer + 40 .gsec7 STX sectionCounter \ Store the loop counter in sectionCounter LDX #&FD \ Copy the first trackSectionI coordinate for track JSR GetSectionCoord \ section Y into xCoord2, so xCoord2 is the 3D \ coordinate of the inner track at the start of the \ section (or, if this is the second loop where Y has \ been incremented by 3, xCoord2 is the 3D coordinate \ of the outer track) JSR GetObjYawAngle-2 \ Calculate xCoord2's yaw angle, from the point of view \ of the player, returning it in (JJ II) LDY sectionCounter \ Set Y to the loop counter BIT directionFacing \ If bit 7 of directionFacing is clear, then we are BPL gsec8 \ facing forwards, so jump to gsec8 TYA \ We are facing backwards, so flip Y between EOR #40 \ sectionListPointer and sectionListPointer + 40 to do TAY \ the inner and outer track sections in reverse order \ (so we always do the right track verge first, then the \ left track verge, where right and left are relative to \ the direction we are facing) .gsec8 JSR GetSectionYawAngle \ Set the following for the Y-th section, to calculate \ the difference in yaw angle between the track section \ and the player: \ \ xVergeRight = (JJ II) - playerYawAngle \ \ Also set (L K) to the distance between the track \ section and the player's car LDX sectionCounter \ If the loop counter in X >= 40, then we are dealing CPX #40 \ with the outer track section, so jump to gsec10 as we BCS gsec10 \ don't need to repeat the pitch angle calculation (the \ track is level from left to right, so the outer track \ is the same pitch angle as the inner track) LDX #&FD \ Set X = &FD so the call to GetObjPitchAngle uses \ xCoord2, which we set above to the 3D coordinate of \ the inner track at the start of the section JSR GetObjPitchAngle-2 \ Calculate xCoord2's pitch angle, from the point \ of view of the player, returning it in A and LL LDX sectionCounter \ Set X to the loop counter, which we know is less than \ 40 at this point (and which is therefore equal to \ sectionListPointer) LDA LL \ Set A to the pitch angle that we just calculated \ for the track section STA yVergeRight,X \ Store the pitch angle in the X-th yVergeRight \ entry, for this point on the right track section STA yVergeLeft,X \ Store the same pitch angle in the X-th yVergeLeft, \ for this point on the left track section, which will \ at the same pitch angle as the track is level from \ left to right CMP horizonLine \ If A < horizonLine, then this track section is lower BCC gsec10 \ than the current horizon, so jump to gsec10 to move on \ to the outer track section, as this section will not \ be obscuring the horizon BNE gsec9 \ If A <> horizonLine, i.e. A > horizonLine, then this \ means the track section is higher than the current \ horizon line, so jump to gsec9 to set the horizon \ line to the pitch angle of this track section, as the \ section is obscuring the horizon \ If we get here, then A = horizonLine, so this section \ is at the same pitch angle as the current horizon line CPX horizonListIndex \ If X < horizonListIndex, then this section has a lower BCC gsec10 \ index than the current horizon section, so jump to \ gsec10 as horizonListIndex already contains the higher \ index, and a higher index is closer to the player, so \ we don't need to change the horizon line details .gsec9 \ If we get here then we want to update the horizon to \ the pitch angle of the track section we are updating, \ as it obscures the horizon STA horizonLine \ Set horizonLine to the pitch angle in A, so the \ horizon is set to the pitch angle of this track \ section STX horizonListIndex \ Store the index of this section in the track section \ list in horizonListIndex .gsec10 TXA \ Set A = X + 40 CLC \ = sectionListPointer + 40 ADC #40 \ \ So A now points to the outer track section coordinates \ and is ready to be put into X (and, when we look back, \ into sectionCounter) for the loop back to gcsec7 below CMP #60 \ If A >= 60, we have done both inner and outer track BCS gsec11 \ sections, so jump to gsec11 TAX \ Set X = A \ = sectionListPointer + 40 LDA thisSectionNumber \ Set Y = thisSectionNumber + 3 CLC \ ADC #3 \ So when we loop back, the offset in Y points to the TAY \ trackSectionO coordinates for the outer track section \ instead of the inner coordinates in trackSectionI (as \ the outer coordinates are 3 bytes after the inner ones \ in the track data) JMP gsec7 \ Loop back to gsec7 to process the outer track section .gsec11 \ If we get here then we have updated this entry in the \ track section list with both left and right angles, so \ we now update the list pointers LDX sectionListPointer \ Set X = sectionListPointer - 1 DEX JSR SetSectionPointers \ Update the section list pointers to move down through \ the track section list LDA #7 \ If prevHorizonIndex <= 7, then the previous call to CMP prevHorizonIndex \ GetTrackAndMarkers (on the last iteration of the main BCS gsec12 \ driving loop) had the horizon on one of the sections \ in the track section list, or the first entry in the \ track segment list (as the list starts at index 6), so \ jump to gsec12 to skip the following STA horizonLine \ If we get here then the previous iteration around the \ main loop had the horizon line on one of the track \ segments in the track segment list (but not the first \ entry in the list), so set horizonLine to 7 .gsec12 RTS \ Return from the subroutine
Name: GetSegmentYawAngle [Show more] Type: Subroutine Category: Track geometry Summary: Calculate the difference in yaw angle between a track segment and the player
Context: See this subroutine on its own page References: This subroutine is called as follows: * GetSegmentAngles (Part 1 of 3) calls GetSegmentYawAngle * GetSegmentAngles (Part 2 of 3) calls GetSegmentYawAngle

Arguments: X The offset from xSegmentCoordILo of the segment's 3D coordinates, i.e. the segment number * 3, with: * X for inner track segment coordinates * X + 120 for outer track segment coordinates segmentListPointer The index of the segment in the track segment list to use for calculations
Returns: (L K) The distance between the object and the player's car A Contains the high byte of (L K)
.GetSegmentYawAngle JSR GetObjYawAngle-2 \ Calculate the segment's yaw angle, from the point of \ view of the player, returning it in (JJ II) LDY segmentListPointer \ Set Y = segmentListPointer, so the result gets stored \ in the correct position in the track segment list \ Fall through into GetSectionYawAngle to set the \ specified xVergeRight or xVergeLeft to the difference \ in the yaw angle between the player and the segment
Name: GetSectionYawAngle [Show more] Type: Subroutine Category: Track geometry Summary: Calculate the difference in yaw angle between an object and the player
Context: See this subroutine on its own page References: This subroutine is called as follows: * GetSectionAngles (Part 3 of 3) calls GetSectionYawAngle

This routine is typically used to calculate the difference in yaw angle between a track section and the player.
Arguments: Y Index from xVergeRight to store the difference in yaw angle between the object and the player (JJ II) The yaw angle of the object
Returns: xVergeRight The difference in the yaw angle between the object and the player (if Y points to the right verge) xVergeLeft The difference in the yaw angle between the object and the player (if Y points to the left verge) (L K) The distance between the object and the player's car A Contains the high byte of (L K) M The smaller yaw angle of the object, where 0 to 255 represents 0 to 45 degrees
.GetSectionYawAngle LDA II \ Set the following for the Y-th section: SEC \ SBC playerYawAngleLo \ xVergeRight = (JJ II) - playerYawAngle STA xVergeRightLo,Y \ \ starting with the low bytes LDA JJ \ And then the high bytes SBC playerYawAngleHi STA xVergeRightHi,Y JMP GetObjectDistance \ Set (L K) to the distance between the object and the \ player's car, with A set to L, returning from the \ subroutine using a tail call
Name: GetSegmentAngles (Part 1 of 3) [Show more] Type: Subroutine Category: Track geometry Summary: Get the yaw and pitch angles for the inner or outer track segments Deep dive: Data structures for the track calculations The track verges
Context: See this subroutine on its own page References: This subroutine is called as follows: * GetTrackAndMarkers calls GetSegmentAngles

This routine works through track segments, starting from distant segments and working backwards towards the player, calculating the angles and verge data for each segment as we go, up to a maximum of 16 segments (which is the capacity of the track segment list).
Arguments: A The index of the first segment to update in the track segment list, starting at 6 for the first entry in list of right segments, and 46 for the first entry in the list of left segments X The offset from xSegmentCoordILo of the segment's 3D coordinates, i.e. the segment number * 3, with: * X for inner track segment coordinates * X + 120 for outer track segment coordinates segmentOffset The offset to use for this segment: * 0 when our car is facing in the same direction * 120 when our car is facing the opposite direction segmentDirection The relative direction of our car: * 0 when our car is facing in the same direction * 1 when our car is facing the opposite direction
Returns: xVergeRight Updated yaw angles for the entries in the track segment list (i.e. indexes 6 to 21) for the right verge yVergeLeft Updated pitch angles for the entries in the track segment list (i.e. indexes 6 to 21) for the left verge edgeDistance The distance between the player's car and the nearest track edge edgeSegmentNumber The number of the segment within the track segment list that is closest to the player's car edgeSegmentPointer The index of the segment within track verge buffer that is closest to the player's car edgeYawAngle The yaw angle of the segment that is closest to the player's car xVergeRight Entries in the second part of the track segment list for the coordinates of the outside of the right track verge (i.e. indexes 22 to 37, which correspond to the yaw angles in the track segment list in indexes 6 to 21) xVergeLeft Entries in the second part of the track segment list for the coordinates of the outside of the left track verge (i.e. indexes 22 to 37, which correspond to the yaw angles in the track segment list in indexes 6 to 21) yVergeRight Pitch angles for the entries in the track segment list (i.e. indexes 6 to 21) for the right verge yVergeLeft Pitch angles for the entries in the track segment list (i.e. indexes 6 to 21) for the left verge xMarker Distance in the x-axis between the track edge and the corner marker for this segment (if there is one) vergeDataRight Data (such as colour) for this segment's right verge vergeDataLeft Data (such as colour) for this segment's left verge
.GetSegmentAngles STA segmentListPointer \ Set segmentListPointer to the index passed in A LDA #0 \ Set segmentCounter = 0, to use to count visible STA segmentCounter \ segments over the course of the following routine \ We now run the rest of the routine for each segment \ in turn, looping back to here while segments are \ visible .gseg1 JSR GetSegmentYawAngle \ Calculate the yaw angle and distance between the \ player's car and the track segment specified in X, and \ store the results in the track segment list at the \ segment list pointer \ \ Also set (A K) = (L K) = the distance between the car \ and the track segment \ We now check to see if this is the closest track \ segment we've come across in this iteration of the \ main loop, and if it is, we set a bunch of variables \ with the details of the track edge CMP edgeDistanceHi \ If A < edgeDistanceHi, then we know that (A K) and BCC gseg2 \ therefore (L K) < (edgeDistanceHi edgeDistanceLo), \ so jump to gseg2 to set (L K) as the new minimum \ distance to the verge BNE gseg3 \ If A <> edgeDistanceHi, i.e. A > edgeDistanceHi, \ then (L K) > (edgeDistanceHi edgeDistanceLo), so \ jump to gseg3 as (L K) is not a new minimum verge \ distance \ We now compare the high bytes LDA edgeDistanceLo \ If edgeDistanceLo < K, then we know that CMP K \ (L K) > (edgeDistanceHi edgeDistanceLo), so jump to BCC gseg3 \ gseg3 as (L K) is not a new minimum verge distance .gseg2 \ If we get here then we know that \ (L K) <= (edgeDistanceHi edgeDistanceLo), so we now \ set (L K) as the new minimum distance to the verge, \ and set a number of variables so we can refer to this \ nearest track edge in places like the crash routine LDA L \ Set (edgeDistanceHi edgeDistanceLo) = (L K) STA edgeDistanceHi LDA K STA edgeDistanceLo LDA segmentCounter \ Set edgeSegmentNumber = segmentCounter STA edgeSegmentNumber \ \ So edgeSegmentNumber contains the number of the \ segment within the track segment list that is closest \ to the player's car LDY segmentListPointer \ Set edgeSegmentPointer = segmentListPointer STY edgeSegmentPointer \ \ So edgeSegmentPointer contains the index of the \ segment within the track verge buffer (i.e. from \ xVergeRight) that is closest to the player's car LDA xVergeRightHi,Y \ Set edgeYawAngle = the segment's entry in STA edgeYawAngle \ xVergeRightHi \ \ So edgeYawAngle contains the yaw angle of the segment \ that is closest to the player's car, from the point of \ view of the car .gseg3 JSR GetObjPitchAngle-2 \ Calculate the segment's pitch angle, from the \ point of view of the player, returning it in A and LL \ \ If the segment is not visible on-screen, the C flag is \ set, otherwise it will be clear BCS gseg4 \ If the segment is not visible on-screen, jump to gseg4 BPL gseg10 \ If the pitch angle is positive, jump to gseg10
Name: GetSegmentAngles (Part 2 of 3) [Show more] Type: Subroutine Category: Track geometry Summary: Process a segment that is not visible by trying to process a segment that's one-quarter of the size Deep dive: Data structures for the track calculations The track verges
Context: See this subroutine on its own page References: No direct references to this subroutine in this source file
.gseg4 \ If we get here then the segment is not visible or the \ segment's pitch angle is negative, so we need to \ stop processing segments \ \ However, before we stop, we try to eke out as much \ accuracy out of the last (not visible) segment by \ trying to process a segment that's one-quarter of the \ size, just in case this smaller segment is visible, in \ which case we finish with something to show for the \ last visible segment (and if not, at least we tried) LDA segmentCounter \ If segmentCounter is non-zero then we have already BNE gseg5 \ found at least one visible segment, so jump to gseg5 RTS \ Otherwise this is the first segment and it's not \ visible, so return from the subroutine as none of the \ others will be either (as we are working backwards \ through the segments towards the player, so if the \ first segment is not visible, so will all the ones \ behind it) .gseg5 LDA #0 \ Set U = 0, to use as an axis counter below STA U LDY prevSegmentOffset \ Set Y to the offset from xSegmentCoordILo of the \ previous segment's 3D coordinates STX W \ Store the segment offset that's in X in W, so we can \ retrieve it below \ We now loop through all three axes, calculating the \ difference in 3D coordinates between this segment and \ the previous segment for xSegmentCoord, ySegmentCoord \ and zSegmentCoord .gseg6 LDA xSegmentCoordILo,X \ Set (A T) to the difference between the coordinate SEC \ of the previous segment and this one, starting with SBC xSegmentCoordILo,Y \ the low bytes STA T LDA xSegmentCoordIHi,X \ And then the high bytes SBC xSegmentCoordIHi,Y CLC \ Clear the C flag BPL gseg7 \ If the result in (A T) is positive, then jump to gseg7 SEC \ Set the C flag, to indicate that the result is \ negative .gseg7 PHP \ Store the C flag on the stack, which contains the sign \ bit of the result (0 for positive, 1 for negative), so \ we can use it to rotate the correct sign but into \ (A T) in the following ROR A \ Set (A T) = (A T) >> 1 ROR T \ \ making sure to retain the correct sign in bit 7 PLP \ Fetch the C flag from the stack, so it once again \ contains the correct sign for (A T) ROR A \ Set (A T) = (A T) >> 1 ROR T \ \ making sure to retain the correct sign in bit 7 STA V \ Set (V T) = (A T) \ \ So (V T) contains the difference in 3D coordinates, \ divided by 4, and with the correct sign retained LDX U \ Set X to the axis counter in U \ \ For clarity, the following comments will assume we are \ working with the x-axis LDA xSegmentCoordILo,Y \ Set xCoord1 = xSegmentCoord for previous segment CLC \ + (V T) ADC T \ STA xCoord1Lo,X \ starting with the low bytes LDA xSegmentCoordIHi,Y \ And then the high bytes ADC V STA xCoord1Hi,X INX \ Increment the axis counter in X CPX #3 \ If X = 3, we have done all three axes, so jump to BEQ gseg8 \ gseg8 STX U \ Store the incremented value in U, so this is the same \ as incrementing U LDX W \ Set X = W, which we set above to the segment offset \ for the current segment INY \ Increment Y to point to the next axis for the previous \ segment INX \ Increment X to point to the next axis for the current \ segment STX W \ Store the updated segment offset for the current \ segment in W JMP gseg6 \ Loop back to gseg6 to process the next axis .gseg8 \ By the time we get here, xCoord1 contains the 3D \ coordinates of the previous segment, plus a quarter \ of the vector from the previous segment to the current \ segment LDX #&FA \ Set X = &FA so the call to GetSegmentYawAngle uses \ xCoord1 JSR GetSegmentYawAngle \ Calculate the yaw angle and distance between the \ player's car and xCoord1, and store the results in \ the track segment list at the segment list pointer \ \ Also set (A K) = (L K) = the distance between the car \ and xCoord1 JSR GetObjPitchAngle-2 \ Calculate xCoord1's pitch angle, from the point \ of view of the player, returning it in A and LL \ \ If xCoord1 is not visible on-screen, the C flag is \ set, otherwise it will be clear BCS gseg9 \ If xCoord1 is not visible on-screen, jump to gseg9 \ to return from the subroutine \ If we get here then xCoord1 is visible, so we can \ store the results as our final entry in the track \ segment list LDX prevSegmentOffset \ Set X to the offset from xSegmentCoordILo of the \ previous segment's 3D coordinates, so the call to \ GetVergeAndMarkers uses the previous segment's verge \ data for our quarter segment's calculation LDA markersToDraw \ Store markersToDraw in markerNumber so we can restore STA markerNumber \ it after the call to GetVergeAndMarkers (so the call \ doesn't change the value of markersToDraw, as we \ don't want to try drawing markers with this \ quarter-size segment) JSR GetVergeAndMarkers \ Get the details for the previous segment's corner \ markers and verge marks and store them for this \ segment LDA markerNumber \ Retrieve the value of markersToDraw that we stored STA markersToDraw \ in markerNumber, so any marker calculations in the \ above call get ignored INC segmentListPointer \ Increment the segment list pointer as we just added a \ new entry to the track segment list .gseg9 RTS \ Return from the subroutine
Name: GetSegmentAngles (Part 3 of 3) [Show more] Type: Subroutine Category: Track geometry Summary: Process a visible segment Deep dive: Data structures for the track calculations The track verges
Context: See this subroutine on its own page References: No direct references to this subroutine in this source file
.gseg10 \ If we get here then the segment's pitch angle is \ positive and the segment is visible on-screen JSR GetVergeAndMarkers \ Get the details for this segment's corner markers and \ verge marks LDA segmentCounter \ If segmentCounter <= edgeSegmentNumber, jump to gseg13 CMP edgeSegmentNumber \ to keep checking segments, as we haven't yet gone past BEQ gseg13 \ the closest segment to the player BCC gseg13 \ If we get here then we have gone past the closest \ segment to the player, so we need to check whether the \ segment is within the 20-degree field of view, and \ stop when the segments become hidden from view LDY segmentListPointer \ Set Y to the segment list pointer LDA xVergeRightHi,Y \ Set A to the high byte of the yaw angle of the \ segment's right verge BPL gseg11 \ If the angle is negative, negate it, so we now have EOR #&FF \ A = |yaw angle| .gseg11 CMP #20 \ If A < 20, then the segment is within the 20-degree BCC gseg13 \ field of view, so jump to gseg13 to keep checking \ segments LDA xVergeRightHi-1,Y \ Set A to the high byte of the yaw angle of the \ previous segment's right verge BPL gseg12 \ If the angle is negative, negate it, so we now have EOR #&FF \ A = |yaw angle| .gseg12 CMP #20 \ If A >= 20, then the previous segment was also outside BCS gseg16 \ the 20-degree field of view, so jump to gseg16 to \ return from the subroutine JMP gseg4 \ If we get here then the current segment is outside the \ 20-degree field of view, but the previous one wasn't, \ so we jump to gseg4 to try processing a segment that's \ one-quarter of the size, in case that fits .gseg13 \ If we get here then we have successfully processed a \ visible segment STX prevSegmentOffset \ Store the offset from xSegmentCoordILo of this \ segment's 3D coordinates in prevSegmentOffset, to use \ in the next iteration if the next segment is not \ visible INC segmentListPointer \ Increment the segment list pointer to point to the \ next entry in the list INC segmentCounter \ Increment the segment counter to indicate that we have \ populated a visible segment (so this will become 1 if \ this is the first visible segment we have processed, \ 2 for the second visible segment, and so on) LDY segmentCounter \ Set Y to the number of visible segments we have \ populated so far CPY #18 \ If Y >= 18, i.e. Y > 17, then Y was > 16 before we BCS gseg16 \ incremented it, which means we have filled the track \ segment list with 16 visible segments, so we jump to \ gseg16 to return from the subroutine to stop \ processing segments LDA segmentStep,Y \ Set T to the segment step for segment number Y, so to STA T \ get the next segment, we step back T steps in the \ track segment buffer \ \ This makes us step a long way backwards for the first \ few segments, and then make shorter steps as we get \ closer to the player TXA \ Set A to the segment offset that's in X SEC \ Set A = A - segmentOffset SBC segmentOffset \ \ so A contains the number of the segment * 3 (as X \ contains the offset from xSegmentCoordILo, which will \ be 120 + X for the X-th outer segment coordinate, so \ subtracting segmentOffset brings the offset down to \ the number * 3, whether this is an inner or outer \ coordinate) CMP T \ If A >= T, jump to gseg14 to jump back T segments BCS gseg14 \ towards the player, for the next iteration \ If we get here then A < T, so we can't jump back T \ segments or we will jump past the beginning of the \ track segment buffer, so we need to add 120 to wrap \ around to the end of the buffer before we can jump \ back T segments TXA \ Set A to the segment offset that's in X CLC \ Set A = A + 120 to wrap around to the end of the track ADC #120 \ segment buffer JMP gseg15 \ Jump to gseg15 .gseg14 TXA \ Set A to the segment offset that's in X .gseg15 SEC \ Set X = A - T SBC T \ TAX \ So the next segment to be tested is T steps backwards \ in the track segment buffer, towards the player (so \ if T = 3, we step back one segment, or if T = 13 * 3, \ we step back 13 segments) JMP gseg1 \ Loop back to gseg1 to move on to the next segment .gseg16 RTS \ Return from the subroutine
Name: MovePlayerSegment [Show more] Type: Subroutine Category: Car geometry Summary: Move the player's car in the correct direction Deep dive: Placing cars on the track
Context: See this subroutine on its own page References: This subroutine is called as follows: * MainDrivingLoop (Part 2 of 5) calls MovePlayerSegment

This routine checks whether the player has turned enough to be in a different direction (i.e. pointing forwards to pointing backwards or vice versa), and if so, it turns the player around by updating the track segment buffer for the new direction, resetting the track section list, and updating all the direction-related variables. Otherwise it works out whether the player has moved into a new segment, and if so, it updates the car's segment and section numbers accordingly.
.MovePlayerSegment LDA playerHeading \ Set A = playerHeading - spinYawAngleTop SEC \ SBC spinYawAngleTop \ So A contains the new heading of the player's car, \ once the current spin is added (i.e. it's the new \ heading of the car) \ A is an angle that represents the new direction in \ which our car will be facing, after applying spin, \ with respect to the track, like this: \ \ 0 \ -32 | +32 Overhead view of car \ \ | / \ \ | / 0 = looking straight ahead \ \|/ +64 = looking sharp right \ -64 -----+----- +64 -64 = looking sharp left \ /|\ \ / | \ \ / | \ \ -96 | +96 \ 128 \ \ An angle of 0 means our car is facing forwards along \ the track, while an angle of +32 means we are facing \ 45 degrees to the right of straight on, and an angle \ of 128 means we are facing backwards along the track BPL mpla1 \ If A is positive, jump to mpla1 to skip the following EOR #&FF \ Invert A, so this effectively reflects the angle into \ the right half of the above diagram: \ \ 0 \ | 32 \ | / \ | / \ |/ \ +----- 64 \ |\ \ | \ \ | \ \ | 96 \ 127 .mpla1 ASL A \ Set A = A << 1, so we now have: \ \ 0 \ | 64 \ | / \ | / \ |/ \ +----- 128 \ |\ \ | \ \ | \ \ | 192 \ 254 CMP #128 \ Clear the C flag if A < 128 (i.e. top-right quadrant) \ is set the C flag if A >= 128 (i.e. bottom-right \ quadrant) \ Note that bit 7 is similar, so we have: \ \ 0 \ | 64 \ | / <-- C flag and bit 7 clear \ | / \ |/ \ +----- 128 \ |\ \ | \ \ | \ <-- C flag and bit 7 set \ | 192 \ 254 EOR directionFacing \ If we are facing forwards, leave A alone, but if we \ are currently facing backwards, flip bit 7 of A BPL mpla3 \ If we are facing forwards and we are in the top-right \ quadrant, or we are facing backwards and we are in the \ bottom-right quadrant, then the direction we are \ facing is still correct, so jump to mpla3 to get on \ with moving the car \ \ Otherwise we may now be facing in a different \ direction to before, and bit 7 of A is set BCC mpla2 \ If bit 7 of A was clear before the above EOR, then we \ are in the top-right quadrant but are currently facing \ backwards, so jump to mpla2 to skip the following \ instruction EOR #%01111111 \ Bit 7 of A was set before the above EOR, so we are in \ the bottom-right quadrant, but are currently facing \ forwards, so flip bits 0-6 of A, changing the range of \ the bottom-right quadrant from 128 to 254 to \ 255 to 129 .mpla2 \ By this point, we are pointing in the opposite \ direction to the setting of directionFacing, and the \ angles are as follows: \ \ 0 \ | 64 \ | / <-- C flag and bit 7 clear \ | / \ |/_.- 127 \ +----- 255 \ |\-._ 252 \ | \ \ | \ <-- C flag and bit 7 set \ | 192 \ 129 \ \ So 0 to 127 is in the top-right quadrant, while 255 to \ 129 is the bottom-right quadrant CMP #252 \ If A >= 252, then the new angle we are facing is in BCS mpla3 \ the top sliver of the bottom-right quadrant, so jump \ to mpla3 to get on with moving the car \ If we get here then A < 252, which means we are either \ now in the top-right quadrant, or we are in the bottom \ part of the bottom-right quadrant, and we are facing \ in a different direction to directionFacing \ \ So we have now officially turned in the opposite \ direction, and need to update all the various buffers \ and variables JSR ChangeDirection \ Turn the player around by updating the track segment \ buffer for the new direction, resetting the track \ section list, and updating all the direction-related \ variables RTS \ Return from the subroutine .mpla3 \ The GetSegmentAngles routine, which has already been \ called by this point, sets up the track segment list \ and sets edgeSegmentNumber to the entry number within \ the track segment list that is closest to the player's \ car \ \ Entry 13 in the track segment list corresponds to the \ segment that's 32 behind the front segment of the \ track segment buffer, which is the position of the \ player's car, so if edgeSegmentNumber does not equal \ 13, then it means that the car has moved into a new \ segment \ \ Specifically, the values of edgeSegmentNumber mean \ the following: \ \ * 11 = player has moved forward two segments \ * 12 = player has moved forward one segment \ * 13 = player is still in the same segment \ * 14 = player has moved back one segment \ * 15 = player has moved back two segments \ \ The player can't travel more than two segments in one \ iteration of the main driving loop LDA edgeSegmentNumber \ If edgeSegmentNumber = 12, jump to mpla4 to move the CMP #12 \ player forward by one segment BEQ mpla4 BCS mpla5 \ If edgeSegmentNumber > 12, then the player is either \ in the same segment, or has moved backwards, so jump \ to mpla5 \ If we get here then edgeSegmentNumber < 12, so \ edgeSegmentNumber must be 11, so we move the player \ forwards by two segments JSR MovePlayerForward \ Move the player forwards by one segment .mpla4 BIT playerPastSegment \ If bit 0 of playerPastSegment is clear, then the BPL mpla7 \ player has not yet gone past the closest segment, so \ jump to mpla7 to return from the subroutine without \ moving forward by this segment JSR MovePlayerForward \ Move the player forwards by one segment RTS \ Return from the subroutine .mpla5 \ If we get here then edgeSegmentNumber > 12 CMP #14 \ If edgeSegmentNumber < 14, i.e. edgeSegmentNumber is BCC mpla7 \ 13, then the player has not changed segment, so jump \ to mpla7 to return from the subroutine BEQ mpla6 \ If edgeSegmentNumber = 14, jump to mpla6 to move the \ player backwards by one segment \ If we get here then edgeSegmentNumber > 14, so \ edgeSegmentNumber must be 15, so we move the player \ backward by two segments JSR MovePlayerBack \ Move the player backwards by one segment .mpla6 JSR MovePlayerBack \ Move the player backwards by one segment .mpla7 RTS \ Return from the subroutine
Name: GetTrackAndMarkers [Show more] Type: Subroutine Category: Track geometry Summary: Calculate the 3D coordinates of the track and corner markers Deep dive: The track verges Corner markers
Context: See this subroutine on its own page References: This subroutine is called as follows: * MainDrivingLoop (Part 2 of 5) calls GetTrackAndMarkers

Other entry points: gtrm2+6 Calculate the following for segment Y: horizonTrackWidth = |xVergeRightHi - xVergeLeftHi| / 2
.GetTrackAndMarkers LDA #0 \ Set horizonLine = 0, so we can calculate a new pitch STA horizonLine \ angle for the horizon in the following process JSR GetSectionAngles \ Get the yaw and pitch angles for the inner and outer \ track sections in the track section list and store the \ results in xVergeRight/Left and yVergeRight/Left LDA #255 \ Set edgeDistanceHi = 255, so GetSegmentAngles can set STA edgeDistanceHi \ it to the distance of the nearest verge LDA #13 \ Set edgeSegmentNumber = 13, as the default value for STA edgeSegmentNumber \ the number of the segment within the track segment \ list that is closest to the player's car LDA #0 \ Fetch the index details of the right track segments JSR GetSegmentDetails LDA #6 \ Get the yaw and pitch angles for the segments (and the JSR GetSegmentAngles \ verge marks and corner markers) along the right side \ of the track and store the results in xVergeRight, \ yVergeRight, xMarker and vergeDataRight LDA segmentListPointer \ Set segmentListRight = segmentListPointer STA segmentListRight \ \ So it contains the index of the last entry in the \ track segment list for the right side of the track LDA #%10000000 \ Fetch the index details of the left track segments JSR GetSegmentDetails LDA #46 \ Get the yaw and pitch angles for the segments (and the JSR GetSegmentAngles \ verge marks and corner markers) along the left side \ of the track and store the results in xVergeLeft, \ yVergeLeft, xMarker and vergeDataLeft LDA horizonListIndex \ If horizonListIndex < 40, then this is a valid index CMP #40 \ into the track verge buffer so jump to gtrm1 to skip BCC gtrm1 \ the following three instructions SEC \ Set horizonListIndex = horizonListIndex - 40 SBC #40 \ STA horizonListIndex \ so if we set horizonListIndex to the index for the \ outer track coordinates, this corrects the value to \ the index for the inner coordinates .gtrm1 TAY \ Set Y to the corrected value of horizonListIndex STY prevHorizonIndex \ Store the horizon section index in prevHorizonIndex, \ so we can refer to it in the next call to \ GetTrackAndMarkers LDA horizonLine \ If horizonLine < 79, then the horizon line is a valid CMP #79 \ number, so jump to gtrm2 to skip the following two BCC gtrm2 \ instructions LDA #78 \ Set horizonLine = 78, so the maximum value for the STA horizonLine \ horizon line is 78 .gtrm2 STA yVergeRight,Y \ Set the pitch angle for the right side of the horizon \ line in the track verge buffer to the updated value of \ horizonLine STA yVergeLeft,Y \ Set the pitch angle for the left side of the horizon \ line in the track verge buffer to the updated value of \ horizonLine LDA xVergeRightHi,Y \ Set A = xVergeRightHi - xVergeLeftHi for the horizon SEC \ section SBC xVergeLeftHi,Y JSR Absolute8Bit \ Set A = |A|, so A contains the arc of the track at \ the horizon (i.e. the track width on the section or \ segment at the horizon) in terms of the high bytes LSR A \ Set horizonTrackWidth = |A| / 2 STA horizonTrackWidth \ \ So horizonTrackWidth contains half the width of the \ track on the horizon, in terms of the high bytes RTS \ Return from the subroutine
Name: GetSegmentDetails [Show more] Type: Subroutine Category: Track geometry Summary: Get the details for the segment in front or behind Deep dive: Data structures for the track calculations The track verges
Context: See this subroutine on its own page References: This subroutine is called as follows: * GetTrackAndMarkers calls GetSegmentDetails

Arguments: A The direction in which to fetch a segment: * Bit 7 clear = forwards (right) * Bit 7 set = backwards (left) In other words, fetch the track segments from the right or left verges, according to the way we are facing
Returns: segmentOffset The offset to use for this segment: * 0 when our car is facing in direction A * 120 when our car is facing opposite direction A segmentDirection The relative direction of our car: * 0 when our car is facing in direction A * 1 when our car is facing opposite direction A X Returns: * frontSegmentIndex when our car is facing in direction A * frontSegmentIndex + 120 when our car is facing the opposite direction to A (so we use the outer xSegmentCoordOLo rather than the inner xSegmentCoordILo)
.GetSegmentDetails LDX frontSegmentIndex \ Set X to the index * 3 of the front track segment in \ the track segment buffer EOR directionFacing \ If bit 7 of A and bit 7 of directionFacing are the BPL segd1 \ same, jump to segd1 TXA \ Set X = X + 120 CLC ADC #120 TAX LDA #120 \ Set A = 120, so segmentOffset gets set to 120 SEC \ Set the C flag, so segmentDirection gets set to 1 BNE segd2 \ Jump to segd2 (this BNE is effectively a JMP as A is \ never zero) .segd1 LDA #0 \ Set A = 0, so segmentOffset gets set to 0 CLC \ Clear the C flag, so segmentDirection gets set to 0 .segd2 STA segmentOffset \ Set segmentOffset = A LDA #0 \ Set segmentDirection to the C flag ROL A STA segmentDirection RTS \ Return from the subroutine
Name: GetVergeAndMarkers (Part 1 of 4) [Show more] Type: Subroutine Category: Track geometry Summary: Get the details for a segment's corner markers and verge marks Deep dive: The track verges Corner markers
Context: See this subroutine on its own page References: This subroutine is called as follows: * GetSegmentAngles (Part 2 of 3) calls GetVergeAndMarkers * GetSegmentAngles (Part 3 of 3) calls GetVergeAndMarkers

The track verge, which is shown in black-and-white or red-and-white verge marks according to the track data, extends outwards from the track edge, where the track edge is the line defined by the segment vectors. This routine calculates the verge colours and the coordinates of the outside of the verge, and it also calculates the coordinates and colours of the corner markers for this track segment.
Arguments: X The offset from xSegmentCoordILo of the segment's 3D coordinates, i.e. the segment number * 3, with: * X for inner track segment coordinates * X + 120 for outer track segment coordinates LL The segment's pitch angle, from the point of view of the player scaleUp The scale up factor for the segment scaleDown The scale down factor for the segment Results: xVergeRight Entries in the second part of the track segment list for the coordinates of the outside of the right track verge (i.e. indexes 22 to 37, which correspond to the yaw angles in the track segment list in indexes 6 to 21) xVergeLeft Entries in the second part of the track segment list for the coordinates of the outside of the left track verge (i.e. indexes 22 to 37, which correspond to the yaw angles in the track segment list in indexes 6 to 21) yVergeRight Pitch angles for the entries in the track segment list (i.e. indexes 6 to 21) for the right verge yVergeLeft Pitch angles for the entries in the track segment list (i.e. indexes 6 to 21) for the left verge xMarker Distance in the x-axis between the track edge and the corner marker for this segment (if there is one) vergeDataRight Data (such as colour) for this segment's right verge vergeDataLeft Data (such as colour) for this segment's left verge
.GetVergeAndMarkers LDY segmentDirection \ Set Y to segmentDirection, which will be 0 when our \ car is facing in the same direction as the segment we \ are checking, or 1 if it's the opposite direction \ \ This determines whether we are creating the left or \ right verge, with 0 for the left verge and 1 for the \ right verge CPX #120 \ If X >= 120, jump to gmar1 to subtract 120 from the BCS gmar1 \ offset LDA segmentFlags,X \ Set A to the flags for this track segment from the \ track segment buffer BCC gmar2 \ Jump to gmar2 (this BCC is effectively a JMP as we \ just passed through a BCS) .gmar1 LDA segmentFlags-120,X \ Set A to the flags for this track segment from the \ track segment buffer .gmar2 AND segmentFlagMask,Y \ Extract the relevant bits of the segment's flags: STA W \ \ W = A AND %00101101 if Y = 0 (right verge) \ %00110011 if Y = 1 (left verge) \ \ So when we are processing the right verge, we extract \ these flags into W while zeroing the rest: \ \ * Bit 0 (section shape) \ * Bit 2 (colour of right verge marks) \ * Bit 3 (show right corner markers) \ * Bit 5 (corner marker colours) \ \ and when we are processing the left verge, we extract \ these flags into W while zeroing the rest: \ \ * Bit 0 (section shape) \ * Bit 1 (colour of left verge marks) \ * Bit 4 (show left corner markers) \ * Bit 5 (corner marker colours) AND #%00000111 \ Set Y = bits 0-2 of W, so Y is in the range 0 to 7, TAY \ where the possible values are as follows: \ \ * Y = 0 = %000 = black right, black left, straight \ * Y = 1 = %001 = black right, black left, curve \ * Y = 2 = %010 = black right, red left, straight \ * Y = 3 = %011 = black right, red left, curve \ * Y = 4 = %100 = red right, black left, straight \ * Y = 5 = %101 = red right, black left, curve \ * Y = 6 = %110 = red right, red left, straight \ * Y = 7 = %111 = red right, red left, curve LDA vergeColour,Y \ When we are processing the right verge, we know bit 1 STA V \ is clear, so the possible values of Y are as follows: \ \ * Y = 0 = %000 = black right, black left, straight \ * Y = 1 = %001 = black right, black left, curve \ * Y = 4 = %100 = red right, black left, straight \ * Y = 5 = %101 = red right, black left, curve \ \ When we are processing the left verge, we know bit 2 \ is clear, so the possible values of Y are as follows: \ \ * Y = 0 = %000 = black right, black left, straight \ * Y = 1 = %001 = black right, black left, curve \ * Y = 2 = %010 = black right, red left, straight \ * Y = 3 = %011 = black right, red left, curve \ \ So if Y = 0 or 1, then we know that the verge we are \ processing is black-and-white, otherwise it is \ red-and-white \ \ These instructions set V to the Y-th entry in the \ vergeColour table, which contains the following: \ \ * 0 when Y = 0 to 1 (black-and-white verge) \ * 1 when Y = 2 to 7 (red-and-white verge) \ \ So V = 0 if this is a black-and-white verge \ 1 if this is a red-and-white verge LDA segmentCounter \ If segmentCounter >= 3 then jump to gmar3 to process CMP #3 \ the segment's corner markers in part 2 BCS gmar3 JMP gmar9 \ Otherwise segmentCounter is 0 to 2, so jump to gmar9 \ to skip the corner markers and move on to the verge \ marks in part 4
Name: GetVergeAndMarkers (Part 2 of 4) [Show more] Type: Subroutine Category: Track geometry Summary: Calculate the segment's verge width and outside verge coordinates
Context: See this subroutine on its own page References: No direct references to this subroutine in this source file
.gmar3 \ We calculate the verge width as follows: \ \ (U A) = scaleUp * 2 ^ (scaleDown - vergeScale) \ \ to determine the width of the verge marks on the side \ of the track \ \ The higher the value of (U A), the wider the verge for \ this segment \ \ The vergeScale factor is between 3 and 5, and scales \ the verge width differently for different track \ configurations, with larger values of vergeScale \ giving smaller verges \ \ This gives the following: \ \ * If both verges are black-and-white, then the \ verges are thin (vergeScale = 5), on both curved \ and straight sections \ \ * If this is a curve and at least one of the verges \ is red-and-white, or we're on a straight and both \ verges are red-and-white, then the verges are \ medium thickness (vergeScale = 4) \ \ * If this is a straight and only one of the verges \ is red-and-white, then the verges are thick \ (vergeScale = 3) LDA scaleDown \ Set Y = scaleDown - vergeScale SEC SBC vergeScale,Y TAY LDA #0 \ Set U = 0, to use as the high byte in (U A) STA U LDA scaleUp \ Set A = scaleUp \ \ So (U A) = scaleUp DEY \ Set Y = Y - 1 \ = scaleDown - vergeScale - 1 \ We now scale (U A) by 2 ^ Y, so if Y is 0 we don't \ do any scaling, if it's negative we scale down, and \ if it's positive we scale up \ \ Note that the -1 in the scale factor calculation is \ reversed by the right-shift that we apply below when \ setting bit 7 of the shifted result, so the result is \ as above, despite the extra -1 BEQ gmar6 \ If Y = 0, then there is no scaling to be done, so jump \ to gmar6 BPL gmar5 \ If Y > 0, then we need to scale up, so jump to gmar5 \ If we get here then Y < 0, so we need to scale down, \ specifically by right-shifting (U A) by |Y| places .gmar4 LSR U \ Set (U A) = (U A) >> 1 ROR A INY \ Increment the shift counter in Y BNE gmar4 \ Loop back to gmar4 to keep shifting right until we \ have shifted by |Y| places BEQ gmar6 \ Jump to gmar6 (this BEQ is effectively a JMP, as we \ just passed through a BNE) .gmar5 \ If we get here then Y > 0, so we need to scale up, \ specifically by left-shifting (U A) by Y places ASL A \ Set (U A) = (U A) << 1 ROL U DEY \ Decrement the shift counter in Y BNE gmar5 \ Loop back to gmar5 to keep shifting left until we \ have shifted by Y places .gmar6 STA T \ Set (U T) = (U A) \ \ So (U T) contains our scaled value LDA segmentDirection \ Set the C flag to bit 0 of segmentDirection, which LSR A \ will be 0 when our car is facing in the same direction \ as the segment we are checking, or 1 if it's the \ opposite direction ROR A \ Set A = A >> 1 and set bit 7 to the C flag EOR directionFacing \ If the C flag matches directionFacing, jump to gmar7 BPL gmar7 \ If we get here then this is the left verge, so we need \ to negate (U T) so the outside of the verge is to the \ left of the track, i.e. in a negative direction along \ the x-axis LDA #0 \ Negate (U T), starting with the low bytes SEC SBC T STA T LDA #0 \ And then the high bytes SBC U STA U \ So we now have our verge width result: \ \ (U T) = scaleUp * 2 ^ (scaleDown - vergeScale) \ \ where the sign of (U T) is positive for the right \ verge and negative for the left verge .gmar7 LDY segmentListPointer \ Set Y to the index of the current entry in the track \ segment list \ We now calculate the coordinates for the outside edge \ of the track verge by adding the verge width in (U T) \ to the track segment's verge coordinates, storing the \ result in the track segment list, 16 bytes after the \ corresponding track segment entry (so indexes 6 to 21 \ contain the track segment list, while indexes 22 to 37 \ contain the corresponding entries for the outside of \ the verge) LDA xVergeRightLo,Y \ Set (xVergeRightHi+16 xVergeRightLo+16) CLC \ = (xVergeRightHi xVergeRightLo) + (U T) ADC T \ STA xVergeRightLo+16,Y \ starting with the low bytes LDA xVergeRightHi,Y \ And then the high bytes ADC U STA xVergeRightHi+16,Y
Name: GetVergeAndMarkers (Part 3 of 4) [Show more] Type: Subroutine Category: Track geometry Summary: Process the segment's corner markers
Context: See this subroutine on its own page References: No direct references to this subroutine in this source file
LDA W \ If bits 3 and 4 of W are clear, which are these bits AND #%00011000 \ in the segment flags: BEQ gmar9 \ \ * Bit 3 (show right corner markers) \ * Bit 4 (show left corner markers) \ \ then we do not show any corner markers for this \ segment, so jump to gmar9 to move on to the verge \ marks in part 4 \ If we get here then we have a marker to draw for this \ segment LDY markersToDraw \ Set Y to the number of markers we have to draw CPY #3 \ If Y >= 3, then we already have three markers ready BCS gmar9 \ to show, which is the maximum at any one time, so \ jump to gmar9 to skip the following LDA segmentListPointer \ Set markerListIndex for marker Y to segmentListPointer STA markerListIndex,Y LDA W \ Set markerData for marker Y to the segment flags for STA markerData,Y \ this marker in W AND #1 \ If bit 0 of W is clear, then this is a straight track BEQ gmar8 \ section, so jump to gmar8 to skip the following \ instruction \ This is a curved section, so move the markers closer \ to the track edge by halving the distance that we \ store in xMarker LSR U \ Set (U T) = (U T) >> 1 ROR T .gmar8 LDA T \ Set (xMarkerHi xMarkerLo) for marker Y to (U T), so STA xMarkerLo,Y \ xMarker contains the width of the verge (halved if LDA U \ this is a corner), which we can use as the x-axis STA xMarkerHi,Y \ distance from the track verge to the marker INC markersToDraw \ Increment markersToDraw, as we have just added a new \ marker to the list
Name: GetVergeAndMarkers (Part 4 of 4) [Show more] Type: Subroutine Category: Track geometry Summary: Store details of the segment's verge marks
Context: See this subroutine on its own page References: No direct references to this subroutine in this source file
.gmar9 \ The verge marks are either black-white-black-white \ or red-white-red-white, so we now work out which of \ these colours applies to this segment TXA \ If bit 0 of X is clear, then this is a non-white verge AND #%00000001 \ mark, so jump to gmar10 to set A = V to use as the BEQ gmar10 \ vergeDataRight for this segment LDA #2 \ Otherwise this is a white verge mark, so set A = 2 \ to use as the vergeDataRight for this segment BNE gmar11 \ Jump to gmar11 (this BNE is effectively a JMP as A is \ never zero) .gmar10 LDA V \ Set A = V, which is 0 (black verge mark) or 1 (red \ verge mark) .gmar11 LDY segmentListPointer \ Set Y to the index of the current entry in the track \ segment list STA vergeDataRight,Y \ Store A in the segment's corresponding vergeDataRight, \ so that's 2 for a white verge mark, 1 for a red verge \ mark, and 0 for a black verge mark LDA LL \ Set A to the segment's pitch angle, from the point \ of view of the player STA yVergeRight,Y \ Store the result in the segment's entry in yVergeRight \ to set the segment's pitch angle CMP #80 \ If the pitch angle is 80 or more, jump to gmar12 BCS gmar12 \ to return from the subroutine CMP horizonLine \ If the pitch angle is less than horizonLine, jump BCC gmar12 \ to gmar12 to return from the subroutine \ If we get here then the pitch angle in A is less \ than 80 and is greater or equal to horizonLine STA horizonLine \ This track segment is higher than the current horizon \ pitch angle, so the track obscures the horizon and we \ need to update horizonLine to this new pitch angle STY horizonListIndex \ Set horizonListIndex to the track segment number in Y .gmar12 RTS \ Return from the subroutine
Name: HideAllCars [Show more] Type: Subroutine Category: Car geometry Summary: Set all the cars to hidden
Context: See this subroutine on its own page References: This subroutine is called as follows: * FinishRace calls HideAllCars * MoveAndDrawCars calls HideAllCars
.HideAllCars LDX #22 \ We are about to process the car status bytes for \ drivers 0 to 19, plus the three extra car objects in \ 20 to 22 that make up the four-object car, so set a \ loop counter in X .hide1 LDA objectStatus,X \ Set bit 7 in the X-th byte of objectStatus to set the ORA #%10000000 \ car for driver X to be hidden STA objectStatus,X DEX \ Decrement the loop counter BPL hide1 \ Loop back until we have hidden all 23 cars RTS \ Return from the subroutine
Name: Delay [Show more] Type: Subroutine Category: Main loop Summary: Delay for a specified number of loops
Context: See this subroutine on its own page References: This subroutine is called as follows: * MoveAndDrawCars calls Delay

This routine performs T + (5 * 256) loop iterations, to create a delay. The value of T doesn't have much effect on the amount of delay, so it looks like this variable was chosen simply because it doesn't contain anything useful at this point.
.Delay LDX #6 \ Set X as the counter for the outer loop .dely1 DEC T \ Loop around for T iterations in the inner loop BNE dely1 DEX \ Loop around for X iterations in the outer loop BNE dely1 RTS \ Return from the subroutine
Name: MoveAndDrawCars [Show more] Type: Subroutine Category: Car geometry Summary: Move the cars around the track and draw any that are visible, up to a maximum of five
Context: See this subroutine on its own page References: This subroutine is called as follows: * MainDrivingLoop (Part 2 of 5) calls MoveAndDrawCars
.MoveAndDrawCars LDA qualifyingTime \ If bit 7 of qualifyingTime is set then this is a BMI Delay \ practice lap (i.e. qualifyingTime = 255), so there are \ no other cars to draw \ \ To maintain the same game speed as for races, we jump \ to Delay to pause for a while before returning from \ the subroutine using a tail call LDX positionBehind \ Set X to the position of the driver behind us LDY driversInOrder,X \ Set Y to the number of the driver in behind us LDA objectStatus,Y \ Clear bit 7 of the car object's status byte, to flag AND #%01111111 \ the car behind us as being visible STA objectStatus,Y JSR MoveCars \ Move the cars around the track JSR ProcessOvertaking \ Process overtaking manoeuvres for the non-player \ drivers JSR HideAllCars \ Set all the cars to be hidden JSR SetPlayerPositions \ Set the current player's position, plus the position \ ahead and the position behind LDX currentPosition \ Set X to the current player's position LDY #5 \ We now work our way through the five nearest cars in \ front of us, so set a loop counter in Y .dcar1 BIT directionFacing \ If bit 7 of directionFacing is clear, then we are BPL dcar2 \ facing forwards, so jump to dcar2 JSR GetPositionBehind \ We are facing backwards, so set X to the number of \ the position behind position X, to get the number of \ the car that we are looking at JMP dcar3 \ Jump to dcar3 to skip the following .dcar2 JSR GetPositionAhead \ We are facing forwards, so set X to the number of the \ position ahead of position X, to get the number of \ the car that we are looking at .dcar3 STY thisDriverNumber \ Store the loop counter in thisDriverNumber so we can \ retrieve it after the following call STX thisPosition \ Store the position of the car we are considering in \ thisPosition JSR BuildVisibleCar \ Build the car object if it is visible, so we can draw \ it below LDX thisPosition \ Retrieve the position of the car that we stored in \ thisPosition above LDY thisDriverNumber \ Retrieve the value of the loop counter that we stored \ in thisDriverNumber above DEY \ Decrement the loop counter BPL dcar1 \ Loop back until we have processed five cars in front JSR DrawCars \ Draw all the cars, with the closest car in front of us \ split into four objects LDX positionBehind \ Set X to the position of the driver behind us JSR BuildVisibleCar \ Build the car object if it is visible, so it can be \ shown in the mirror if close enough RTS \ Return from the subroutine
Name: SwapDriverPosition [Show more] Type: Subroutine Category: Drivers Summary: Swap the position for two drivers (i.e. overtake)
Context: See this subroutine on its own page References: This subroutine is called as follows: * ProcessOvertaking (Part 1 of 3) calls SwapDriverPosition * ResetVariables calls SwapDriverPosition

Arguments: X The first position Y The second position
Returns: X The number of the driver now at position X Y The number of the driver now at position Y
.SwapDriverPosition LDA driversInOrder,X \ Set T to the number of the driver at position X STA T LDA driversInOrder,Y \ Set A to the number of the driver at position Y STA driversInOrder,X \ Set the driver at position X to the driver from \ position Y TAX \ Set X to the number of the driver now at position X LDA T \ Set the driver at position y to the driver from STA driversInOrder,Y \ position X TAY \ Set Y to the number of the driver now at position Y RTS \ Return from the subroutine